diff --git a/README.md b/README.md index 076d11f..1959fc6 100644 --- a/README.md +++ b/README.md @@ -54,3 +54,13 @@ Stack2nix can generate a nix expressions for Haskell packages hosted in git repo ## Testing Run `./scripts/travis.sh` to build and test. + +## Development + +### Updating GHC base packages + +``` +curl https://raw.githubusercontent.com/bgamari/ghc-utils/master/library-versions/pkg_versions.txt > pkg_versions.txt +``` + +then check it into the repo. diff --git a/nixpkgs-src.json b/nixpkgs-src.json index c31792d..ce18ee6 100644 --- a/nixpkgs-src.json +++ b/nixpkgs-src.json @@ -1,6 +1,6 @@ { "owner": "NixOS", "repo": "nixpkgs", - "rev": "872502aa56bd4d574fcfe9cfef9066c9e8ee2894", - "sha256": "07kbsnrmcrr0nnb91vbm6p3ixww9c5fgia0drx14y2hcc0292s8s" + "rev": "cfed29bfcb28259376713005d176a6f82951014a", + "sha256": "1pvhhns513d5j121yvqspcfax70sn9b7xab5bnavlf7y0hnnbb6l" } diff --git a/src/Stack2nix.hs b/src/Stack2nix.hs index 2cd38dd..a699c0e 100644 --- a/src/Stack2nix.hs +++ b/src/Stack2nix.hs @@ -10,7 +10,8 @@ module Stack2nix import Control.Monad (unless, void, when) import Data.Maybe (isJust) -import Data.Monoid ((<>)) +import Path +import Path.IO import Paths_stack2nix (version) import Stack2nix.External.Stack import Stack2nix.External.Util (runCmdFrom, failHard) @@ -18,11 +19,7 @@ import Stack2nix.External.VCS.Git (Command (..), ExternalCmd (..), InternalCmd (..), git) import Stack2nix.Types (Args (..)) import Stack2nix.Util -import System.Directory (doesFileExist, - getCurrentDirectory, withCurrentDirectory) import System.Environment (getEnv, setEnv) -import System.FilePath (()) -import System.IO.Temp (withSystemTempDirectory) stack2nix :: Args -> IO () stack2nix args@Args{..} = do @@ -36,15 +33,16 @@ stack2nix args@Args{..} = do updateCabalPackageIndex -- cwd <- getCurrentDirectory -- let projRoot = if isAbsolute argUri then argUri else cwd argUri - let projRoot = argUri - isLocalRepo <- doesFileExist $ projRoot argStackYaml + projRoot <- resolveDir' argUri + stackYaml <- resolveFile projRoot argStackYaml + isLocalRepo <- doesFileExist stackYaml logDebug args $ "stack2nix (isLocalRepo): " ++ show isLocalRepo logDebug args $ "stack2nix (projRoot): " ++ show projRoot logDebug args $ "stack2nix (argUri): " ++ show argUri if isLocalRepo then handleStackConfig Nothing projRoot - else withSystemTempDirectory "s2n-" $ \tmpDir -> - tryGit tmpDir >> handleStackConfig (Just argUri) tmpDir + else withSystemTempDir "s2n-" $ \tmpDir -> + tryGit (fromAbsDir tmpDir) >> handleStackConfig (Just argUri) tmpDir where updateCabalPackageIndex :: IO () updateCabalPackageIndex = do @@ -59,17 +57,17 @@ stack2nix args@Args{..} = do Just r -> void $ git $ InsideRepo tmpDir (Checkout r) Nothing -> return mempty - handleStackConfig :: Maybe String -> FilePath -> IO () + handleStackConfig :: Maybe String -> Path Abs Dir -> IO () handleStackConfig remoteUri localDir = do - cwd <- getCurrentDirectory - logDebug args $ "handleStackConfig (cwd): " ++ cwd - logDebug args $ "handleStackConfig (localDir): " ++ localDir + cwd <- getCurrentDir + logDebug args $ "handleStackConfig (cwd): " ++ fromAbsDir cwd + logDebug args $ "handleStackConfig (localDir): " ++ fromAbsDir localDir logDebug args $ "handleStackConfig (remoteUri): " ++ show remoteUri - let stackFile = localDir argStackYaml + stackFile <- resolveFile localDir argStackYaml alreadyExists <- doesFileExist stackFile - unless alreadyExists $ error $ stackFile <> " does not exist. Use 'stack init' to create it." + unless alreadyExists $ error $ fromAbsFile stackFile <> " does not exist. Use 'stack init' to create it." logDebug args $ "handleStackConfig (alreadyExists): " ++ show alreadyExists let go = if isJust remoteUri - then withCurrentDirectory localDir + then withCurrentDir localDir else id go $ runPlan localDir remoteUri args diff --git a/src/Stack2nix/External/Cabal2nix.hs b/src/Stack2nix/External/Cabal2nix.hs index aea62bf..1bdd152 100644 --- a/src/Stack2nix/External/Cabal2nix.hs +++ b/src/Stack2nix/External/Cabal2nix.hs @@ -13,6 +13,7 @@ import Data.Text (Text, unpack) import qualified Distribution.Nixpkgs.Haskell.Hackage as DB import Distribution.Nixpkgs.Haskell.Derivation (Derivation) import Distribution.PackageDescription (unFlagName) +import Distribution.Pretty (prettyShow) import Distribution.System (Platform(..), Arch(..), OS(..)) import Language.Nix import System.IO (hPutStrLn, stderr) @@ -35,7 +36,7 @@ cabal2nix Args{..} ghcVersion uri commit subpath flags hackageDB = do , maybeToList argCabal2nixArgs , ["--subpath", dir] , ["--system", fromCabalPlatform argPlatform] - , ["--compiler", "ghc-" ++ show ghcVersion] + , ["--compiler", "ghc-" ++ prettyShow ghcVersion] , ["-f" ++ bool "-" "" enable ++ unFlagName f | (f, enable) <- flags] , [uri] ] diff --git a/src/Stack2nix/External/Stack.hs b/src/Stack2nix/External/Stack.hs index 2672029..cb3ee6d 100644 --- a/src/Stack2nix/External/Stack.hs +++ b/src/Stack2nix/External/Stack.hs @@ -1,202 +1,164 @@ {-# LANGUAGE DataKinds #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE TemplateHaskell #-} module Stack2nix.External.Stack ( PackageRef(..), runPlan ) where -import Control.Lens ((%~)) -import Control.Monad (when) -import Data.List (concat) +import Control.Lens ((<>~)) import qualified Data.Map.Strict as M import Data.Maybe (fromJust) -import qualified Data.Set as Set (fromList, - union) -import Data.Text (pack, unpack) +import qualified Data.Set as Set (fromList) +import Data.Text (pack, + unpack) import Distribution.Nixpkgs.Haskell.Derivation (Derivation, configureFlags) import qualified Distribution.Nixpkgs.Haskell.Hackage as DB +import Distribution.Pretty (prettyShow) +import Distribution.Types.PackageName (unPackageName) import Options.Applicative -import Path (parseAbsFile) -import Stack.Build.Source (getGhcOptions, loadSourceMapFull) +import Path (fromRelDir, + mkAbsDir) +import Path.IO import Stack.Build.Target (NeedTargets (..)) -import Stack.Config import Stack.Options.BuildParser import Stack.Options.GlobalParser import Stack.Options.Utils (GlobalOptsContext (..)) import Stack.Prelude hiding - (logDebug) -import Stack.Runners (loadCompilerVersion, - withBuildConfig) -import Stack.Types.BuildPlan (PackageLocation (..), - Repo (..)) -import Stack.Types.Compiler (getGhcVersion) + (logDebug) +import Stack.Runners (ShouldReexec(..), + withConfig, + withEnvConfig, + withRunnerGlobal) +import Stack.Types.Compiler (ActualCompiler(..)) import Stack.Types.Config -import Stack.Types.Config.Build (BuildCommand (..)) -import Stack.Types.FlagName (toCabalFlagName) import Stack.Types.Nix -import Stack.Types.Package (PackageSource (..), - lpLocation, - lpPackage, - packageFlags, - packageName, - packageVersion) -import Stack.Types.PackageIdentifier (PackageIdentifier (..), - PackageIdentifierRevision (..), - packageIdentifierString) -import Stack.Types.PackageName (PackageName, parsePackageName) -import Stack.Types.Runner -import Stack.Types.Version (Version) +import Stack.Types.SourceMap (SourceMap(..), + CommonPackage(..)) import Stack2nix.External.Cabal2nix (cabal2nix) import Stack2nix.Hackage (loadHackageDB) import Stack2nix.Render (render) -import Stack2nix.Types (Args (..), Flags) +import Stack2nix.Types (Args (..), Flags, GhcOptions) import Stack2nix.Util (ensureExecutable, logDebug, mapPool) -import System.Directory (canonicalizePath, - createDirectoryIfMissing, - getCurrentDirectory, - makeRelativeToCurrentDirectory) -import System.FilePath (makeRelative, - ()) import Text.PrettyPrint.HughesPJClass (Doc) data PackageRef - = HackagePackage Flags PackageIdentifierRevision - | NonHackagePackage Flags PackageIdentifier (PackageLocation FilePath) + = HackagePackage GhcOptions Flags PackageIdentifier -- TODO: what about revisions? + | NonHackagePackage GhcOptions Flags (ResolvedPath Dir) deriving (Eq, Show) -genNixFile :: Args -> Version -> FilePath -> Maybe String -> Maybe String -> DB.HackageDB -> PackageRef -> IO (Either Doc Derivation) -genNixFile args ghcVersion baseDir uri argRev hackageDB pkgRef = do - cwd <- getCurrentDirectory +genNixFile :: Args -> Version -> Path Abs Dir -> Maybe String -> Maybe String -> DB.HackageDB -> PackageRef -> IO (Either Doc Derivation) +genNixFile args ghcVersion _baseDir uri argRev hackageDB pkgRef = do case pkgRef of - NonHackagePackage _flags _ident PLArchive {} -> error "genNixFile: No support for archive package locations" - HackagePackage flags (PackageIdentifierRevision pkg _) -> - cabal2nix args ghcVersion ("cabal://" <> packageIdentifierString pkg) Nothing Nothing flags hackageDB - NonHackagePackage flags _ident (PLRepo repo) -> - cabal2nix args ghcVersion (unpack $ repoUrl repo) (Just $ repoCommit repo) (Just (repoSubdirs repo)) flags hackageDB - NonHackagePackage flags _ident (PLFilePath path) -> do - relPath <- makeRelativeToCurrentDirectory path - projRoot <- canonicalizePath $ cwd baseDir - let defDir = baseDir makeRelative projRoot path - cabal2nix args ghcVersion (fromMaybe defDir uri) (pack <$> argRev) (const relPath <$> uri) flags hackageDB + HackagePackage ghcOptions flags pkgId -> + fmap (addGhcOptions ghcOptions) <$> + cabal2nix args ghcVersion ("cabal://" <> packageIdentifierString pkgId) Nothing Nothing flags hackageDB + NonHackagePackage ghcOptions flags path -> do + relPath <- fromRelDir <$> makeRelativeToCurrentDir (resolvedAbsolute path) + let cabal2nix_uri = fromMaybe (toFilePath $ resolvedAbsolute path) uri + let commit = pack <$> argRev + let subpath = const relPath <$> uri + fmap (addGhcOptions ghcOptions) <$> + cabal2nix args ghcVersion cabal2nix_uri commit subpath flags hackageDB -- TODO: remove once we use flags, options -sourceMapToPackages :: Map PackageName PackageSource -> [PackageRef] -sourceMapToPackages = map sourceToPackage . M.elems +sourceMapToPackages :: SourceMap -> [PackageRef] +sourceMapToPackages sm = + map depPkgToPackage (M.elems $ smDeps sm) <> map projPkgToPackage (M.elems $ smProject sm) where - sourceToPackage :: PackageSource -> PackageRef - sourceToPackage (PSIndex _ flags _options pir) = HackagePackage (toCabalFlags flags) pir - sourceToPackage (PSFiles lp _) = - let pkg = lpPackage lp - ident = PackageIdentifier (packageName pkg) (packageVersion pkg) - in NonHackagePackage (toCabalFlags $ packageFlags pkg) ident (lpLocation lp) - toCabalFlags fs = [ (toCabalFlagName f0, enabled) - | (f0, enabled) <- M.toList fs ] - + depPkgToPackage ::DepPackage -> PackageRef + depPkgToPackage dp = case dpLocation dp of + PLMutable _ -> + error "depPkgToPackage/PLMutable TBD" + PLImmutable (PLIHackage pkgId _blobKey _treeKey) -> + let common = dpCommon dp + in HackagePackage (cpGhcOptions common) (M.toList $ cpFlags common) pkgId + PLImmutable (PLIArchive{}) -> + error "depPkgToPackage/PLIArchive TBD" + PLImmutable (PLIRepo{}) -> + error "depPkgToPackage/PLIRepo TBD" + projPkgToPackage :: ProjectPackage -> PackageRef + projPkgToPackage pp = + let common = ppCommon pp + in NonHackagePackage (cpGhcOptions common) (M.toList $ cpFlags common) (ppResolvedDir pp) planAndGenerate :: HasEnvConfig env - => BuildOptsCLI - -> FilePath + => Path Abs Dir -> Maybe String -> Args - -> Version -> RIO env () -planAndGenerate boptsCli baseDir remoteUri args@Args {..} ghcVersion = do - (_targets, _mbp, _locals, _extraToBuild, sourceMap) <- loadSourceMapFull - NeedTargets - boptsCli +planAndGenerate baseDir remoteUri args@Args {..} = do + sourceMap <- view sourceMapL + ghcVersion <- case smCompiler sourceMap of + ACGhc v -> + pure v + ACGhcGit _ _ -> + error "stack2nix doesn't support GHC from git" + when argEnsureExecutables $ + liftIO $ ensureExecutable ("haskell.compiler.ghc" ++ nixVersion ghcVersion) - -- Stackage lists bin-package-db but it's in GHC 7.10's boot libraries - binPackageDb <- parsePackageName "bin-package-db" - let pkgs = sourceMapToPackages (M.delete binPackageDb sourceMap) + let pkgs = sourceMapToPackages sourceMap liftIO $ logDebug args $ "plan:\n" ++ show pkgs hackageDB <- liftIO $ loadHackageDB Nothing argHackageSnapshot - buildConf <- envConfigBuildConfig <$> view envConfigL drvs <- liftIO $ mapPool argThreads - (\p -> - fmap (addGhcOptions buildConf p) - <$> genNixFile args ghcVersion baseDir remoteUri argRev hackageDB p - ) + (genNixFile args ghcVersion baseDir remoteUri argRev hackageDB) pkgs - let locals = map (\l -> show (packageName (lpPackage l))) _locals - liftIO . render drvs args locals $ nixVersion ghcVersion + let locals = map show $ M.keys (smProject sourceMap) + let basePackageNames = Set.fromList . map unPackageName $ M.keys (smGlobal sourceMap) + liftIO $ render drvs args locals (nixVersion ghcVersion) basePackageNames --- | Add ghc-options declared in stack.yaml to the nix derivation for a package --- by adding to the configureFlags attribute of the derivation -addGhcOptions :: BuildConfig -> PackageRef -> Derivation -> Derivation -addGhcOptions buildConf pkgRef drv = - drv & configureFlags %~ (Set.union stackGhcOptions) - where - stackGhcOptions :: Set String - stackGhcOptions = - Set.fromList . map (unpack . ("--ghc-option=" <>)) $ getGhcOptions - buildConf - buildOpts - pkgName - False - False - pkgName :: PackageName - pkgName = case pkgRef of - HackagePackage _ (PackageIdentifierRevision (PackageIdentifier n _) _) -> n - NonHackagePackage _ (PackageIdentifier n _) _ -> n +addGhcOptions :: GhcOptions -> Derivation -> Derivation +addGhcOptions ghcOptions drv = + drv & configureFlags <>~ (Set.fromList . map (unpack . ("--ghc-option=" <>)) $ ghcOptions) -runPlan :: FilePath +runPlan :: Path Abs Dir -> Maybe String -> Args -> IO () -runPlan baseDir remoteUri args@Args{..} = do - let stackRoot = "/tmp/s2n" - createDirectoryIfMissing True stackRoot - let globals = globalOpts baseDir stackRoot args - let stackFile = baseDir argStackYaml - - ghcVersion <- getGhcVersionIO globals stackFile - when argEnsureExecutables $ - ensureExecutable ("haskell.compiler.ghc" ++ nixVersion ghcVersion) - withBuildConfig globals $ planAndGenerate buildOpts baseDir remoteUri args ghcVersion +runPlan baseDir remoteUri args = do + let stackRoot = $(mkAbsDir "/tmp/s2n") + ensureDir stackRoot + globals <- globalOpts baseDir stackRoot args + withRunnerGlobal globals $ withConfig NoReexec $ withEnvConfig NeedTargets buildOpts $ + planAndGenerate baseDir remoteUri args nixVersion :: Version -> String nixVersion = - filter (/= '.') . show + filter (/= '.') . prettyShow -getGhcVersionIO :: GlobalOpts -> FilePath -> IO Version -getGhcVersionIO go stackFile = do - cp <- canonicalizePath stackFile - fp <- parseAbsFile cp - lc <- withRunner LevelError True False ColorAuto Nothing False $ \runner -> - -- https://www.fpcomplete.com/blog/2017/07/the-rio-monad - runRIO runner $ loadConfig mempty Nothing (SYLOverride fp) - getGhcVersion <$> loadCompilerVersion go lc - -globalOpts :: FilePath -> FilePath -> Args -> GlobalOpts -globalOpts currentDir stackRoot Args{..} = - go { globalReExecVersion = Just "1.5.1" -- TODO: obtain from stack lib if exposed - , globalConfigMonoid = - (globalConfigMonoid go) - { configMonoidNixOpts = mempty - { nixMonoidEnable = First (Just True) - } - } - , globalStackYaml = SYLOverride (currentDir argStackYaml) - , globalLogLevel = if argVerbose then LevelDebug else LevelInfo - } +globalOpts :: MonadIO m => Path Abs Dir -> Path b Dir -> Args -> m GlobalOpts +globalOpts currentDir stackRoot Args{..} = do + go0 <- globalOptsFromMonoid False . fromJust . getParseResult $ + execParserPure defaultPrefs pinfo args + globalStackYaml <- resolveFile currentDir argStackYaml + pure $ go0 { globalReExecVersion = Just "2.3.3" -- TODO: obtain from stack lib if exposed + , globalConfigMonoid = + (globalConfigMonoid go0) + { configMonoidNixOpts = mempty + { nixMonoidEnable = First (Just True) + } + , configMonoidSystemGHC = First (Just True) + } + , globalStackYaml = SYLOverride globalStackYaml + , globalLogLevel = if argVerbose then LevelDebug else LevelInfo + } where - pinfo = info (globalOptsParser currentDir OuterGlobalOpts (Just LevelError)) briefDesc - args = concat [ ["--stack-root", stackRoot] + pinfo = info (globalOptsParser (toFilePath currentDir) OuterGlobalOpts (Just LevelError)) briefDesc + args = concat [ ["--stack-root", toFilePath stackRoot] , ["--jobs", show argThreads] , ["--test" | argTest] , ["--bench" | argBench] , ["--haddock" | argHaddock] , ["--no-install-ghc"] + , ["--system-ghc"] ] - go = globalOptsFromMonoid False ColorNever . fromJust . getParseResult $ - execParserPure defaultPrefs pinfo args buildOpts :: BuildOptsCLI buildOpts = fromJust . getParseResult $ execParserPure defaultPrefs (info (buildOptsParser Build) briefDesc) ["--dry-run"] diff --git a/src/Stack2nix/External/Util.hs b/src/Stack2nix/External/Util.hs index 92ee816..90c1db1 100644 --- a/src/Stack2nix/External/Util.hs +++ b/src/Stack2nix/External/Util.hs @@ -1,6 +1,5 @@ module Stack2nix.External.Util where -import Data.Monoid ((<>)) import System.Directory (getCurrentDirectory) import System.Exit (ExitCode (..)) import System.Process (CreateProcess (..), proc, diff --git a/src/Stack2nix/Render.hs b/src/Stack2nix/Render.hs index 4047444..5615855 100644 --- a/src/Stack2nix/Render.hs +++ b/src/Stack2nix/Render.hs @@ -10,13 +10,13 @@ import Control.Lens import Control.Monad (when) import qualified Data.ByteString as BS import Data.Either (lefts, rights) -import Data.List (filter, isPrefixOf, +import Data.List (isPrefixOf, sort) -import Data.Monoid ((<>)) import Data.Set (Set) import qualified Data.Set as Set import qualified Data.Text as Text import Data.Text.Encoding (encodeUtf8) +import Data.Version (showVersion) import Distribution.Nixpkgs.Haskell.BuildInfo (haskell, pkgconfig, system, tool) import Distribution.Nixpkgs.Haskell.Derivation (Derivation, @@ -24,57 +24,22 @@ import Distribution.Nixpkgs.Haskell.Derivation (Derivation, dependencies, doCheck, pkgid, runHaddock, testDepends) -import Distribution.Text (display) import Distribution.Types.PackageId (PackageIdentifier (..), pkgName) import Distribution.Types.PackageName (unPackageName) import Language.Nix (path) import Language.Nix.Binding (Binding, reference) -import Language.Nix.PrettyPrinting (disp) import Paths_stack2nix (version) import Stack2nix.Types (Args (..)) import Stack2nix.PP (ppIndented, ppSingletons) import System.IO (hPutStrLn, stderr) import qualified Text.PrettyPrint as PP import Text.PrettyPrint.HughesPJClass (Doc, fcat, nest, - pPrint, punctuate, + pPrint, prettyShow, punctuate, semi, space, text) --- TODO: this only covers GHC 8.0.2 -basePackages :: Set String -basePackages = Set.fromList - [ "array" - , "base" - -- bin-package-db is in GHC 7.10's boot libraries - , "bin-package-db" - , "binary" - , "bytestring" - , "Cabal" - , "containers" - , "deepseq" - , "directory" - , "filepath" - , "ghc-boot" - , "ghc-boot-th" - , "ghc-prim" - , "ghci" - , "haskeline" - , "hoopl" - , "hpc" - , "integer-gmp" - , "pretty" - , "process" - , "rts" - , "template-haskell" - , "terminfo" - , "time" - , "transformers" - , "unix" - , "xhtml" - ] - -render :: [Either Doc Derivation] -> Args -> [String] -> String -> IO () -render results args locals ghcnixversion = do +render :: [Either Doc Derivation] -> Args -> [String] -> String -> Set String -> IO () +render results args locals ghcnixversion basePackages = do let docs = lefts results when (length docs > 0) $ do hPutStrLn stderr $ show docs @@ -106,11 +71,11 @@ renderOne args locals drv' = nest 6 $ PP.hang nonXpkgs = filter (\e -> not ( "libX" - `Data.List.isPrefixOf` (display (((view (reference . path) e) !! 1))) + `Data.List.isPrefixOf` (prettyShow (((view (reference . path) e) !! 1))) ) ) nixPkgs - pkgs = fcat $ punctuate space [ disp b <> semi | b <- nonXpkgs ] + pkgs = fcat $ punctuate space [ pPrint b <> semi | b <- nonXpkgs ] drv = filterDepends args isLocal drv' & doCheck @@ -141,7 +106,7 @@ drvToName drv = unPackageName $ pkgName $ view pkgid drv defaultNix :: (Doc -> String) -> String -> [Doc] -> String defaultNix pp ghcnixversion drvs = unlines $ - [ "# Generated using stack2nix " <> display version <> "." + [ "# Generated using stack2nix " <> showVersion version <> "." , "" , "{ pkgs ? (import {})" , ", compiler ? pkgs.haskell.packages.ghc" ++ ghcnixversion @@ -150,7 +115,7 @@ defaultNix pp ghcnixversion drvs = unlines $ , "with pkgs.haskell.lib;" , "" , "let" - , " stackPackages = { pkgs, stdenv, callPackage }:" + , " stackPackages = { pkgs, lib, callPackage, ... }:" , " self: {" ] ++ (map pp drvs) ++ [ " };" diff --git a/src/Stack2nix/Types.hs b/src/Stack2nix/Types.hs index 3276c45..b2ca829 100644 --- a/src/Stack2nix/Types.hs +++ b/src/Stack2nix/Types.hs @@ -1,5 +1,6 @@ module Stack2nix.Types where +import Data.Text (Text) import Data.Time (UTCTime) import Distribution.PackageDescription (FlagName) import Distribution.System (Platform) @@ -23,3 +24,5 @@ data Args = Args deriving (Show) type Flags = [(FlagName, Bool)] + +type GhcOptions = [Text] diff --git a/stack.yaml b/stack.yaml index d741d1d..61f62bf 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,4 +1,4 @@ -resolver: lts-13.15 +resolver: lts-18.2 packages: - '.' diff --git a/stack2nix.cabal b/stack2nix.cabal index 4dafe29..1120126 100644 --- a/stack2nix.cabal +++ b/stack2nix.cabal @@ -11,6 +11,7 @@ build-type: Simple extra-source-files: README.md ChangeLog.md + pkg_versions.txt cabal-version: >= 1.10 source-repository head @@ -19,23 +20,24 @@ source-repository head library hs-source-dirs: src - build-depends: base >=4.9 && <4.13 - , Cabal >= 2.0.0.2 && < 2.5 + build-depends: base + , Cabal , async >= 2.1.1.1 && < 2.3 , bytestring , cabal2nix >= 2.10 , containers >= 0.5.7.1 && < 0.7 , directory >= 1.3 && < 1.4 - , distribution-nixpkgs >= 1.1 && < 1.3 + , distribution-nixpkgs , filepath >= 1.4.1.1 && < 1.5 , hackage-db - , optparse-applicative >= 0.13.2 && < 0.15 + , optparse-applicative , pretty , path + , path-io , language-nix , lens , process >= 1.4.3 && < 1.7 - , regex-pcre >= 0.94.4 && < 0.95 + , regex-pcre , SafeSemaphore >= 0.10.1 && < 0.11 , stack >= 1.9 , temporary >= 1.2.0.4 && < 1.4 @@ -59,8 +61,9 @@ executable stack2nix main-is: Main.hs build-depends: base , Cabal - , stack2nix , optparse-applicative + , split + , stack2nix , time hs-source-dirs: stack2nix ghc-options: -Wall -threaded -rtsopts -with-rtsopts=-N diff --git a/stack2nix.nix b/stack2nix.nix index 76c0df7..7ad2a57 100644 --- a/stack2nix.nix +++ b/stack2nix.nix @@ -1,46 +1,66 @@ # Generated using stack2nix 0.2.3. { pkgs ? (import {}) -, compiler ? pkgs.haskell.packages.ghc863 +, compiler ? pkgs.haskell.packages.ghc8104 }: with pkgs.haskell.lib; let - stackPackages = { pkgs, stdenv, callPackage }: + stackPackages = { pkgs, lib, callPackage, ... }: self: { + Cabal = null; array = null; base = null; - bin-package-db = null; binary = null; bytestring = null; containers = null; deepseq = null; directory = null; filepath = null; + ghc = null; ghc-boot = null; ghc-boot-th = null; + ghc-compact = null; + ghc-heap = null; ghc-prim = null; ghci = null; - hoopl = null; hpc = null; integer-gmp = null; + libiserv = null; + mtl = null; + parsec = null; pretty = null; process = null; rts = null; + stm = null; template-haskell = null; terminfo = null; + text = null; time = null; transformers = null; unix = null; + xhtml = null; + "AC-Angle" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "AC-Angle"; + version = "1.0"; + sha256 = "b545b0086832adc7d9ae15b4c3f3d1522d63a746f204570766828f1a893a4965"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + description = "Angles in degrees and radians"; + license = lib.licenses.bsd3; + }) {}; "ALUT" = callPackage - ({ mkDerivation, base, freealut, OpenAL, StateVar, stdenv + ({ mkDerivation, base, freealut, lib, OpenAL, StateVar , transformers }: mkDerivation { pname = "ALUT"; - version = "2.4.0.2"; - sha256 = "b8364da380f5f1d85d13e427851a153be2809e1838d16393e37566f34b384b87"; + version = "2.4.0.3"; + sha256 = "71891b0a1d96a6a07d1404e542dc9c86b30f757543c294de9644af98f781d912"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base OpenAL StateVar transformers ]; @@ -49,10 +69,10 @@ let doCheck = false; homepage = "https://github.com/haskell-openal/ALUT"; description = "A binding for the OpenAL Utility Toolkit"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) freealut;}; "ANum" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "ANum"; version = "0.2.0.2"; @@ -62,10 +82,116 @@ let doCheck = false; homepage = "https://github.com/DanBurton/ANum#readme"; description = "Num instance for Applicatives provided via the ANum newtype"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "Agda" = callPackage + ({ mkDerivation, aeson, alex, array, async, base, binary + , blaze-html, boxes, bytestring, Cabal, case-insensitive + , containers, data-hash, deepseq, directory, edit-distance, emacs + , equivalence, exceptions, filepath, ghc-compact, gitrev, happy + , hashable, hashtables, haskeline, lib, monad-control, mtl + , murmur-hash, parallel, pretty, process, regex-tdfa, split, stm + , strict, template-haskell, text, time, transformers + , unordered-containers, uri-encode, zlib + }: + mkDerivation { + pname = "Agda"; + version = "2.6.2"; + sha256 = "072caaad7a405b764423958d2001b68fbfd3fc8f98870cd0a5f0bcaeadfd3095"; + isLibrary = true; + isExecutable = true; + enableSeparateDataOutput = true; + setupHaskellDepends = [ base Cabal directory filepath process ]; + libraryHaskellDepends = [ + aeson array async base binary blaze-html boxes bytestring + case-insensitive containers data-hash deepseq directory + edit-distance equivalence exceptions filepath ghc-compact gitrev + hashable hashtables haskeline monad-control mtl murmur-hash + parallel pretty process regex-tdfa split stm strict + template-haskell text time transformers unordered-containers + uri-encode zlib + ]; + libraryToolDepends = [ alex happy ]; + executableHaskellDepends = [ base directory filepath process ]; + executableToolDepends = [ emacs ]; + doHaddock = false; + doCheck = false; + homepage = "http://wiki.portal.chalmers.se/agda/"; + description = "A dependently typed functional programming language and proof assistant"; + license = "unknown"; + hydraPlatforms = lib.platforms.none; + }) {}; + "Allure" = callPackage + ({ mkDerivation, async, base, enummapset, file-embed, filepath + , ghc-compact, hsini, LambdaHack, lib, optparse-applicative + , primitive, splitmix, template-haskell, text, th-lift-instances + , transformers + }: + mkDerivation { + pname = "Allure"; + version = "0.10.2.0"; + sha256 = "fcb9f38ea543d3277fa90eee004f7624d1168bf7f2c17902cda1870293b7c2f4"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + async base enummapset file-embed filepath ghc-compact hsini + LambdaHack optparse-applicative primitive splitmix template-haskell + text th-lift-instances transformers + ]; + executableHaskellDepends = [ + async base filepath LambdaHack optparse-applicative + ]; + doHaddock = false; + doCheck = false; + homepage = "http://allureofthestars.com"; + description = "Near-future Sci-Fi roguelike and tactical squad combat game"; + license = lib.licenses.agpl3Plus; + }) {}; + "BNFC" = callPackage + ({ mkDerivation, alex, array, base, Cabal, cabal-doctest + , containers, deepseq, directory, filepath, happy, lib, mtl, pretty + , process, string-qq, time + }: + mkDerivation { + pname = "BNFC"; + version = "2.9.2"; + sha256 = "b13e4e6d6fab0ff37e76829a4a9587d78aa702fa16ad7171eddc199e8d32c4f2"; + isLibrary = true; + isExecutable = true; + setupHaskellDepends = [ base Cabal cabal-doctest ]; + libraryHaskellDepends = [ + array base containers deepseq directory filepath mtl pretty process + string-qq time + ]; + libraryToolDepends = [ alex happy ]; + executableHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "http://bnfc.digitalgrammars.com/"; + description = "A compiler front-end generator"; + license = lib.licenses.bsd3; + }) {}; + "BNFC-meta" = callPackage + ({ mkDerivation, alex-meta, array, base, fail, happy-meta + , haskell-src-meta, lib, syb, template-haskell + }: + mkDerivation { + pname = "BNFC-meta"; + version = "0.6.1"; + sha256 = "2a1ed6a91dac45a185ce4edb70e41a99535f757305b5852351bf4b46dd64ca6a"; + revision = "2"; + editedCabalFile = "1xg96a83jhz5jiw16yrgm3x5k7fz7zmz6cvggnfmjvw7v7bl69ph"; + libraryHaskellDepends = [ + alex-meta array base fail happy-meta haskell-src-meta syb + template-haskell + ]; + doHaddock = false; + doCheck = false; + description = "Deriving Parsers and Quasi-Quoters from BNF Grammars"; + license = lib.licenses.gpl2Only; }) {}; "Boolean" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "Boolean"; version = "0.2.4"; @@ -74,10 +200,10 @@ let doHaddock = false; doCheck = false; description = "Generalized booleans and numbers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "BoundedChan" = callPackage - ({ mkDerivation, array, base, stdenv }: + ({ mkDerivation, array, base, lib }: mkDerivation { pname = "BoundedChan"; version = "1.0.3.0"; @@ -86,46 +212,59 @@ let doHaddock = false; doCheck = false; description = "Implementation of bounded channels"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "Cabal" = callPackage - ({ mkDerivation, array, base, binary, bytestring, containers - , deepseq, directory, filepath, mtl, parsec, pretty, process - , stdenv, text, time, transformers, unix + "ChannelT" = callPackage + ({ mkDerivation, base, free, lib, mmorph, mtl, transformers-base }: + mkDerivation { + pname = "ChannelT"; + version = "0.0.0.7"; + sha256 = "3e215d425e3cfccf2e4d84b1402fb39a2081cb33b6556059db616e722a7c77a0"; + libraryHaskellDepends = [ base free mmorph mtl transformers-base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/pthariensflame/ChannelT"; + description = "Generalized stream processors"; + license = lib.licenses.bsd3; + }) {}; + "Chart" = callPackage + ({ mkDerivation, array, base, colour, data-default-class, lens, lib + , mtl, old-locale, operational, time, vector }: mkDerivation { - pname = "Cabal"; - version = "2.4.1.0"; - sha256 = "736a902da9fb2c826e75e9f7b4b591983bf58a6a62c8cae9866f6a9d5ace3594"; - revision = "1"; - editedCabalFile = "1dvs2i0kfk8rji9wbrv7y0iydbif9jzg4c7rmaa6lxg8hp7mij2n"; - setupHaskellDepends = [ mtl parsec ]; + pname = "Chart"; + version = "1.9.3"; + sha256 = "3e17f4ca0112399df627862bb50581f81ec3ebf54b618e3c690f10380b9ec95c"; + revision = "2"; + editedCabalFile = "04mmsm54mdqcrypvgawhhbwjscmky3j7g5841bc71c0q6d33h2k4"; libraryHaskellDepends = [ - array base binary bytestring containers deepseq directory filepath - mtl parsec pretty process text time transformers unix + array base colour data-default-class lens mtl old-locale + operational time vector ]; doHaddock = false; doCheck = false; - homepage = "http://www.haskell.org/cabal/"; - description = "A framework for packaging Haskell software"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/timbod7/haskell-chart/wiki"; + description = "A library for generating 2D Charts and Plots"; + license = lib.licenses.bsd3; }) {}; - "ChannelT" = callPackage - ({ mkDerivation, base, free, mmorph, mtl, stdenv, transformers-base + "ChasingBottoms" = callPackage + ({ mkDerivation, base, containers, lib, mtl, QuickCheck, random + , syb }: mkDerivation { - pname = "ChannelT"; - version = "0.0.0.7"; - sha256 = "3e215d425e3cfccf2e4d84b1402fb39a2081cb33b6556059db616e722a7c77a0"; - libraryHaskellDepends = [ base free mmorph mtl transformers-base ]; + pname = "ChasingBottoms"; + version = "1.3.1.10"; + sha256 = "c32d9bb86f66db6175c3dda8a5407fbc6cd96604f1a9b0696bc05bd4a02999ba"; + libraryHaskellDepends = [ + base containers mtl QuickCheck random syb + ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/pthariensflame/ChannelT"; - description = "Generalized stream processors"; - license = stdenv.lib.licenses.bsd3; + description = "For testing partial and infinite values"; + license = lib.licenses.mit; }) {}; "Clipboard" = callPackage - ({ mkDerivation, base, directory, stdenv, unix, utf8-string, X11 }: + ({ mkDerivation, base, directory, lib, unix, utf8-string, X11 }: mkDerivation { pname = "Clipboard"; version = "2.3.2.0"; @@ -135,19 +274,51 @@ let doCheck = false; homepage = "http://haskell.org/haskellwiki/Clipboard"; description = "System clipboard interface"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "ClustalParser" = callPackage + ({ mkDerivation, base, cmdargs, either-unwrap, lib, parsec, text + , vector + }: + mkDerivation { + pname = "ClustalParser"; + version = "1.3.0"; + sha256 = "e64ebe0a43ef2c010079b31b8f359c159d098496ee9f3ea0bbba25bd2fb1a07e"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base parsec text vector ]; + executableHaskellDepends = [ + base cmdargs either-unwrap parsec text vector + ]; + doHaddock = false; + doCheck = false; + description = "Libary for parsing Clustal tools output"; + license = lib.licenses.gpl3Only; + }) {}; + "Color" = callPackage + ({ mkDerivation, base, data-default-class, deepseq, lib, vector }: + mkDerivation { + pname = "Color"; + version = "0.3.2"; + sha256 = "13eaa70efe3be2b86988232f5653562620af1dc5322f903c761a1cada418bdec"; + libraryHaskellDepends = [ base data-default-class deepseq vector ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/lehins/Color"; + description = "Color spaces and conversions between them"; + license = lib.licenses.bsd3; }) {}; "DAV" = callPackage ({ mkDerivation, base, bytestring, case-insensitive, containers , data-default, exceptions, haskeline, http-client, http-client-tls - , http-types, lens, mtl, network, network-uri, optparse-applicative - , stdenv, transformers, transformers-base, transformers-compat - , utf8-string, xml-conduit, xml-hamlet + , http-types, lens, lib, mtl, network, network-uri + , optparse-applicative, transformers, transformers-base + , transformers-compat, utf8-string, xml-conduit, xml-hamlet }: mkDerivation { pname = "DAV"; - version = "1.3.3"; - sha256 = "24f49c63bd603b7757569ac0f5842ac30dea2bfcce64d157162a952e576e3991"; + version = "1.3.4"; + sha256 = "5e3b825290a0bd4c9da1c814b5e67901b0f9f1d16a88effaa7e060a81c895bc7"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -166,77 +337,88 @@ let doCheck = false; homepage = "http://floss.scru.org/hDAV"; description = "RFC 4918 WebDAV support"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; }) {}; "DBFunctor" = callPackage ({ mkDerivation, base, bytestring, cassava, cereal, containers - , deepseq, either, MissingH, stdenv, text, transformers + , deepseq, either, lib, text, time, transformers , unordered-containers, vector }: mkDerivation { pname = "DBFunctor"; - version = "0.1.0.0"; - sha256 = "87a978ed52c47d3a42f8b89705f47cfd64c2f2f8c7c6306bbde84b341714ad29"; - revision = "1"; - editedCabalFile = "1gfadkmnf1c151kkcq41ca2vx36drp2kfhq74ybhvdz32kbrvwq3"; + version = "0.1.2.1"; + sha256 = "9f35ed8732c246960fd15d24ce3673f544b6036e2984f0db2537d7f092266b46"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - base bytestring cassava cereal containers deepseq either MissingH - text transformers unordered-containers vector + base bytestring cassava cereal containers deepseq either text time + transformers unordered-containers vector ]; executableHaskellDepends = [ - base bytestring cassava cereal containers deepseq either MissingH - text transformers unordered-containers vector + base bytestring cassava cereal containers deepseq either text time + transformers unordered-containers vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nkarag/haskell-DBFunctor#readme"; description = "DBFunctor - Functional Data Management => ETL/ELT Data Processing in Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "Decimal" = callPackage - ({ mkDerivation, base, deepseq, stdenv }: + ({ mkDerivation, base, deepseq, lib }: mkDerivation { pname = "Decimal"; - version = "0.5.1"; - sha256 = "575ca5c65a8ea5a5bf2cd7b794a0d16622082cb501bf4b0327c5895c0b80f34c"; + version = "0.5.2"; + sha256 = "a37a0220424e4bcb8cae1d38844c7027ee314449758d0d14ff3e2e0a5c8a87a7"; libraryHaskellDepends = [ base deepseq ]; doHaddock = false; doCheck = false; homepage = "https://github.com/PaulJohnson/Haskell-Decimal"; description = "Decimal numbers with variable precision"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "Diff" = callPackage - ({ mkDerivation, array, base, pretty, stdenv }: + ({ mkDerivation, array, base, lib, pretty }: mkDerivation { pname = "Diff"; - version = "0.3.4"; - sha256 = "77b7daec5a79ade779706748f11b4d9b8f805e57a68e7406c3b5a1dee16e0c2f"; + version = "0.4.0"; + sha256 = "7290ac098ad8b4748b9c10e494cc85ba54af688226ae69a465aa7b4c73f149c7"; libraryHaskellDepends = [ array base pretty ]; doHaddock = false; doCheck = false; description = "O(ND) diff algorithm in haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "ENIG" = callPackage + ({ mkDerivation, base, lib, text, unicode-transforms, vector }: + mkDerivation { + pname = "ENIG"; + version = "0.0.1.0"; + sha256 = "03b29362c5bf0b33ded4e776d0252e71f3227da7c93cefa3d67348ab976f66ff"; + libraryHaskellDepends = [ base text unicode-transforms vector ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/QuietJoon/ENIG#readme"; + description = "Auto Korean conjugator/adjustor/adopter/converter"; + license = lib.licenses.bsd3; }) {}; "Earley" = callPackage - ({ mkDerivation, base, ListLike, stdenv }: + ({ mkDerivation, base, lib, ListLike }: mkDerivation { pname = "Earley"; - version = "0.13.0.0"; - sha256 = "0f50ec9bd2f612ed0d1da74741081930031000cdce82775b257f77d30a4bd25f"; + version = "0.13.0.1"; + sha256 = "1e60bcfda0d7441ce2886d7f3523e017e74c225506dd9d0e7a3c012959943899"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base ListLike ]; doHaddock = false; doCheck = false; description = "Parsing all context-free grammars using Earley's algorithm"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "Ebnf2ps" = callPackage - ({ mkDerivation, array, base, containers, directory, happy - , old-time, stdenv, unix + ({ mkDerivation, array, base, containers, directory, happy, lib + , old-time, unix }: mkDerivation { pname = "Ebnf2ps"; @@ -252,10 +434,10 @@ let doCheck = false; homepage = "https://github.com/FranklinChen/Ebnf2ps"; description = "Peter's Syntax Diagram Drawing Tool"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "FenwickTree" = callPackage - ({ mkDerivation, base, QuickCheck, stdenv, template-haskell }: + ({ mkDerivation, base, lib, QuickCheck, template-haskell }: mkDerivation { pname = "FenwickTree"; version = "0.1.2.1"; @@ -266,10 +448,10 @@ let doCheck = false; homepage = "https://github.com/mgajda/FenwickTree"; description = "Data structure for fast query and update of cumulative sums"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "FindBin" = callPackage - ({ mkDerivation, base, directory, filepath, stdenv }: + ({ mkDerivation, base, directory, filepath, lib }: mkDerivation { pname = "FindBin"; version = "0.0.5"; @@ -279,28 +461,28 @@ let doCheck = false; homepage = "https://github.com/audreyt/findbin"; description = "Locate directory of original program"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "FloatingHex" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { pname = "FloatingHex"; - version = "0.4"; - sha256 = "b277054db48d2dec62e3831586f218cbe0a056dec44dbc032e9a73087425a24c"; + version = "0.5"; + sha256 = "a3a37a0f373a09a1261954b737959a7129b79e3e8f775b981bbe4abb85016830"; libraryHaskellDepends = [ base template-haskell ]; doHaddock = false; doCheck = false; description = "Read and write hexadecimal floating point numbers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "FontyFruity" = callPackage ({ mkDerivation, base, binary, bytestring, containers, deepseq - , directory, filepath, stdenv, text, vector, xml + , directory, filepath, lib, text, vector, xml }: mkDerivation { pname = "FontyFruity"; - version = "0.5.3.4"; - sha256 = "43d3878154d543a337b0cc45f40dcd57153e47fca39122bac0e5ed81b6bc5b3d"; + version = "0.5.3.5"; + sha256 = "2deb5ba03a5326c7dd364900b86e427344266c4866b863e8325bf6eade760a9a"; libraryHaskellDepends = [ base binary bytestring containers deepseq directory filepath text vector xml @@ -308,25 +490,40 @@ let doHaddock = false; doCheck = false; description = "A true type file format loader"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "ForestStructures" = callPackage + ({ mkDerivation, base, bifunctors, containers, fgl, lens, lib + , QuickCheck, unordered-containers, vector, vector-th-unbox + }: + mkDerivation { + pname = "ForestStructures"; + version = "0.0.1.0"; + sha256 = "7c5b4a7b78178396152c0dc24d966b55557f5bdaaf0cfa24ee71c9cb006315c2"; + libraryHaskellDepends = [ + base bifunctors containers fgl lens QuickCheck unordered-containers + vector vector-th-unbox + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/choener/ForestStructures"; + description = "Tree- and forest structures"; + license = lib.licenses.bsd3; }) {}; "GLFW-b" = callPackage - ({ mkDerivation, base, bindings-GLFW, deepseq, stdenv }: + ({ mkDerivation, array, base, bindings-GLFW, deepseq, lib }: mkDerivation { pname = "GLFW-b"; - version = "3.2.1.0"; - sha256 = "31c022e0ad63f259ff9fa582a235924786e929a95b52efae10a3d29fef7cb6a6"; - revision = "2"; - editedCabalFile = "0xlby7483dv33c13f44kkvmai186g72jhxmcq8749s1hyxi6fqnb"; - libraryHaskellDepends = [ base bindings-GLFW deepseq ]; + version = "3.3.0.0"; + sha256 = "64772fd294a168567742753588f33627836bd0de876761f2da721d46aab506f6"; + libraryHaskellDepends = [ array base bindings-GLFW deepseq ]; doHaddock = false; doCheck = false; description = "Bindings to GLFW OpenGL library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "GLURaw" = callPackage - ({ mkDerivation, base, libGL, libGLU, OpenGLRaw, stdenv - , transformers + ({ mkDerivation, base, lib, libGL, libGLU, OpenGLRaw, transformers }: mkDerivation { pname = "GLURaw"; @@ -338,16 +535,16 @@ let doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Opengl"; description = "A raw binding for the OpenGL graphics system"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) libGL; inherit (pkgs) libGLU;}; "GLUT" = callPackage - ({ mkDerivation, array, base, containers, OpenGL, StateVar, stdenv + ({ mkDerivation, array, base, containers, lib, OpenGL, StateVar , transformers }: mkDerivation { pname = "GLUT"; - version = "2.7.0.14"; - sha256 = "5cf8f7700a6b6ac33e39b2d7bd300679a245ff7c1498eb423901134f9d302106"; + version = "2.7.0.16"; + sha256 = "b6fae948d0778ee49e1199b20a007d1c4e9e7c008096fcfe6d2f7ec98974b36d"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -357,10 +554,10 @@ let doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Opengl"; description = "A binding for the OpenGL Utility Toolkit"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "GenericPretty" = callPackage - ({ mkDerivation, base, ghc-prim, pretty, stdenv }: + ({ mkDerivation, base, ghc-prim, lib, pretty }: mkDerivation { pname = "GenericPretty"; version = "1.2.2"; @@ -370,16 +567,16 @@ let doCheck = false; homepage = "https://github.com/RazvanRanca/GenericPretty"; description = "A generic, derivable, haskell pretty printer"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "Glob" = callPackage - ({ mkDerivation, base, containers, directory, dlist, filepath - , stdenv, transformers, transformers-compat + ({ mkDerivation, base, containers, directory, dlist, filepath, lib + , transformers, transformers-compat }: mkDerivation { pname = "Glob"; - version = "0.9.3"; - sha256 = "3a77853eba3700c5346cd6d4008302e70dca93a7e8ac0d679cf41b16c7a4c9e8"; + version = "0.10.1"; + sha256 = "cae4476d944947010705e0b00cf3e36c90ef407f968861f6771b931056b6d315"; libraryHaskellDepends = [ base containers directory dlist filepath transformers transformers-compat @@ -388,33 +585,55 @@ let doCheck = false; homepage = "http://iki.fi/matti.niemenmaa/glob/"; description = "Globbing library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "H" = callPackage + ({ mkDerivation, base, bytestring, cmdargs, file-embed, inline-r + , lib, pretty, process, temporary, vector + }: + mkDerivation { + pname = "H"; + version = "0.9.0.1"; + sha256 = "5fc04dfefcac9f6882cea9e65755479f7b1d853618c89258a005df63c8d57134"; + revision = "1"; + editedCabalFile = "07pddiap3jzcnc09v442wq30j46nmkdibilzcv69hz5imcnmhz0h"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ + base bytestring cmdargs file-embed inline-r pretty process + temporary vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://tweag.github.io/HaskellR"; + description = "The Haskell/R mixed programming environment"; + license = lib.licenses.bsd3; }) {}; "HCodecs" = callPackage - ({ mkDerivation, array, base, bytestring, QuickCheck, random - , semigroups, stdenv + ({ mkDerivation, array, base, bytestring, fail, lib, QuickCheck + , random, semigroups }: mkDerivation { pname = "HCodecs"; - version = "0.5.1"; - sha256 = "a724616b79ac12c2d661dc3f54cfa0e7d530d1ba3eafa1e6c3e7116e035a3143"; + version = "0.5.2"; + sha256 = "51160ff3e137f11f5669e4a83cd2cf892e991826353da799e57107715ebc7a3d"; libraryHaskellDepends = [ - array base bytestring QuickCheck random semigroups + array base bytestring fail QuickCheck random semigroups ]; doHaddock = false; doCheck = false; homepage = "http://www-db.informatik.uni-tuebingen.de/team/giorgidze"; description = "A library to read, write and manipulate MIDI, WAVE, and SoundFont2 files"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "HDBC" = callPackage - ({ mkDerivation, base, bytestring, containers, convertible, mtl - , old-time, stdenv, text, time, utf8-string + ({ mkDerivation, base, bytestring, containers, convertible, lib + , mtl, old-time, text, time, utf8-string }: mkDerivation { pname = "HDBC"; - version = "2.4.0.2"; - sha256 = "670757fd674b6caf2f456034bdcb54812af2cdf2a32465d7f4b7f0baa377db5a"; + version = "2.4.0.3"; + sha256 = "1e63bc1f3d1818e39a231eb5467546e0705554de38aeca43fd4ad4cb53a2626f"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -425,28 +644,10 @@ let doCheck = false; homepage = "https://github.com/hdbc/hdbc"; description = "Haskell Database Connectivity"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "HDBC-mysql" = callPackage - ({ mkDerivation, base, bytestring, Cabal, HDBC, mysqlclient - , openssl, stdenv, time, utf8-string, zlib - }: - mkDerivation { - pname = "HDBC-mysql"; - version = "0.7.1.0"; - sha256 = "81c985d4a243c965930fb412b3175ca799ba66985f8b6844014fd600df1da7cf"; - setupHaskellDepends = [ base Cabal ]; - libraryHaskellDepends = [ base bytestring HDBC time utf8-string ]; - librarySystemDepends = [ mysqlclient openssl zlib ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/ryantm/hdbc-mysql"; - description = "MySQL driver for HDBC"; - license = "LGPL"; - }) {inherit (pkgs) mysqlclient; inherit (pkgs) openssl; -inherit (pkgs) zlib;}; "HDBC-session" = callPackage - ({ mkDerivation, base, HDBC, stdenv }: + ({ mkDerivation, base, HDBC, lib }: mkDerivation { pname = "HDBC-session"; version = "0.1.2.0"; @@ -456,22 +657,10 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "http://khibino.github.io/haskell-relational-record/"; description = "Bracketed connection for HDBC"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "HSet" = callPackage - ({ mkDerivation, base, containers, hashable, hashtables, stdenv }: - mkDerivation { - pname = "HSet"; - version = "0.0.1"; - sha256 = "eba93be5a76581585ae33af6babe9c2718fae307d41989cd36a605d9b0e8d16a"; - libraryHaskellDepends = [ base containers hashable hashtables ]; - doHaddock = false; - doCheck = false; - description = "Faux heterogeneous sets"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "HSlippyMap" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "HSlippyMap"; version = "3.0.1"; @@ -481,17 +670,19 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/apeyroux/HSlippyMap"; description = "OpenStreetMap Slippy Map"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "HStringTemplate" = callPackage ({ mkDerivation, array, base, blaze-builder, bytestring, containers - , deepseq, directory, filepath, mtl, old-locale, parsec, pretty - , semigroups, stdenv, syb, template-haskell, text, time, void + , deepseq, directory, filepath, lib, mtl, old-locale, parsec + , pretty, semigroups, syb, template-haskell, text, time, void }: mkDerivation { pname = "HStringTemplate"; version = "0.8.7"; sha256 = "4f4ea4aa2e45e7c45821b87b0105c201fbadebc2f2d00c211e728403a0af6b0e"; + revision = "1"; + editedCabalFile = "0s7y606q2q0vnbg9c51kypawyvapva60i2lw1dg1bij50aiv5d3i"; libraryHaskellDepends = [ array base blaze-builder bytestring containers deepseq directory filepath mtl old-locale parsec pretty semigroups syb @@ -500,58 +691,59 @@ inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "StringTemplate implementation in Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "HSvm" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "HSvm"; - version = "0.1.0.3.22"; - sha256 = "8dac8a583c762675f2d64138303618f017d6be95d59e60774ea7cbfc040dab04"; + version = "0.1.1.3.22"; + sha256 = "8f348ff87d7312a5a41d99a1df558df72592aa34f4520c4b03fad4376e0f326e"; libraryHaskellDepends = [ base containers ]; doHaddock = false; doCheck = false; description = "Haskell Bindings for libsvm"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "HTF" = callPackage ({ mkDerivation, aeson, array, base, base64-bytestring, bytestring - , containers, cpphs, Diff, directory, haskell-src, HUnit - , lifted-base, monad-control, mtl, old-time, pretty, process - , QuickCheck, random, regex-compat, stdenv, text, time, unix - , vector, xmlgen + , Cabal, containers, cpphs, Diff, directory, haskell-src, HUnit + , lib, lifted-base, monad-control, mtl, old-time, pretty, process + , QuickCheck, random, regex-compat, text, time, unix, vector + , xmlgen }: mkDerivation { pname = "HTF"; - version = "0.13.2.5"; - sha256 = "365af323c6254ec5c33745e1d42ceeba0940992a43f523608c4dc64d7c49aece"; + version = "0.14.0.6"; + sha256 = "58cfad065c069c4a484f6d342b5bb60c4c13103c72ba6d4aa43e2d6b87daa452"; isLibrary = true; isExecutable = true; + setupHaskellDepends = [ base Cabal process ]; libraryHaskellDepends = [ aeson array base base64-bytestring bytestring containers cpphs Diff directory haskell-src HUnit lifted-base monad-control mtl old-time pretty process QuickCheck random regex-compat text time unix vector xmlgen ]; + libraryToolDepends = [ cpphs ]; executableHaskellDepends = [ array base cpphs directory HUnit mtl old-time random text ]; + executableToolDepends = [ cpphs ]; doHaddock = false; doCheck = false; homepage = "https://github.com/skogsbaer/HTF/"; description = "The Haskell Test Framework"; - license = stdenv.lib.licenses.lgpl21; + license = lib.licenses.lgpl21Only; }) {}; "HTTP" = callPackage - ({ mkDerivation, array, base, bytestring, mtl, network, network-uri - , parsec, stdenv, time + ({ mkDerivation, array, base, bytestring, lib, mtl, network + , network-uri, parsec, time }: mkDerivation { pname = "HTTP"; - version = "4000.3.12"; - sha256 = "a3ff6a9c93771079121083f1691188fe45f84380118e0f76bc4578153c361990"; - revision = "2"; - editedCabalFile = "1gw6xzp1n4gsqwnbfr29ds8v4wpk78b2bha8i108dqav97viwm8c"; + version = "4000.3.16"; + sha256 = "d6091c037871ac3d08d021c906206174567499d5a26a6cb804cf530cd590fe2d"; libraryHaskellDepends = [ array base bytestring mtl network network-uri parsec time ]; @@ -559,23 +751,23 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/haskell/HTTP"; description = "A library for client-side HTTP"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "HUnit" = callPackage - ({ mkDerivation, base, call-stack, deepseq, stdenv }: + ({ mkDerivation, base, call-stack, deepseq, lib }: mkDerivation { pname = "HUnit"; - version = "1.6.0.0"; - sha256 = "7448e6b966e98e84b7627deba23f71b508e9a61e7bc571d74304a25d30e6d0de"; + version = "1.6.2.0"; + sha256 = "b0b7538871ffc058486fc00740886d2f3172f8fa6869936bfe83a5e10bd744ab"; libraryHaskellDepends = [ base call-stack deepseq ]; doHaddock = false; doCheck = false; homepage = "https://github.com/hspec/HUnit#readme"; description = "A unit testing framework for Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "HUnit-approx" = callPackage - ({ mkDerivation, base, call-stack, HUnit, stdenv }: + ({ mkDerivation, base, call-stack, HUnit, lib }: mkDerivation { pname = "HUnit-approx"; version = "1.1.1.1"; @@ -585,11 +777,52 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/goldfirere/HUnit-approx"; description = "Approximate equality for floating point numbers with HUnit"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "HaTeX" = callPackage + ({ mkDerivation, base, bibtex, bytestring, containers, hashable + , lib, matrix, parsec, prettyprinter, QuickCheck, text + , transformers + }: + mkDerivation { + pname = "HaTeX"; + version = "3.22.3.0"; + sha256 = "74924a8288bdd9d9833aecd9cf9ea063675193d716f197299f372775287e3b6d"; + libraryHaskellDepends = [ + base bibtex bytestring containers hashable matrix parsec + prettyprinter QuickCheck text transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/Daniel-Diaz/HaTeX/blob/master/README.md"; + description = "The Haskell LaTeX library"; + license = lib.licenses.bsd3; + }) {}; + "HaXml" = callPackage + ({ mkDerivation, base, bytestring, containers, directory, filepath + , lib, polyparse, pretty, random + }: + mkDerivation { + pname = "HaXml"; + version = "1.25.5"; + sha256 = "cbc51ac4b6128e130f0272a7b42ab464bc865b3c238d6cce6b76e451765c1235"; + revision = "4"; + editedCabalFile = "029jnlmab1llr55dmlamrn2hxkbqw7ryz1dfg19h1aip6byf4ljh"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base bytestring containers filepath polyparse pretty random + ]; + executableHaskellDepends = [ base directory polyparse pretty ]; + doHaddock = false; + doCheck = false; + homepage = "http://projects.haskell.org/HaXml/"; + description = "Utilities for manipulating XML documents"; + license = "LGPL"; }) {}; "HandsomeSoup" = callPackage - ({ mkDerivation, base, containers, HTTP, hxt, hxt-http, mtl - , network, network-uri, parsec, stdenv, transformers + ({ mkDerivation, base, containers, HTTP, hxt, hxt-http, lib, mtl + , network, network-uri, parsec, transformers }: mkDerivation { pname = "HandsomeSoup"; @@ -606,59 +839,47 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/egonSchiele/HandsomeSoup"; description = "Work with HTML more easily in HXT"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "HaskellNet" = callPackage - ({ mkDerivation, array, base, base64-string, bytestring, cryptohash - , mime-mail, mtl, network, old-time, pretty, stdenv, text - }: + "HasBigDecimal" = callPackage + ({ mkDerivation, base, lib }: mkDerivation { - pname = "HaskellNet"; - version = "0.5.1"; - sha256 = "3245d31ad76f9f9013a2f6e2285d73ed37376eeb073c100b9a6d19e87f0ca838"; - libraryHaskellDepends = [ - array base base64-string bytestring cryptohash mime-mail mtl - network old-time pretty text - ]; + pname = "HasBigDecimal"; + version = "0.1.1"; + sha256 = "0a14a02696d1ecbbfa99b87ee94ffc217e73a005509f6a43d0a9e71adab3be35"; + libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/jtdaugherty/HaskellNet"; - description = "Client support for POP3, SMTP, and IMAP"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/thma/HasBigDecimal#readme"; + description = "A library for arbitrary precision decimal numbers"; + license = lib.licenses.asl20; }) {}; - "Hoed" = callPackage - ({ mkDerivation, array, base, bytestring, cereal, cereal-text - , cereal-vector, clock, containers, deepseq, directory, hashable - , libgraph, open-browser, primitive, process, QuickCheck - , regex-tdfa, regex-tdfa-text, semigroups, stdenv, strict - , template-haskell, terminal-size, text, transformers, uniplate - , unordered-containers, vector, vector-th-unbox + "HaskellNet" = callPackage + ({ mkDerivation, array, base, base64, bytestring, cryptohash-md5 + , lib, mime-mail, mtl, network, network-bsd, old-time, pretty, text }: mkDerivation { - pname = "Hoed"; - version = "0.5.1"; - sha256 = "a8f6dc9717e15642f00cd84a8d1030ac6a7c7870f7015e380bd728a843c3f4e7"; + pname = "HaskellNet"; + version = "0.6"; + sha256 = "a249b46b154a2d67aa3db71f4102f586295ac1d2fd6d0697c489538775c1564b"; libraryHaskellDepends = [ - array base bytestring cereal cereal-text cereal-vector clock - containers deepseq directory hashable libgraph open-browser - primitive process QuickCheck regex-tdfa regex-tdfa-text semigroups - strict template-haskell terminal-size text transformers uniplate - unordered-containers vector vector-th-unbox + array base base64 bytestring cryptohash-md5 mime-mail mtl network + network-bsd old-time pretty text ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/MaartenFaddegon/Hoed"; - description = "Lightweight algorithmic debugging"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/qnikst/HaskellNet"; + description = "Client support for POP3, SMTP, and IMAP"; + license = lib.licenses.bsd3; }) {}; "HsOpenSSL" = callPackage - ({ mkDerivation, base, bytestring, Cabal, network, openssl, stdenv + ({ mkDerivation, base, bytestring, Cabal, lib, network, openssl , time }: mkDerivation { pname = "HsOpenSSL"; - version = "0.11.4.15"; - sha256 = "cebdceef21d8f00feaa3dcc31b18fc960bbfeaec1326ece1edeb56d4cc54b545"; + version = "0.11.7"; + sha256 = "a3ea3e27adfc235376acaa0a90c54b1597b2efbd70ac75b7644fa1b85039514e"; configureFlags = [ "-f-fast-bignum" ]; setupHaskellDepends = [ base Cabal ]; libraryHaskellDepends = [ base bytestring network time ]; @@ -667,48 +888,69 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/vshabanov/HsOpenSSL"; description = "Partial OpenSSL binding for Haskell"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {inherit (pkgs) openssl;}; "HsOpenSSL-x509-system" = callPackage - ({ mkDerivation, base, bytestring, HsOpenSSL, stdenv, unix }: + ({ mkDerivation, base, bytestring, HsOpenSSL, lib, unix }: mkDerivation { pname = "HsOpenSSL-x509-system"; - version = "0.1.0.3"; - sha256 = "5bdcb7ae2faba07a374109fea0a1431ae09d080f8574e60ab7a351b46f931f92"; + version = "0.1.0.4"; + sha256 = "1956efbb1047b9f5fc646f7d68ceeafbf335aae7e6fe154eba9f86871738b796"; libraryHaskellDepends = [ base bytestring HsOpenSSL unix ]; doHaddock = false; doCheck = false; homepage = "https://github.com/redneb/HsOpenSSL-x509-system"; description = "Use the system's native CA certificate store with HsOpenSSL"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "HsYAML" = callPackage - ({ mkDerivation, base, bytestring, containers, mtl, parsec, stdenv - , text + ({ mkDerivation, base, bytestring, containers, deepseq, lib, mtl + , parsec, text }: mkDerivation { pname = "HsYAML"; - version = "0.1.1.3"; - sha256 = "5dd03c26c4d82e9cebab4ba6104389790aa0dbd411eafcd56245c7b65ae5932b"; + version = "0.2.1.0"; + sha256 = "60f727d5c90e693ef71df7dcbed8f40b66d2db11375528043e0326749e861f83"; + revision = "2"; + editedCabalFile = "0f7867jfzlmlqnkv3fjrzjvvfzjlvhbm10kmg7n0qk69ic8grkbc"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - base bytestring containers mtl parsec text + base bytestring containers deepseq mtl parsec text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/hvr/HsYAML"; - description = "Pure Haskell YAML 1.2 parser"; - license = stdenv.lib.licenses.gpl2; + description = "Pure Haskell YAML 1.2 processor"; + license = lib.licenses.gpl2Only; + }) {}; + "HsYAML-aeson" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers, HsYAML, lib + , mtl, scientific, text, unordered-containers, vector + }: + mkDerivation { + pname = "HsYAML-aeson"; + version = "0.2.0.0"; + sha256 = "cfb9634b43fcaddb5a520838119ba4b02b18423a35471fef5a805d6004e75d8b"; + revision = "3"; + editedCabalFile = "0vhdndyj5f07vvvnssn5ybdja5wmaydq0n2lfpihvdg4dkhczrx2"; + libraryHaskellDepends = [ + aeson base bytestring containers HsYAML mtl scientific text + unordered-containers vector + ]; + doHaddock = false; + doCheck = false; + description = "JSON to YAML Adapter"; + license = lib.licenses.gpl2Plus; }) {}; "IPv6Addr" = callPackage - ({ mkDerivation, aeson, attoparsec, base, iproute, network - , network-info, random, stdenv, text + ({ mkDerivation, aeson, attoparsec, base, iproute, lib, network + , network-info, random, text }: mkDerivation { pname = "IPv6Addr"; - version = "1.1.1"; - sha256 = "3b0959a9f1357b12aff50bda88e3af6e13ba0787758209c68a60fb6e88755e50"; + version = "2.0.2"; + sha256 = "7c76ab1d7051058bf828e80298ba5e1850ab0391be693ffccb0b6d0a8a10e164"; libraryHaskellDepends = [ aeson attoparsec base iproute network network-info random text ]; @@ -716,10 +958,10 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/MichelBoucey/IPv6Addr"; description = "Library to deal with IPv6 address text representations"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "Imlib" = callPackage - ({ mkDerivation, array, base, imlib2, stdenv, X11 }: + ({ mkDerivation, array, base, imlib2, lib, X11 }: mkDerivation { pname = "Imlib"; version = "0.1.2"; @@ -728,31 +970,29 @@ inherit (pkgs) zlib;}; librarySystemDepends = [ imlib2 ]; doHaddock = false; doCheck = false; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) imlib2;}; "IntervalMap" = callPackage - ({ mkDerivation, base, containers, deepseq, stdenv }: + ({ mkDerivation, base, containers, deepseq, lib }: mkDerivation { pname = "IntervalMap"; - version = "0.6.1.0"; - sha256 = "133676b9e01008b9d9bfeb5dbf3f51aabdc53b3a334588e68a8b6f5089ab873c"; + version = "0.6.1.2"; + sha256 = "8df21ea147e3596f1c7f2fc1a8b153fb1199c8fd0a2c428ab2c5fd3039fc550f"; libraryHaskellDepends = [ base containers deepseq ]; doHaddock = false; doCheck = false; homepage = "http://www.chr-breitkopf.de/comp/IntervalMap"; description = "Containers for intervals, with efficient search"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "JuicyPixels" = callPackage - ({ mkDerivation, base, binary, bytestring, containers, deepseq, mtl - , primitive, stdenv, transformers, vector, zlib + ({ mkDerivation, base, binary, bytestring, containers, deepseq, lib + , mtl, primitive, transformers, vector, zlib }: mkDerivation { pname = "JuicyPixels"; - version = "3.3.3"; - sha256 = "2c04b5b6504a780e9363dc8894837976e18ce0623182e38aab6bc5e76c40b3c4"; - revision = "1"; - editedCabalFile = "1q8xyxn1a4ldaa1grmr7dywdbf4vqjw65v52h6z7ssz12hgjx0gq"; + version = "3.3.5"; + sha256 = "eca5144499ec7148943e687be1d14354024a51447dd2b0470e6c64539c97447a"; libraryHaskellDepends = [ base binary bytestring containers deepseq mtl primitive transformers vector zlib @@ -761,32 +1001,56 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/Twinside/Juicy.Pixels"; description = "Picture loading/serialization (in png, jpeg, bitmap, gif, tga, tiff and radiance)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "JuicyPixels-blurhash" = callPackage + ({ mkDerivation, base, bytestring, containers, filepath + , JuicyPixels, lib, optparse-applicative, vector + }: + mkDerivation { + pname = "JuicyPixels-blurhash"; + version = "0.1.0.3"; + sha256 = "c08c5fbd968b8619823c470c7683dadf25f6b57a1cd8997dc1e882948e14f44d"; + revision = "5"; + editedCabalFile = "1iv2jz1jwndpfj68zqkya1yc45fs43anc8dqbk2pdbqyxwlxwfaj"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base bytestring containers filepath JuicyPixels vector + ]; + executableHaskellDepends = [ + base bytestring containers filepath JuicyPixels + optparse-applicative vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/SamProtas/JuicyPixels-blurhash#readme"; + description = "Blurhash is a very compact represenation of a placeholder for an image"; + license = lib.licenses.bsd3; }) {}; "JuicyPixels-extra" = callPackage - ({ mkDerivation, base, JuicyPixels, stdenv }: + ({ mkDerivation, base, JuicyPixels, lib }: mkDerivation { pname = "JuicyPixels-extra"; - version = "0.4.0"; - sha256 = "0cbff986501adc734742b41414e5d0bb414a02cd2d6ee19be037700e90168ca6"; + version = "0.5.1"; + sha256 = "f8cad5b6bf8d79103ebca6889fc1972792397c87edca91303f59c2ea0d15ebcd"; enableSeparateDataOutput = true; libraryHaskellDepends = [ base JuicyPixels ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mrkkrp/JuicyPixels-extra"; description = "Efficiently scale, crop, flip images with JuicyPixels"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "JuicyPixels-scale-dct" = callPackage - ({ mkDerivation, base, base-compat, carray, fft, JuicyPixels - , stdenv + ({ mkDerivation, base, base-compat, carray, fft, JuicyPixels, lib }: mkDerivation { pname = "JuicyPixels-scale-dct"; version = "0.1.2"; sha256 = "f7381b88446224897e6677692bbdc39cb5b755216212f0ad8050046865cd3013"; - revision = "2"; - editedCabalFile = "0pp67ygrd3m6q8ry5229m1b2rhy401gb74368h09bqc6wa3g7ygv"; + revision = "6"; + editedCabalFile = "0np8wqf0s0pwqnjfhs8zw9h133p2x173xbv984c4dn5a1xhn0azq"; libraryHaskellDepends = [ base base-compat carray fft JuicyPixels ]; @@ -794,11 +1058,44 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/phadej/JuicyPixels-scale-dct#readme"; description = "Scale JuicyPixels images with DCT"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "LambdaHack" = callPackage + ({ mkDerivation, assert-failure, async, base, base-compat, binary + , bytestring, containers, deepseq, directory, enummapset + , file-embed, filepath, ghc-compact, ghc-prim, hashable, hsini + , int-cast, keys, lib, miniutter, open-browser + , optparse-applicative, pretty-show, primitive, sdl2, sdl2-ttf + , splitmix, stm, template-haskell, text, th-lift-instances, time + , transformers, unordered-containers, vector + , vector-binary-instances, zlib + }: + mkDerivation { + pname = "LambdaHack"; + version = "0.10.2.0"; + sha256 = "6c8a86150c0c696c55e294db528c4776e17b5bc097895f7f442aab19aa6f02f4"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + assert-failure async base base-compat binary bytestring containers + deepseq directory enummapset file-embed filepath ghc-compact + ghc-prim hashable hsini int-cast keys miniutter open-browser + optparse-applicative pretty-show primitive sdl2 sdl2-ttf splitmix + stm template-haskell text th-lift-instances time transformers + unordered-containers vector vector-binary-instances zlib + ]; + executableHaskellDepends = [ + async base filepath optparse-applicative + ]; + doHaddock = false; + doCheck = false; + homepage = "https://lambdahack.github.io"; + description = "A game engine library for tactical squad ASCII roguelike dungeon crawlers"; + license = lib.licenses.bsd3; }) {}; "LibZip" = callPackage - ({ mkDerivation, base, bindings-libzip, bytestring, filepath, mtl - , stdenv, time, utf8-string + ({ mkDerivation, base, bindings-libzip, bytestring, filepath, lib + , mtl, time, utf8-string }: mkDerivation { pname = "LibZip"; @@ -811,10 +1108,10 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "http://bitbucket.org/astanin/hs-libzip/"; description = "Bindings to libzip, a library for manipulating zip archives"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "List" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "List"; version = "0.6.2"; @@ -826,31 +1123,28 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/yairchu/generator"; description = "List monad transformer and class"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "ListLike" = callPackage ({ mkDerivation, array, base, bytestring, containers, deepseq - , dlist, fmlist, stdenv, text, utf8-string, vector + , dlist, fmlist, lib, text, utf8-string, vector }: mkDerivation { pname = "ListLike"; - version = "4.6"; - sha256 = "c1cdec79a5f585a5839eea26a2afe6a37aab5ed2f402a16e7d59fe9a4e925a9a"; - revision = "2"; - editedCabalFile = "1mca2r4gjznqdh4kck5cjkn53isgkhvkf3ri09qsn7nsssvgki0g"; + version = "4.7.4"; + sha256 = "11d3c076ff08daa896321ab3140767103dd9fc61e1a308a482447904c0cf1e9c"; libraryHaskellDepends = [ array base bytestring containers deepseq dlist fmlist text utf8-string vector ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/JohnLato/listlike"; - description = "Generic support for list-like structures"; - license = stdenv.lib.licenses.bsd3; + homepage = "http://github.com/ddssff/listlike"; + description = "Generalized support for list-like structures"; + license = lib.licenses.bsd3; }) {}; "ListTree" = callPackage - ({ mkDerivation, base, directory, filepath, List, stdenv - , transformers + ({ mkDerivation, base, directory, filepath, lib, List, transformers }: mkDerivation { pname = "ListTree"; @@ -863,14 +1157,27 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/yairchu/generator/tree"; description = "Trees and monadic trees expressed as monadic lists where the underlying monad is a list"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "MapWith" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "MapWith"; + version = "0.2.0.0"; + sha256 = "4ab6333b5e20f8e484e9da8f855af3d6ab5851f4966caeb0208e2e3f90547ef6"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/davjam/MapWith#readme"; + description = "mapWith: like fmap, but with additional parameters (isFirst, isLast, etc)"; + license = lib.licenses.bsd3; }) {}; "MemoTrie" = callPackage - ({ mkDerivation, base, newtype-generics, stdenv }: + ({ mkDerivation, base, lib, newtype-generics }: mkDerivation { pname = "MemoTrie"; - version = "0.6.9"; - sha256 = "1d6045b8fdf7b89ed6b495e535613f5091cdfc9cdfe05a862207e76ce205f794"; + version = "0.6.10"; + sha256 = "584df0e138093b2f2edc893a69883eb8cbca3402ebdc75392a7742e86156ba53"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base newtype-generics ]; @@ -878,29 +1185,10 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/conal/MemoTrie"; description = "Trie-based memo functions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "MissingH" = callPackage - ({ mkDerivation, array, base, containers, directory, filepath - , hslogger, HUnit, mtl, network, old-locale, old-time, parsec - , process, random, regex-compat, stdenv, time, unix - }: - mkDerivation { - pname = "MissingH"; - version = "1.4.1.0"; - sha256 = "49ecd2df3ad45d6da64a984e506cd0e2ca02c238a743d757feeea8c4cddce0ca"; - libraryHaskellDepends = [ - array base containers directory filepath hslogger HUnit mtl network - old-locale old-time parsec process random regex-compat time unix - ]; - doHaddock = false; - doCheck = false; - homepage = "http://software.complete.org/missingh"; - description = "Large utility library"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "MonadPrompt" = callPackage - ({ mkDerivation, base, mtl, stdenv }: + "MonadPrompt" = callPackage + ({ mkDerivation, base, lib, mtl }: mkDerivation { pname = "MonadPrompt"; version = "1.0.0.5"; @@ -909,27 +1197,29 @@ inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "MonadPrompt, implementation & examples"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "MonadRandom" = callPackage - ({ mkDerivation, base, mtl, primitive, random, stdenv, transformers + ({ mkDerivation, base, lib, mtl, primitive, random, transformers , transformers-compat }: mkDerivation { pname = "MonadRandom"; - version = "0.5.1.1"; - sha256 = "abda4a297acf197e664695b839b4fb70f53e240f5420489dc21bcf6103958470"; + version = "0.5.3"; + sha256 = "27184dadda0a49abac0208a1e6576b14217a60dc45b6839cd9e90af25ee00a9f"; + revision = "1"; + editedCabalFile = "1wpgmcv704i7x38jwalnbmx8c10vdw269gbvzjxaj4rlvff3s4sq"; libraryHaskellDepends = [ base mtl primitive random transformers transformers-compat ]; doHaddock = false; doCheck = false; description = "Random-number generation monad"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "MusicBrainz" = callPackage ({ mkDerivation, aeson, base, bytestring, conduit, conduit-extra - , HTTP, http-conduit, http-types, monad-control, resourcet, stdenv + , HTTP, http-conduit, http-types, lib, monad-control, resourcet , text, time, time-locale-compat, transformers, unliftio-core , vector, xml-conduit, xml-types }: @@ -946,10 +1236,10 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "http://floss.scru.org/hMusicBrainz"; description = "interface to MusicBrainz XML2 and JSON web services"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; }) {}; "NineP" = callPackage - ({ mkDerivation, base, binary, bytestring, stdenv }: + ({ mkDerivation, base, binary, bytestring, lib }: mkDerivation { pname = "NineP"; version = "0.0.2.1"; @@ -960,23 +1250,10 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "http://9ph.googlecode.com"; description = "9P2000 in pure Haskell"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "NoHoed" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: - mkDerivation { - pname = "NoHoed"; - version = "0.1.1"; - sha256 = "9b663a234c034e0049126ae7f06d1756dc496012177bf18548c6d8caeec43b3d"; - libraryHaskellDepends = [ base template-haskell ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/pepeiborra/NoHoed"; - description = "Placeholder package to preserve debug ability via conditional builds"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "NumInstances" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "NumInstances"; version = "1.4"; @@ -986,10 +1263,10 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/conal/NumInstances"; description = "Instances of numeric classes for functions and tuples"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "ObjectName" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "ObjectName"; version = "1.1.0.1"; @@ -999,24 +1276,24 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/svenpanne/ObjectName"; description = "Explicitly handled object names"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "OneTuple" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "OneTuple"; - version = "0.2.2"; - sha256 = "d82e702485bcbdefbda0d12b6a250d318a269572ee58d63b60eee531e56624dc"; + version = "0.2.2.1"; + sha256 = "acc7721c3cb67da5d6d31b22812da1f418c2f74a84e97c30426294e4e6349a96"; revision = "1"; - editedCabalFile = "07jd23glblzmnlw7sn565sk9gm7vj9h459j46bkbcrrxnp0n0myq"; + editedCabalFile = "03mygfz7lv6h0i30bq2grvmahbg9j7a36mc0wls2nr81dv9p19s7"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; description = "Singleton Tuple"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "Only" = callPackage - ({ mkDerivation, base, deepseq, stdenv }: + ({ mkDerivation, base, deepseq, lib }: mkDerivation { pname = "Only"; version = "0.1"; @@ -1027,16 +1304,16 @@ inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "The 1-tuple type or single-value \"collection\""; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "OpenAL" = callPackage - ({ mkDerivation, base, ObjectName, openal, OpenGL, StateVar, stdenv + ({ mkDerivation, base, lib, ObjectName, openal, OpenGL, StateVar , transformers }: mkDerivation { pname = "OpenAL"; - version = "1.7.0.4"; - sha256 = "3989f6c4fe437843551004dd011c4308bf63d787ae4fbb8ce71d44b1b0b1f118"; + version = "1.7.0.5"; + sha256 = "343a546d94f8d05008896be509149b94ad601c0b48a83dd9e26990a0e97af898"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -1047,34 +1324,36 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/haskell-openal/ALUT"; description = "A binding to the OpenAL cross-platform 3D audio API"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) openal;}; "OpenGL" = callPackage - ({ mkDerivation, base, bytestring, containers, GLURaw, ObjectName - , OpenGLRaw, StateVar, stdenv, text, transformers + ({ mkDerivation, base, bytestring, containers, GLURaw, lib + , ObjectName, OpenGLRaw, StateVar, text, transformers }: mkDerivation { pname = "OpenGL"; - version = "3.0.2.2"; - sha256 = "4cba40fe8eecee67c8251556b4c05d9e98256c11d49c20e914f8232bfae67da7"; + version = "3.0.3.0"; + sha256 = "5a05ffc752dfc7dd16818d7b3c7c59a27639e246cdfa1963fa02e3ce247a2e19"; + revision = "1"; + editedCabalFile = "1748mrb6r9mpf5jbrx436lwbg8w6dadyy8dhxw2dwnrj5z7zf741"; libraryHaskellDepends = [ base bytestring containers GLURaw ObjectName OpenGLRaw StateVar text transformers ]; doHaddock = false; doCheck = false; - homepage = "http://www.haskell.org/haskellwiki/Opengl"; + homepage = "https://wiki.haskell.org/OpenGL"; description = "A binding for the OpenGL graphics system"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "OpenGLRaw" = callPackage - ({ mkDerivation, base, bytestring, containers, fixed, half, libGL - , stdenv, text, transformers + ({ mkDerivation, base, bytestring, containers, fixed, half, lib + , libGL, text, transformers }: mkDerivation { pname = "OpenGLRaw"; - version = "3.3.1.0"; - sha256 = "6b0745f6d421f658b57c13bfdbae014c0aa6871a98e11e98908d4a04461f1cf5"; + version = "3.3.4.0"; + sha256 = "756169eaadfe16627a893c35e7952d82ff466ac77b13ec2d1ea1de8fb5afba3e"; libraryHaskellDepends = [ base bytestring containers fixed half text transformers ]; @@ -1083,10 +1362,10 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Opengl"; description = "A raw binding for the OpenGL graphics system"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) libGL;}; "ParsecTools" = callPackage - ({ mkDerivation, base, parsec, stdenv }: + ({ mkDerivation, base, lib, parsec }: mkDerivation { pname = "ParsecTools"; version = "0.0.2.0"; @@ -1095,10 +1374,27 @@ inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Parsec combinators for more complex objects"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; + }) {}; + "PyF" = callPackage + ({ mkDerivation, base, containers, haskell-src-exts + , haskell-src-meta, lib, megaparsec, mtl, template-haskell, text + }: + mkDerivation { + pname = "PyF"; + version = "0.9.0.3"; + sha256 = "c8c9f1759cc14ebe7d2bf37890dcd6979d155435cd461e581dbfc436b0cf3ff4"; + libraryHaskellDepends = [ + base containers haskell-src-exts haskell-src-meta megaparsec mtl + template-haskell text + ]; + doHaddock = false; + doCheck = false; + description = "Quasiquotations for a python like interpolated string formater"; + license = lib.licenses.bsd3; }) {}; "QuasiText" = callPackage - ({ mkDerivation, attoparsec, base, haskell-src-meta, stdenv + ({ mkDerivation, attoparsec, base, haskell-src-meta, lib , template-haskell, text, th-lift-instances }: mkDerivation { @@ -1113,51 +1409,67 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mikeplus64/QuasiText"; description = "A QuasiQuoter for Text"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "QuickCheck" = callPackage - ({ mkDerivation, base, containers, deepseq, erf, random, stdenv - , template-haskell, tf-random, transformers + ({ mkDerivation, base, containers, deepseq, lib, random, splitmix + , template-haskell, transformers }: mkDerivation { pname = "QuickCheck"; - version = "2.12.6.1"; - sha256 = "0b2aa7f5c625b5875c36f5f548926fcdaedf4311bd3a4c291fcf10b8d7faa170"; + version = "2.14.2"; + sha256 = "d87b6c85696b601175274361fa62217894401e401e150c3c5d4013ac53cd36f3"; + configureFlags = [ "-f-old-random" ]; libraryHaskellDepends = [ - base containers deepseq erf random template-haskell tf-random + base containers deepseq random splitmix template-haskell transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nick8325/quickcheck"; description = "Automatic testing of Haskell programs"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "RSA" = callPackage ({ mkDerivation, base, binary, bytestring, crypto-api - , crypto-pubkey-types, SHA, stdenv + , crypto-pubkey-types, lib, SHA }: mkDerivation { pname = "RSA"; - version = "2.3.1"; - sha256 = "5c929c14de467a9f032641e1b79cbb31a796615c89bf90d059aee5b04eb3671a"; + version = "2.4.1"; + sha256 = "72c5d8c45ef1013e0e8aff763bb8894df0f022f28e698e33ae87bbdb33d69041"; libraryHaskellDepends = [ base binary bytestring crypto-api crypto-pubkey-types SHA ]; doHaddock = false; doCheck = false; description = "Implementation of RSA, using the padding schemes of PKCS#1 v2.1."; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "Ranged-sets" = callPackage + ({ mkDerivation, base, HUnit, lib, QuickCheck }: + mkDerivation { + pname = "Ranged-sets"; + version = "0.4.0"; + sha256 = "4b25a843f0fbbeda9bf218e3f4be7f1ac58704e433a08ef02ead1dee8d126dea"; + revision = "2"; + editedCabalFile = "1dl69wa509yn2jvl0d4c5c036swq22i6nd73kqn0bp7vhbj4rfq4"; + libraryHaskellDepends = [ base HUnit QuickCheck ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/PaulJohnson/Ranged-sets"; + description = "Ranged sets for Haskell"; + license = lib.licenses.bsd3; }) {}; "Rasterific" = callPackage ({ mkDerivation, base, bytestring, containers, dlist, FontyFruity - , free, JuicyPixels, mtl, primitive, stdenv, transformers, vector + , free, JuicyPixels, lib, mtl, primitive, transformers, vector , vector-algorithms }: mkDerivation { pname = "Rasterific"; - version = "0.7.4.2"; - sha256 = "811b41ac7af262d58ae5bd1fe51d4e2cacbd6dd0ef163b7b5e8f98c5361be6e9"; + version = "0.7.5.4"; + sha256 = "c1156b67e8314522448449de7815fdfc815b5ee6b616baf9c17d16b484a3511f"; libraryHaskellDepends = [ base bytestring containers dlist FontyFruity free JuicyPixels mtl primitive transformers vector vector-algorithms @@ -1165,11 +1477,29 @@ inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A pure haskell drawing engine"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "Rattus" = callPackage + ({ mkDerivation, base, Cabal, containers, ghc, ghc-prim, lib + , simple-affine-space, transformers + }: + mkDerivation { + pname = "Rattus"; + version = "0.5"; + sha256 = "75c4c096dcc8a96c026819d78575e5c3e34bf66c9f400ccfb40f62ae90a506b6"; + setupHaskellDepends = [ base Cabal ]; + libraryHaskellDepends = [ + base containers ghc ghc-prim simple-affine-space transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/pa-ba/Rattus"; + description = "A modal FRP language"; + license = lib.licenses.bsd3; }) {}; "RefSerialize" = callPackage ({ mkDerivation, base, binary, bytestring, containers, hashtables - , stdenv, stringsearch + , lib, stringsearch }: mkDerivation { pname = "RefSerialize"; @@ -1181,10 +1511,10 @@ inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Write to and read from ByteStrings maintaining internal memory references"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "SHA" = callPackage - ({ mkDerivation, array, base, binary, bytestring, stdenv }: + ({ mkDerivation, array, base, binary, bytestring, lib }: mkDerivation { pname = "SHA"; version = "1.6.4.4"; @@ -1195,33 +1525,22 @@ inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Implementations of the SHA suite of message digest functions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "SVGFonts" = callPackage - ({ mkDerivation, attoparsec, base, blaze-markup, blaze-svg - , bytestring, cereal, cereal-vector, containers, data-default-class - , diagrams-core, diagrams-lib, directory, parsec, split, stdenv - , text, vector, xml - }: + "STMonadTrans" = callPackage + ({ mkDerivation, array, base, lib, mtl }: mkDerivation { - pname = "SVGFonts"; - version = "1.7"; - sha256 = "da3ccd65e0963473df035f4543b56dfc84b45edca540990050e5de444fa431cd"; - revision = "1"; - editedCabalFile = "1w687f4lk4l07wqgldhpg7ycid0fs099x8vrylcxqdgfrzmm04dg"; - enableSeparateDataOutput = true; - libraryHaskellDepends = [ - attoparsec base blaze-markup blaze-svg bytestring cereal - cereal-vector containers data-default-class diagrams-core - diagrams-lib directory parsec split text vector xml - ]; + pname = "STMonadTrans"; + version = "0.4.5"; + sha256 = "35815e2c2648e49f0f4e154a46e200ebe18b0d1ca9cdfa254115cd1fe5179e4e"; + libraryHaskellDepends = [ array base mtl ]; doHaddock = false; doCheck = false; - description = "Fonts from the SVG-Font format"; - license = stdenv.lib.licenses.bsd3; + description = "A monad transformer version of the ST monad"; + license = lib.licenses.bsd3; }) {}; "SafeSemaphore" = callPackage - ({ mkDerivation, base, containers, stdenv, stm }: + ({ mkDerivation, base, containers, lib, stm }: mkDerivation { pname = "SafeSemaphore"; version = "0.10.1"; @@ -1233,16 +1552,41 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/ChrisKuklewicz/SafeSemaphore"; description = "Much safer replacement for QSemN, QSem, and SampleVar"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "ShellCheck" = callPackage + ({ mkDerivation, aeson, array, base, bytestring, containers + , deepseq, Diff, directory, filepath, lib, mtl, parsec, process + , QuickCheck, regex-tdfa + }: + mkDerivation { + pname = "ShellCheck"; + version = "0.7.2"; + sha256 = "ff7534d80c3dc8817c0794a76f432979a7d5c2e537ee5a7c19b424aca41d8472"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson array base bytestring containers deepseq Diff directory + filepath mtl parsec process QuickCheck regex-tdfa + ]; + executableHaskellDepends = [ + aeson array base bytestring containers deepseq Diff directory + filepath mtl parsec QuickCheck regex-tdfa + ]; + doHaddock = false; + doCheck = false; + homepage = "https://www.shellcheck.net/"; + description = "Shell script analysis tool"; + license = lib.licenses.gpl3Only; }) {}; "Spintax" = callPackage - ({ mkDerivation, attoparsec, base, extra, mtl, mwc-random, stdenv + ({ mkDerivation, attoparsec, base, extra, lib, mtl, mwc-random , text }: mkDerivation { pname = "Spintax"; - version = "0.3.3"; - sha256 = "21df2193bf1216d55a0d43691182125993eeadc6f097eaf5eb995c23f2016b13"; + version = "0.3.6"; + sha256 = "d3ccfe6f02ee8b763adaf76752aae3a35b855656128ee9b851511cbc7fbe1e00"; libraryHaskellDepends = [ attoparsec base extra mtl mwc-random text ]; @@ -1250,38 +1594,36 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/MichelBoucey/spintax"; description = "Random text generation based on spintax"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "StateVar" = callPackage - ({ mkDerivation, base, stdenv, stm, transformers }: + ({ mkDerivation, base, lib, stm, transformers }: mkDerivation { pname = "StateVar"; - version = "1.1.1.1"; - sha256 = "eb6436516ab2d5e3d3e070b5a1595c4dceea760a58a9cc8d23dad5f6008f2223"; + version = "1.2.1"; + sha256 = "ee261552912b60d8b937f0253615e310e6cc25f9c407001b3bcc2e3d55000f8b"; libraryHaskellDepends = [ base stm transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-opengl/StateVar"; description = "State variables"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "Strafunski-StrategyLib" = callPackage - ({ mkDerivation, base, directory, mtl, stdenv, syb, transformers }: + "Stream" = callPackage + ({ mkDerivation, base, lazysmallcheck, lib, QuickCheck }: mkDerivation { - pname = "Strafunski-StrategyLib"; - version = "5.0.1.0"; - sha256 = "a018c7420289a381d2b491a753f685b9d691be07cea99855cc5c8e05d5a9a295"; - revision = "1"; - editedCabalFile = "1hngxq1f7fybg6ixkdhmvgsw608mhnxkwbw04ql5zspcfl78v6l2"; - libraryHaskellDepends = [ base directory mtl syb transformers ]; + pname = "Stream"; + version = "0.4.7.2"; + sha256 = "990be249b3ef1b0075563026d4d2c803b86e3cbf168965ba6f9f2b4227a007d1"; + libraryHaskellDepends = [ base lazysmallcheck QuickCheck ]; doHaddock = false; doCheck = false; - description = "Library for strategic programming"; - license = stdenv.lib.licenses.bsd3; + description = "A library for manipulating infinite lists"; + license = lib.licenses.bsd3; }) {}; "TCache" = callPackage ({ mkDerivation, base, bytestring, containers, directory - , hashtables, mtl, old-time, RefSerialize, stdenv, stm, text + , hashtables, lib, mtl, old-time, RefSerialize, stm, text }: mkDerivation { pname = "TCache"; @@ -1294,26 +1636,41 @@ inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A Transactional cache with user-defined persistence"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "TotalMap" = callPackage - ({ mkDerivation, adjunctions, base, distributive, generics-sop - , lens, stdenv + "Taxonomy" = callPackage + ({ mkDerivation, aeson, base, bytestring, either-unwrap, fgl + , graphviz, lib, parsec, text, vector }: mkDerivation { - pname = "TotalMap"; - version = "0.1.0.0"; - sha256 = "6de8ad8ff44848473ab8bd2fed776de1dfe043dca6ca81ff4877a9a98a2c894c"; + pname = "Taxonomy"; + version = "2.2.0"; + sha256 = "3c71e4f32b0b73229c48b83fbf1750ab9eb1e36e7d21dfd6afb64c10ca1d9567"; libraryHaskellDepends = [ - adjunctions base distributive generics-sop lens + aeson base bytestring either-unwrap fgl graphviz parsec text vector ]; doHaddock = false; doCheck = false; - description = "A total map datatype"; - license = stdenv.lib.licenses.mit; + description = "Libary for parsing, processing and vizualization of taxonomy data"; + license = lib.licenses.gpl3Only; + }) {}; + "TypeCompose" = callPackage + ({ mkDerivation, base, base-orphans, lib }: + mkDerivation { + pname = "TypeCompose"; + version = "0.9.14"; + sha256 = "56034f7917c7464e3be93754c36302d91b8d750f84f6ed7af146f94c4fd05a57"; + revision = "1"; + editedCabalFile = "1pxg6az5vkl0zvs3zdvvvnhxqawd9fkkd44jmzzzyyibppgni6x4"; + libraryHaskellDepends = [ base base-orphans ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/conal/TypeCompose"; + description = "Type composition classes & instances"; + license = lib.licenses.bsd3; }) {}; "ViennaRNAParser" = callPackage - ({ mkDerivation, base, parsec, ParsecTools, process, stdenv + ({ mkDerivation, base, lib, parsec, ParsecTools, process , transformers }: mkDerivation { @@ -1326,10 +1683,25 @@ inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Libary for parsing ViennaRNA package output"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; + }) {}; + "Win32" = callPackage + ({ mkDerivation, lib }: + mkDerivation { + pname = "Win32"; + version = "2.6.1.0"; + sha256 = "eba445ba0717e96f239c984890f67172e7bfe72a23f32f37fe265b6cadfd9ce3"; + revision = "1"; + editedCabalFile = "1ia6dk2fvxg3gzqdmcypdka6fcnnrza23hq1rhslj53jy3qzs3kn"; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell/win32"; + description = "A binding to part of the Win32 library"; + license = lib.licenses.bsd3; + platforms = lib.platforms.none; }) {}; "Win32-notify" = callPackage - ({ mkDerivation, base, containers, directory, stdenv, Win32 }: + ({ mkDerivation, base, containers, directory, lib, Win32 }: mkDerivation { pname = "Win32-notify"; version = "0.3.0.3"; @@ -1340,17 +1712,17 @@ inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A binding to part of the Win32 library for file notification"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "X11" = callPackage - ({ mkDerivation, base, data-default, libX11, libXext, libXinerama - , libXrandr, libXrender, libXScrnSaver, stdenv + ({ mkDerivation, base, data-default-class, lib, libX11, libXext + , libXinerama, libXrandr, libXrender, libXScrnSaver }: mkDerivation { pname = "X11"; - version = "1.9"; - sha256 = "10138e863d8c6f860aad1755a6f1a36949cc02d83e5afacf6677fb3999f10db9"; - libraryHaskellDepends = [ base data-default ]; + version = "1.10"; + sha256 = "b6a01287e2949bebd8898c4a6672aa33d60b63318b2a9df5963fa6d47dc62dff"; + libraryHaskellDepends = [ base data-default-class ]; librarySystemDepends = [ libX11 libXext libXinerama libXrandr libXrender libXScrnSaver ]; @@ -1358,11 +1730,11 @@ inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/xmonad/X11"; description = "A binding to the X11 graphics library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs.xorg) libXScrnSaver; inherit (pkgs.xorg) libXext; inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; "X11-xft" = callPackage - ({ mkDerivation, base, libXft, stdenv, utf8-string, X11 }: + ({ mkDerivation, base, lib, libXft, utf8-string, X11 }: mkDerivation { pname = "X11-xft"; version = "0.3.1"; @@ -1375,7 +1747,7 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; license = "LGPL"; }) {}; "Xauth" = callPackage - ({ mkDerivation, base, libXau, stdenv }: + ({ mkDerivation, base, lib, libXau }: mkDerivation { pname = "Xauth"; version = "0.1"; @@ -1385,10 +1757,10 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doHaddock = false; doCheck = false; description = "A binding to the X11 authentication library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "abstract-deque" = callPackage - ({ mkDerivation, array, base, containers, random, stdenv, time }: + ({ mkDerivation, array, base, containers, lib, random, time }: mkDerivation { pname = "abstract-deque"; version = "0.3"; @@ -1398,28 +1770,10 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/rrnewton/haskell-lockfree/wiki"; description = "Abstract, parameterized interface to mutable Deques"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "abstract-deque-tests" = callPackage - ({ mkDerivation, abstract-deque, array, base, containers, HUnit - , random, stdenv, test-framework, test-framework-hunit, time - }: - mkDerivation { - pname = "abstract-deque-tests"; - version = "0.3"; - sha256 = "5f17fb4cc26559f81c777f494622907e8927181175eaa172fb6adbf14b2feba5"; - libraryHaskellDepends = [ - abstract-deque array base containers HUnit random test-framework - test-framework-hunit time - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/rrnewton/haskell-lockfree/wiki"; - description = "A test-suite for any queue or double-ended queue satisfying an interface"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "abstract-par" = callPackage - ({ mkDerivation, base, deepseq, stdenv }: + ({ mkDerivation, base, deepseq, lib }: mkDerivation { pname = "abstract-par"; version = "0.3.3"; @@ -1429,10 +1783,10 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/simonmar/monad-par"; description = "Type classes generalizing the functionality of the 'monad-par' library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "accuerr" = callPackage - ({ mkDerivation, base, bifunctors, lens, semigroups, stdenv }: + ({ mkDerivation, base, bifunctors, lens, lib, semigroups }: mkDerivation { pname = "accuerr"; version = "0.2.0.2"; @@ -1442,11 +1796,11 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "http://www.github.com/massysett/accuerr"; description = "Data type like Either but with accumulating error type"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "ace" = callPackage ({ mkDerivation, attoparsec, base, blaze-html, blaze-markup - , data-default, parsec, stdenv, text + , data-default, lib, parsec, text }: mkDerivation { pname = "ace"; @@ -1458,10 +1812,10 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doHaddock = false; doCheck = false; description = "Attempto Controlled English parser and printer"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "action-permutations" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "action-permutations"; version = "0.0.0.1"; @@ -1470,37 +1824,19 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doHaddock = false; doCheck = false; description = "Execute a set of actions (e.g. parsers) in each possible order"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "active" = callPackage - ({ mkDerivation, base, lens, linear, semigroupoids, semigroups - , stdenv, vector - }: - mkDerivation { - pname = "active"; - version = "0.2.0.13"; - sha256 = "5d9a141d58bcefbf699ed233a22309ded671c25ed64bcee11a663d00731280fb"; - revision = "7"; - editedCabalFile = "0z4l6j1q3y5zq4941bsb6ypkhfg3pyvb5gcmasymh2nj9g952xkd"; - libraryHaskellDepends = [ - base lens linear semigroupoids semigroups vector - ]; - doHaddock = false; - doCheck = false; - description = "Abstractions for animation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "ad" = callPackage ({ mkDerivation, array, base, Cabal, cabal-doctest, comonad - , containers, data-reify, erf, free, nats, reflection, semigroups - , stdenv, transformers + , containers, data-reify, erf, free, lib, nats, reflection + , semigroups, transformers }: mkDerivation { pname = "ad"; - version = "4.3.5"; - sha256 = "9c5e754b1f0ff83490bcc30f5dfa8504de5a34ab8f7be03ac232882940dc8d60"; - revision = "5"; - editedCabalFile = "0yzyfqhsafzaqzj8wmjrj5ghm6jwbxya3wxc9sjl59j9q20jc4nq"; + version = "4.4.1"; + sha256 = "cf68739f867b57c0ba308462d97be0c3ff89348319b8847707c5125fc1c4d7a9"; + revision = "1"; + editedCabalFile = "1sprgwc6niixmc3p073al3bm3ff873h6zjgizdz2wpqm0b6rfmka"; setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ array base comonad containers data-reify erf free nats reflection @@ -1510,12 +1846,12 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "http://github.com/ekmett/ad"; description = "Automatic Differentiation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "adjunctions" = callPackage ({ mkDerivation, array, base, comonad, containers, contravariant - , distributive, free, mtl, profunctors, semigroupoids, semigroups - , stdenv, tagged, transformers, transformers-compat, void + , distributive, free, lib, mtl, profunctors, semigroupoids + , semigroups, tagged, transformers, transformers-compat, void }: mkDerivation { pname = "adjunctions"; @@ -1532,10 +1868,10 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "http://github.com/ekmett/adjunctions/"; description = "Adjunctions and representable functors"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "adler32" = callPackage - ({ mkDerivation, base, bytestring, stdenv, zlib }: + ({ mkDerivation, base, bytestring, lib, zlib }: mkDerivation { pname = "adler32"; version = "0.1.2.0"; @@ -1546,73 +1882,72 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/redneb/hs-adler32"; description = "An implementation of Adler-32, supporting rolling checksum operation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) zlib;}; - "advent-of-code-api" = callPackage - ({ mkDerivation, attoparsec, base, containers, curl, deepseq - , directory, filepath, finite-typelits, mtl, stdenv, tagsoup, text - , time, uri-encode + "aern2-mp" = callPackage + ({ mkDerivation, base, cdar-mBound, collect-errors, deepseq, hspec + , integer-logarithms, lib, mixed-types-num, QuickCheck, reflection + , regex-tdfa, template-haskell }: mkDerivation { - pname = "advent-of-code-api"; - version = "0.1.2.3"; - sha256 = "f4d48b2519a0e897bdd5d18bade8adb6065e5aa0c6b155caeb2fc3dd1bea49d5"; + pname = "aern2-mp"; + version = "0.2.7.0"; + sha256 = "ef8d649184c55d74c12ad14217aca1445abfea33a6fca113bdec56f3de5358bf"; libraryHaskellDepends = [ - attoparsec base containers curl deepseq directory filepath - finite-typelits mtl tagsoup text time uri-encode + base cdar-mBound collect-errors deepseq hspec integer-logarithms + mixed-types-num QuickCheck reflection regex-tdfa template-haskell ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/mstksg/advent-of-code-api#readme"; - description = "Advent of Code REST API bindings"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/michalkonecny/aern2#readme"; + description = "Multi-precision ball (interval) arithmetic"; + license = lib.licenses.bsd3; }) {}; - "aern2-mp" = callPackage - ({ mkDerivation, base, convertible, hspec, integer-logarithms, lens - , mixed-types-num, QuickCheck, regex-tdfa, rounded, stdenv - , template-haskell + "aern2-real" = callPackage + ({ mkDerivation, aern2-mp, base, collect-errors, hspec + , integer-logarithms, lib, mixed-types-num, QuickCheck }: mkDerivation { - pname = "aern2-mp"; - version = "0.1.3.1"; - sha256 = "758b01846bf21c90aad334867fb29e3115d4b174ac68bd9286ab7ddc7467d1bf"; + pname = "aern2-real"; + version = "0.2.7.0"; + sha256 = "8971e374b0d087d4cef4d64ce8088015fbbc4ad98793be77ca2ee6724e805737"; libraryHaskellDepends = [ - base convertible hspec integer-logarithms lens mixed-types-num - QuickCheck regex-tdfa rounded template-haskell + aern2-mp base collect-errors hspec integer-logarithms + mixed-types-num QuickCheck ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/michalkonecny/aern2"; - description = "Multi-precision ball (interval) arithmetic"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/michalkonecny/aern2#readme"; + description = "Real numbers as sequences of MPBalls"; + license = lib.licenses.bsd3; }) {}; "aeson" = callPackage - ({ mkDerivation, attoparsec, base, base-compat, bytestring - , containers, deepseq, dlist, ghc-prim, hashable, primitive - , scientific, stdenv, tagged, template-haskell, text - , th-abstraction, time, time-locale-compat, unordered-containers - , uuid-types, vector + ({ mkDerivation, attoparsec, base, base-compat-batteries + , bytestring, containers, data-fix, deepseq, dlist, ghc-prim + , hashable, lib, primitive, scientific, strict, tagged + , template-haskell, text, th-abstraction, these, time, time-compat + , unordered-containers, uuid-types, vector }: mkDerivation { pname = "aeson"; - version = "1.4.2.0"; - sha256 = "75ce71814a33d5e5568208e6806a8847e7ba47fea74d30f6a8b1b56ecb318bd0"; + version = "1.5.6.0"; + sha256 = "0361c34be3d2ec945201f02501693436fbda10dcc549469481a084b2de22bfe8"; revision = "1"; - editedCabalFile = "067y82gq86740j2zj4y6v7z9b5860ncg2g9lfnrpsnb9jqm7arl1"; + editedCabalFile = "1y7ddmghsjblsxaj1wyif66wrw0vvp2dca5i7v9rqk33z1r6iryk"; libraryHaskellDepends = [ - attoparsec base base-compat bytestring containers deepseq dlist - ghc-prim hashable primitive scientific tagged template-haskell text - th-abstraction time time-locale-compat unordered-containers - uuid-types vector + attoparsec base base-compat-batteries bytestring containers + data-fix deepseq dlist ghc-prim hashable primitive scientific + strict tagged template-haskell text th-abstraction these time + time-compat unordered-containers uuid-types vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/bos/aeson"; + homepage = "https://github.com/haskell/aeson"; description = "Fast JSON parsing and encoding"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "aeson-attoparsec" = callPackage - ({ mkDerivation, aeson, attoparsec, base, stdenv }: + ({ mkDerivation, aeson, attoparsec, base, lib }: mkDerivation { pname = "aeson-attoparsec"; version = "0.0.0"; @@ -1622,11 +1957,11 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/athanclark/aeson-attoparsec#readme"; description = "Embed an Attoparsec text parser into an Aeson parser"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "aeson-better-errors" = callPackage - ({ mkDerivation, aeson, base, bytestring, dlist, mtl, scientific - , stdenv, text, transformers, transformers-compat + ({ mkDerivation, aeson, base, bytestring, dlist, lib, mtl + , scientific, text, transformers, transformers-compat , unordered-containers, vector, void }: mkDerivation { @@ -1641,30 +1976,64 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/hdgarrood/aeson-better-errors"; description = "Better error messages when decoding JSON values"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "aeson-casing" = callPackage - ({ mkDerivation, aeson, base, stdenv }: + ({ mkDerivation, aeson, base, lib }: mkDerivation { pname = "aeson-casing"; - version = "0.1.0.5"; - sha256 = "cfec563dc6822f035858a7190153d8818c200be565806b43b70f198bf5410577"; + version = "0.2.0.0"; + sha256 = "3723075673a3f188a05e5db0cd2851c249ca16eba532c3e76e7f1fa60cf19233"; libraryHaskellDepends = [ aeson base ]; doHaddock = false; doCheck = false; description = "Tools to change the formatting of field names in Aeson instances"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "aeson-combinators" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers, fail, lib + , scientific, text, time, time-compat, unordered-containers + , uuid-types, vector, void + }: + mkDerivation { + pname = "aeson-combinators"; + version = "0.0.5.0"; + sha256 = "6ab8a3e4b5e5dee14ef17b343ea50f36f45921392f4d2edad85474e7ee5eaefc"; + libraryHaskellDepends = [ + aeson base bytestring containers fail scientific text time + time-compat unordered-containers uuid-types vector void + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/turboMaCk/aeson-combinators"; + description = "Aeson combinators for dead simple JSON decoding"; + license = lib.licenses.bsd3; + }) {}; + "aeson-commit" = callPackage + ({ mkDerivation, aeson, base, lib, mtl, text }: + mkDerivation { + pname = "aeson-commit"; + version = "1.3"; + sha256 = "5ba62ac3e564ec2ec08e48bf45f039eee080b630bbf7572768fd86a4cd2d28f0"; + libraryHaskellDepends = [ aeson base mtl text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/xc-jp/aeson-commit#readme"; + description = "Parse Aeson data with commitment"; + license = lib.licenses.bsd3; }) {}; "aeson-compat" = callPackage ({ mkDerivation, aeson, attoparsec, attoparsec-iso8601, base - , base-compat, bytestring, containers, exceptions, hashable - , scientific, stdenv, tagged, text, time, time-locale-compat + , base-compat, bytestring, containers, exceptions, hashable, lib + , scientific, tagged, text, time, time-locale-compat , unordered-containers, vector }: mkDerivation { pname = "aeson-compat"; version = "0.3.9"; sha256 = "e043941ba761c13a3854fc087521b864b56b2df874154e42aedb67b2a77f23c8"; + revision = "6"; + editedCabalFile = "18ni5j2zvn7qfdama9j1s84kz9ylsnjmi5ynbq68mpri5wimm448"; libraryHaskellDepends = [ aeson attoparsec attoparsec-iso8601 base base-compat bytestring containers exceptions hashable scientific tagged text time @@ -1674,19 +2043,30 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/phadej/aeson-compat#readme"; description = "Compatibility layer for aeson"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "aeson-default" = callPackage + ({ mkDerivation, aeson, base, containers, lib }: + mkDerivation { + pname = "aeson-default"; + version = "0.9.1.0"; + sha256 = "5e7eb4b6633d6f6a9871915c324528ec9032eaea229ae25fceb361a8aceab23a"; + libraryHaskellDepends = [ aeson base containers ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/versioncloud/aeson-default#readme"; + description = "Apply default value to FromJSON instacnes' Maybe fields"; + license = lib.licenses.bsd3; }) {}; "aeson-diff" = callPackage ({ mkDerivation, aeson, base, bytestring, edit-distance-vector - , hashable, mtl, optparse-applicative, scientific, stdenv, text + , hashable, lib, mtl, optparse-applicative, scientific, text , unordered-containers, vector }: mkDerivation { pname = "aeson-diff"; - version = "1.1.0.5"; - sha256 = "61d9dd60b6c19dd5aa350b85083ebed3eab8d8611893db1279e55e43d7c7fbcf"; - revision = "1"; - editedCabalFile = "0a29nph4a1ny365nhsxlm73mk6zgaam4sfx6knzqjy8dxp1gkj48"; + version = "1.1.0.9"; + sha256 = "22654e736744e34e729664614605cc0f9b0fa2dac013d69bc9f971293d2675a1"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -1700,35 +2080,10 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/thsutton/aeson-diff"; description = "Extract and apply patches to JSON documents"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "aeson-extra" = callPackage - ({ mkDerivation, aeson, aeson-compat, attoparsec - , attoparsec-iso8601, base, base-compat-batteries, bytestring - , containers, deepseq, exceptions, hashable, parsec - , recursion-schemes, scientific, stdenv, template-haskell, text - , these, time, unordered-containers, vector - }: - mkDerivation { - pname = "aeson-extra"; - version = "0.4.1.1"; - sha256 = "d48a65d976cbf496c8e5e9c927118ffcc878d6a83adf2fc9cebd418186d6fdf8"; - revision = "3"; - editedCabalFile = "0b9ccv529msmqay0gw2xcxm67n08hmv6s45ivyd8vq0rig4wz407"; - libraryHaskellDepends = [ - aeson aeson-compat attoparsec attoparsec-iso8601 base - base-compat-batteries bytestring containers deepseq exceptions - hashable parsec recursion-schemes scientific template-haskell text - these time unordered-containers vector - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/phadej/aeson-extra#readme"; - description = "Extra goodies for aeson"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "aeson-generic-compat" = callPackage - ({ mkDerivation, aeson, base, stdenv }: + ({ mkDerivation, aeson, base, lib }: mkDerivation { pname = "aeson-generic-compat"; version = "0.0.1.3"; @@ -1737,46 +2092,66 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doHaddock = false; doCheck = false; description = "Compatible generic class names of Aeson"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "aeson-iproute" = callPackage - ({ mkDerivation, aeson, base, iproute, stdenv, text - , unordered-containers + "aeson-lens" = callPackage + ({ mkDerivation, aeson, base, bytestring, lens, lib, text + , unordered-containers, vector }: mkDerivation { - pname = "aeson-iproute"; - version = "0.2"; - sha256 = "ee4d53338bfdc4a6ce0039dea24e797a0ff1e22c312b31be2e73ddc0bddf268f"; + pname = "aeson-lens"; + version = "0.5.0.0"; + sha256 = "7ace668031da8119439e21b6ccbe329d37c533be2f5c5612389107d2676728df"; + libraryHaskellDepends = [ + aeson base bytestring lens text unordered-containers vector + ]; + doHaddock = false; + doCheck = false; + description = "Lens of Aeson"; + license = lib.licenses.bsd3; + }) {}; + "aeson-optics" = callPackage + ({ mkDerivation, aeson, attoparsec, base, base-compat, bytestring + , lib, optics-core, optics-extra, scientific, text + , unordered-containers, vector + }: + mkDerivation { + pname = "aeson-optics"; + version = "1.1.0.1"; + sha256 = "c7555096900d1c9bb18b1a5c8697976e6dc8268a9ec1c6dbb9abf0431941d1dd"; + revision = "5"; + editedCabalFile = "102mdf74ka25qnw45282j7c4ds3v4mppa3g1mp1hr0hf0f2ya3bk"; libraryHaskellDepends = [ - aeson base iproute text unordered-containers + aeson attoparsec base base-compat bytestring optics-core + optics-extra scientific text unordered-containers vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/greydot/aeson-iproute"; - description = "Aeson instances for iproute types"; - license = stdenv.lib.licenses.bsd3; + homepage = "http://github.com/phadej/aeson-optics"; + description = "Law-abiding optics for aeson"; + license = lib.licenses.mit; }) {}; "aeson-picker" = callPackage - ({ mkDerivation, aeson, base, lens, lens-aeson, stdenv, text }: + ({ mkDerivation, aeson, base, lens, lens-aeson, lib, text }: mkDerivation { pname = "aeson-picker"; - version = "0.1.0.4"; - sha256 = "b20e23905c395d7b61fce6c5f6343758e3753a2dbee61800d3e15e753ac7c452"; + version = "0.1.0.5"; + sha256 = "97df83f6ef5f201e784c0a96c3bc3205c94d20b67f5ff4e3193acd8e9a339c16"; libraryHaskellDepends = [ aeson base lens lens-aeson text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/ozzzzz/aeson-picker#readme"; description = "Tiny library to get fields from JSON format"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "aeson-pretty" = callPackage ({ mkDerivation, aeson, attoparsec, base, base-compat, bytestring - , cmdargs, scientific, stdenv, text, unordered-containers, vector + , cmdargs, lib, scientific, text, unordered-containers, vector }: mkDerivation { pname = "aeson-pretty"; - version = "0.8.7"; - sha256 = "c1c1ecc5e3abd004a6c4c256ee6f61da2a43d7f1452ffa391dee250df43b27d5"; + version = "0.8.8"; + sha256 = "81cea61cb6dcf32c3f0529ea5cfc98dbea3894152d7f2d9fe1cb051f927ec726"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -1790,17 +2165,17 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "http://github.com/informatikr/aeson-pretty"; description = "JSON pretty-printing library and command-line tool"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "aeson-qq" = callPackage ({ mkDerivation, aeson, attoparsec, base, base-compat - , haskell-src-meta, parsec, scientific, stdenv, template-haskell - , text, vector + , haskell-src-meta, lib, parsec, scientific, template-haskell, text + , vector }: mkDerivation { pname = "aeson-qq"; - version = "0.8.2"; - sha256 = "6db252c94601efcb1ce395de0084ccf931a3525339ccdca011a740e7b11cc152"; + version = "0.8.3"; + sha256 = "8f3129cf88bf52214a9f74c0be584a3c3296d1541280ad900188e102fee7f482"; libraryHaskellDepends = [ aeson attoparsec base base-compat haskell-src-meta parsec scientific template-haskell text vector @@ -1809,46 +2184,64 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/sol/aeson-qq#readme"; description = "JSON quasiquoter for Haskell"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "aeson-schemas" = callPackage + ({ mkDerivation, aeson, base, first-class-families, hashable, lib + , megaparsec, template-haskell, text, unordered-containers + }: + mkDerivation { + pname = "aeson-schemas"; + version = "1.3.4"; + sha256 = "bd3c730e3dac094528fd601c88bda36ca3e624997189633f854459e6a596f720"; + libraryHaskellDepends = [ + aeson base first-class-families hashable megaparsec + template-haskell text unordered-containers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/LeapYear/aeson-schemas#readme"; + description = "Easily consume JSON data on-demand with type-safety"; + license = lib.licenses.bsd3; }) {}; "aeson-typescript" = callPackage - ({ mkDerivation, aeson, base, containers, interpolate, mtl, stdenv - , template-haskell, text, th-abstraction, unordered-containers + ({ mkDerivation, aeson, base, containers, lib, mtl + , string-interpolate, template-haskell, text, th-abstraction + , unordered-containers }: mkDerivation { pname = "aeson-typescript"; - version = "0.1.1.0"; - sha256 = "77a3b10384383f0188feef57015a896e89bac9882df4c83bed765f70b77aa46b"; + version = "0.3.0.1"; + sha256 = "fbb36d742e1e2fbe0876834a160beead0e7fe96d59d7f229c364df4e43357275"; libraryHaskellDepends = [ - aeson base containers interpolate mtl template-haskell text + aeson base containers mtl string-interpolate template-haskell text th-abstraction unordered-containers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/codedownio/aeson-typescript#readme"; description = "Generate TypeScript definition files from your ADTs"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "aeson-utils" = callPackage - ({ mkDerivation, aeson, attoparsec, base, bytestring, scientific - , stdenv, text + "aeson-with" = callPackage + ({ mkDerivation, aeson, base, lens, lens-aeson, lib, scientific + , text, unordered-containers, vector }: mkDerivation { - pname = "aeson-utils"; - version = "0.3.0.2"; - sha256 = "71814b1be8849f945395eb81217a2ad464f2943134c50c09afd8a3126add4b1f"; - revision = "7"; - editedCabalFile = "0lnlmsn5imbapdhbza1175wm04ynn1w75llkhlk1akpanx1dnd15"; + pname = "aeson-with"; + version = "0.1.2.0"; + sha256 = "e8bb59b650f0d19e136d2af0b6eb1b594d6bbbbc5fbb3f2a9a261a81b594487e"; libraryHaskellDepends = [ - aeson attoparsec base bytestring scientific text + aeson base lens lens-aeson scientific text unordered-containers + vector ]; doHaddock = false; doCheck = false; - description = "Utilities for working with Aeson"; - license = stdenv.lib.licenses.bsd3; + description = "withXField combinators for aeson"; + license = lib.licenses.mit; }) {}; "aeson-yak" = callPackage - ({ mkDerivation, aeson, base, stdenv }: + ({ mkDerivation, aeson, base, lib }: mkDerivation { pname = "aeson-yak"; version = "0.1.1.3"; @@ -1858,10 +2251,50 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/tejon/aeson-yak"; description = "Handle JSON that may or may not be a list, or exist"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "aeson-yaml" = callPackage + ({ mkDerivation, aeson, base, bytestring, lib, text + , unordered-containers, vector + }: + mkDerivation { + pname = "aeson-yaml"; + version = "1.1.0.0"; + sha256 = "deece91c2c0ad1d9782a2e70c976f8184f21e2cf339375e7a9fc5f3cb880d9cf"; + revision = "1"; + editedCabalFile = "167gfgmy1pq50rh3rszj01ch4qy3jl4lpl3g8yq300kffrfs882a"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson base bytestring text unordered-containers vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/clovyr/aeson-yaml"; + description = "Output any Aeson value as YAML (pure Haskell library)"; + license = lib.licenses.bsd3; + }) {}; + "agda2lagda" = callPackage + ({ mkDerivation, base, directory, filepath, lib + , optparse-applicative + }: + mkDerivation { + pname = "agda2lagda"; + version = "0.2021.6.1"; + sha256 = "3a2e58c2bee6b0f7f2f2ffd5198836a05dbf8c608b87a7d5c5066d47e8ef0884"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ + base directory filepath optparse-applicative + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/andreasabel/agda2lagda"; + description = "Translate .agda files into .lagda.tex files."; + license = lib.licenses.publicDomain; }) {}; "al" = callPackage - ({ mkDerivation, base, c2hs, mtl, openal, stdenv }: + ({ mkDerivation, base, c2hs, lib, mtl, openal }: mkDerivation { pname = "al"; version = "0.1.4.2"; @@ -1873,45 +2306,44 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "http://github.com/phaazon/al"; description = "OpenAL 1.1 raw API."; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) openal;}; "alarmclock" = callPackage - ({ mkDerivation, async, base, clock, stdenv, stm, time + ({ mkDerivation, async, base, clock, lib, stm, time , unbounded-delays }: mkDerivation { pname = "alarmclock"; - version = "0.6.0.2"; - sha256 = "4cabd649d1fdc17e3ab1658db9491f147bfcefd16ccbfa253b9b946eba1e18fe"; + version = "0.7.0.5"; + sha256 = "494ef7c8cc1f29a3bb09b853d383cad58bd8e9ed75c15282adc566c234bc2705"; libraryHaskellDepends = [ async base clock stm time unbounded-delays ]; doHaddock = false; doCheck = false; - homepage = "https://bitbucket.org/davecturner/alarmclock"; + homepage = "https://github.com/DaveCTurner/alarmclock"; description = "Wake up and perform an action at a certain time"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "alerts" = callPackage - ({ mkDerivation, base, blaze-html, stdenv, text }: + ({ mkDerivation, base, blaze-html, lib, text }: mkDerivation { pname = "alerts"; - version = "0.1.0.0"; - sha256 = "52418ed3abfff15e802506e5fb45f56d38eee020cb01af3f0acfe163c470ca68"; + version = "0.1.2.0"; + sha256 = "8e9c684b1236c5a730f50b48aa38de2b835fbb48d5bc27be41e742cedb64de91"; libraryHaskellDepends = [ base blaze-html text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/alx741/alerts#readme"; description = "Alert messages for web applications"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "alex" = callPackage - ({ mkDerivation, array, base, containers, directory, happy, stdenv - }: + ({ mkDerivation, array, base, containers, directory, happy, lib }: mkDerivation { pname = "alex"; - version = "3.2.4"; - sha256 = "d58e4d708b14ff332a8a8edad4fa8989cb6a9f518a7c6834e96281ac5f8ff232"; + version = "3.2.6"; + sha256 = "91aa08c1d3312125fbf4284815189299bbb0be34421ab963b1f2ae06eccc5410"; isLibrary = false; isExecutable = true; enableSeparateDataOutput = true; @@ -1921,39 +2353,58 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "http://www.haskell.org/alex/"; description = "Alex is a tool for generating lexical analysers in Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "alex-meta" = callPackage + ({ mkDerivation, alex, array, base, containers, happy + , haskell-src-meta, lib, QuickCheck, template-haskell + }: + mkDerivation { + pname = "alex-meta"; + version = "0.3.0.13"; + sha256 = "7be084d4ec462d2335016368452e47f7a0a964861962528bb8e38c1619557951"; + libraryHaskellDepends = [ + array base containers haskell-src-meta QuickCheck template-haskell + ]; + libraryToolDepends = [ alex happy ]; + doHaddock = false; + doCheck = false; + description = "Quasi-quoter for Alex lexers"; + license = lib.licenses.bsd3; }) {}; "alg" = callPackage - ({ mkDerivation, base, stdenv, util }: + ({ mkDerivation, base, dual, lib, util }: mkDerivation { pname = "alg"; - version = "0.2.9.0"; - sha256 = "98724f959ada2387e94cc17a7bdc39eb868d8ef291daa12b82535b517eedb470"; - libraryHaskellDepends = [ base util ]; + version = "0.2.13.1"; + sha256 = "83929d69abda54ba724c5221071b8629ed60605edb8ec9a66ed8a025ad90c41c"; + revision = "1"; + editedCabalFile = "0rm66k502d8la140ffawd38yaf0hr92h8x7xrq6krn6ypljwql0v"; + libraryHaskellDepends = [ base dual util ]; doHaddock = false; doCheck = false; description = "Algebraic structures"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "algebraic-graphs" = callPackage - ({ mkDerivation, array, base, base-compat, containers, deepseq, mtl - , stdenv + ({ mkDerivation, array, base, containers, deepseq, lib, mtl + , transformers }: mkDerivation { pname = "algebraic-graphs"; - version = "0.3"; - sha256 = "1492ace011d13757155ae2aca18737095cee9d5b94e810bac0a7ca3e9ea79de0"; + version = "0.5"; + sha256 = "89b9fecf8245476ec823355125fcb95decf41fd9784e807d7bd0d09f0a79c50b"; libraryHaskellDepends = [ - array base base-compat containers deepseq mtl + array base containers deepseq mtl transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/snowleopard/alga"; description = "A library for algebraic graph construction and transformation"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "almost-fix" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "almost-fix"; version = "0.0.2"; @@ -1962,10 +2413,10 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doHaddock = false; doCheck = false; description = "Recurse while a predicate is satisfied"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "alsa-core" = callPackage - ({ mkDerivation, alsaLib, base, extensible-exceptions, stdenv }: + ({ mkDerivation, alsaLib, base, extensible-exceptions, lib }: mkDerivation { pname = "alsa-core"; version = "0.5.0.1"; @@ -1976,11 +2427,13 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/ALSA"; description = "Binding to the ALSA Library API (Exceptions)"; - license = stdenv.lib.licenses.bsd3; - platforms = [ "i686-linux" "x86_64-linux" ]; + license = lib.licenses.bsd3; + platforms = [ + "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" + ]; }) {inherit (pkgs) alsaLib;}; "alsa-mixer" = callPackage - ({ mkDerivation, alsa-core, alsaLib, base, c2hs, stdenv, unix }: + ({ mkDerivation, alsa-core, alsaLib, base, c2hs, lib, unix }: mkDerivation { pname = "alsa-mixer"; version = "0.3.0"; @@ -1992,11 +2445,11 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/ttuegel/alsa-mixer"; description = "Bindings to the ALSA simple mixer API"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) alsaLib;}; "alsa-pcm" = callPackage ({ mkDerivation, alsa-core, alsaLib, array, base - , extensible-exceptions, sample-frame, semigroups, stdenv + , extensible-exceptions, lib, sample-frame, semigroups , storable-record }: mkDerivation { @@ -2014,17 +2467,17 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/ALSA"; description = "Binding to the ALSA Library API (PCM audio)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) alsaLib;}; "alsa-seq" = callPackage ({ mkDerivation, alsa-core, alsaLib, array, base, bytestring - , data-accessor, enumset, extensible-exceptions, poll, stdenv + , data-accessor, enumset, extensible-exceptions, lib, poll , transformers, utility-ht }: mkDerivation { pname = "alsa-seq"; - version = "0.6.0.7"; - sha256 = "06cda1e24993aaf0c3592b51a613cf1e187eea603dd77ad3a129a8a7b1e0b778"; + version = "0.6.0.8"; + sha256 = "5bd2ff2f3817fcfdb0a131f46e6c1efddda88b5860ab56e372d11244c641c701"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -2036,10 +2489,10 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/ALSA"; description = "Binding to the ALSA Library API (MIDI sequencer)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) alsaLib;}; "alternative-vector" = callPackage - ({ mkDerivation, base, stdenv, vector }: + ({ mkDerivation, base, lib, vector }: mkDerivation { pname = "alternative-vector"; version = "0.0.0"; @@ -2049,372 +2502,334 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/athanclark/alternative-vector#readme"; description = "Use vectors instead of lists for many and some"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "alternators" = callPackage - ({ mkDerivation, base, lens, mmorph, mtl, newtype-generics, stdenv - , stm, transformers - }: - mkDerivation { - pname = "alternators"; - version = "1.0.0.0"; - sha256 = "44395b8b42193fdd78f94fd9f62560bfa69aef345a0fb2602df0d8d3613fd339"; - libraryHaskellDepends = [ - base lens mmorph mtl newtype-generics stm transformers - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/louispan/alternators#readme"; - description = "Handy functions when using transformers"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "amazonka" = callPackage - ({ mkDerivation, amazonka-core, base, bytestring, conduit - , conduit-extra, directory, exceptions, http-client, http-conduit - , http-types, ini, mmorph, monad-control, mtl, resourcet, retry - , stdenv, text, time, transformers, transformers-base - , transformers-compat, void - }: - mkDerivation { - pname = "amazonka"; - version = "1.6.0"; - sha256 = "3721892c87946c12bbd87ddba38d9e244aa962db190d8897c16a264c4f3fc41c"; - libraryHaskellDepends = [ - amazonka-core base bytestring conduit conduit-extra directory - exceptions http-client http-conduit http-types ini mmorph - monad-control mtl resourcet retry text time transformers - transformers-base transformers-compat void - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/brendanhay/amazonka"; - description = "Comprehensive Amazon Web Services SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.bsd3; }) {}; "amazonka-apigateway" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-apigateway"; - version = "1.6.0"; - sha256 = "56e63ecfbd8358d0d2766e08f8f2b08362bb435c1059a5791964089dbab75ae8"; + version = "1.6.1"; + sha256 = "3b843dd490d09c45aac415269bf3d7db894fad8104cdd76292058adb03adf385"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon API Gateway SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-application-autoscaling" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-application-autoscaling"; - version = "1.6.0"; - sha256 = "5536a7d1c24cd5907b85bd743df5989d91cb3325602944062c9c640178a61df7"; + version = "1.6.1"; + sha256 = "da0eaaa282cc04c6aa486dfe00cdb5f42afc77e6785493ffdaa2ff7c9a8ad286"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Application Auto Scaling SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-appstream" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-appstream"; - version = "1.6.0"; - sha256 = "eb90692b932d62c4e7006d661b8022c4dd9f7d4dcc07e5499eceae14b33747df"; + version = "1.6.1"; + sha256 = "6644fac750a0a415439df14567597de57bbe75cfe259feb42265af58867c088c"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon AppStream SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-athena" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-athena"; - version = "1.6.0"; - sha256 = "99d4eeb81656e876d5d65d0bfeacf9db5871215bd3bee99949979bbc2ccd77db"; + version = "1.6.1"; + sha256 = "370ee46f0d9b7f09b911b25d97457d727510fa049b42921f5f6e4a730fe15b9d"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Athena SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-autoscaling" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-autoscaling"; - version = "1.6.0"; - sha256 = "1b52132b23ef899937d20cef595d9f8757f85861d142616bcb5ee0ba8ed5f8d3"; + version = "1.6.1"; + sha256 = "2fb4adc14d35ce6a24b1c294bbf3974317ff8b315fc10dc8f9609399a8acc914"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Auto Scaling SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-budgets" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-budgets"; - version = "1.6.0"; - sha256 = "ccc692856a7f7ddfba573cde6506108a30a59f641748ecc787aece894d7ce4b7"; + version = "1.6.1"; + sha256 = "84ab20850439ba786153a6e0c27bc8a321ef1c79524a8bf2d89adb56442d6273"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Budgets SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-certificatemanager" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-certificatemanager"; - version = "1.6.0"; - sha256 = "1fdf93c685a1b348a851b793b170a0a2282b06dc65a91c016d4756ea5726aa6a"; + version = "1.6.1"; + sha256 = "833d7b67e7bae4c8633d34109998675edbc95478ac0eb86ec1cf866079689ef2"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Certificate Manager SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-cloudformation" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-cloudformation"; - version = "1.6.0"; - sha256 = "15e2c82574906a13d390f68f5a57a83f4bbfc37fb9ce590c9f73e00dcafa8335"; + version = "1.6.1"; + sha256 = "e823eab5456b0b6f86f9cd391cf2572998e30ecbed9ce373cd8e3ac6f5d3afc8"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon CloudFormation SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-cloudfront" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-cloudfront"; - version = "1.6.0"; - sha256 = "956a60988ff3b9bef042bf523b63c882cd7b2c386483cc3f1d1d8534aad334a2"; + version = "1.6.1"; + sha256 = "8c5900fb0d34878ecfe9470bcd897259e2575dbf7e13fc526a515a0e52dfa779"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon CloudFront SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-cloudhsm" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-cloudhsm"; - version = "1.6.0"; - sha256 = "e4227038a39486e8c390198997571ca1b14ebf5e15fec1146169da7378a41b5f"; + version = "1.6.1"; + sha256 = "34dfe223cf33e207be71c6c0f092e892b549f5332eb392a0c474493be0e0a019"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon CloudHSM SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-cloudsearch" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-cloudsearch"; - version = "1.6.0"; - sha256 = "dd17345576acd8f44fd3af82f07b00fdce0781abbd51ab2df827fa48528c6394"; + version = "1.6.1"; + sha256 = "d04812c26d5c19b5ad00f343e2607e18a91f12743508903ee76f12999bcd7adc"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon CloudSearch SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-cloudsearch-domains" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-cloudsearch-domains"; - version = "1.6.0"; - sha256 = "24f0d36f9aeed5041fd893b8a0d60e5df6f31c8a126cead4652115c6b28f7ca7"; + version = "1.6.1"; + sha256 = "041b6c655878f0ae85803cc4ef338bf1c4eab48ec327c46ffadb78b5c886b11f"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon CloudSearch Domain SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-cloudtrail" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-cloudtrail"; - version = "1.6.0"; - sha256 = "d9d99df96ac2e46321e0da7d1797f12472ee32011f126d2881a2f19aa7491c24"; + version = "1.6.1"; + sha256 = "55cc7c15a2e26824621ddb7e8086605bac315f994ac4cefb56b6b9726e0f7da9"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon CloudTrail SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-cloudwatch" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-cloudwatch"; - version = "1.6.0"; - sha256 = "25c812b364b22d96d082e3598cd75d988cb8e3decdb8e3291a0deb9714dbee51"; + version = "1.6.1"; + sha256 = "4e56b617c7b14f0074812562c52f05059c83921800cf737e231e3a8a4149326d"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon CloudWatch SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-cloudwatch-events" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-cloudwatch-events"; - version = "1.6.0"; - sha256 = "13fb5e436fc4c534d6e01c47ef23f589c01042f8a9d7efb622e89bd8f5d2ec4d"; + version = "1.6.1"; + sha256 = "8b323d428e163bebb83bbcc3790666356c53bde5c418c84ac48898ebcc3f7646"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon CloudWatch Events SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-cloudwatch-logs" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-cloudwatch-logs"; - version = "1.6.0"; - sha256 = "80e4e74af0fb29f5ecc04f4d956ba0e9950f7936c858c1ff84461b62ca87ee7d"; + version = "1.6.1"; + sha256 = "61dfdebb7c99d7d2875cd5ddba10000923c14a0d8a22e233ed3bbe617aa4d490"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon CloudWatch Logs SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-codebuild" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-codebuild"; - version = "1.6.0"; - sha256 = "fdbf43578e0aa54c616b2daf8b442b32a8765b62da0c3b7f6b1df95f4e55a0ab"; + version = "1.6.1"; + sha256 = "1375ef0b6b261e6762a3c35837055af3f0066f1da00c62f00fb28def8d39a6b0"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon CodeBuild SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-codecommit" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-codecommit"; - version = "1.6.0"; - sha256 = "8a2f2630bfabd3c71fdb811a9bbafefb058ce085ad18c1756a82f59bdd682415"; + version = "1.6.1"; + sha256 = "b639a3106095c6dc5d3885a75e20bd9ae4c270ae70b3fb342a40d191da1d0733"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon CodeCommit SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-codedeploy" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-codedeploy"; - version = "1.6.0"; - sha256 = "3315b99ab8851acb5ae1251344474e0ec03796e9fd59f1d18278abc7add3c2df"; + version = "1.6.1"; + sha256 = "3dff6fd082f1dc5c0f5992229499432e97b1a958a810a98330e25cf7175b54fa"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon CodeDeploy SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-codepipeline" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-codepipeline"; - version = "1.6.0"; - sha256 = "c46eea221931601ced439454d3a3fe0030acccbb776bf153182010ca8f2ec043"; + version = "1.6.1"; + sha256 = "bfa0ffffdf925b5e8693c10d4d73c1fbe310cb8f51a20d155ed08761cb3965c9"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon CodePipeline SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-cognito-identity" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-cognito-identity"; - version = "1.6.0"; - sha256 = "3aac30e210d3fc0f45166b6211c4c61eb7cc4480fb550f106cd6206c8dc9b6d5"; + version = "1.6.1"; + sha256 = "b97778558ce4ba5b8703d5549cd0ffa0b899812e2dd044d7515435070f9e8204"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Cognito Identity SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-cognito-idp" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-cognito-idp"; - version = "1.6.0"; - sha256 = "a98989c8ca10bb938fb4f27803920462fc8f88d7104cebb5106b9e3728e81fff"; + version = "1.6.1"; + sha256 = "df62c34ef4269974d71cc8a1ed6a8160dd739a4dd7ef5e18a5c061a9f2e8f01b"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Cognito Identity Provider SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-cognito-sync" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-cognito-sync"; - version = "1.6.0"; - sha256 = "5fde10d8e1f31e676433dfd32d061739d805a076ee58abd9c05d8faba36cf435"; + version = "1.6.1"; + sha256 = "e048f9d072b5655f8da36d47c40c45f2d77d85a0a0e4ae0adf14b0e30590db63"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Cognito Sync SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-config" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-config"; - version = "1.6.0"; - sha256 = "5cb03ebc049efbccfb48ab926e08f0e9824880bb349129601f724679fe42c9cd"; + version = "1.6.1"; + sha256 = "ff36ba897040319981edf9736115ca541e000eb37fe6fd408f07f32792f06834"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Config SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-core" = callPackage ({ mkDerivation, aeson, attoparsec, base, bifunctors, bytestring , case-insensitive, conduit, conduit-extra, cryptonite, deepseq , exceptions, hashable, http-client, http-conduit, http-types, lens - , memory, mtl, resourcet, scientific, semigroups, stdenv, tagged - , text, time, transformers, transformers-compat - , unordered-containers, xml-conduit, xml-types + , lib, memory, mtl, resourcet, scientific, semigroups, tagged, text + , time, transformers, transformers-compat, unordered-containers + , xml-conduit, xml-types }: mkDerivation { pname = "amazonka-core"; - version = "1.6.0"; - sha256 = "afe1c5b74aadc0222419bd792688fd179e4f5693aeb75b74232f770fff093dc9"; + version = "1.6.1"; + sha256 = "4198f52da9d20338bd6a3a18748d4312d3ff2c06bc84503cb18406251b28a243"; + revision = "1"; + editedCabalFile = "1656dyw6fk3gvph6v3xzvdp3p8xny3ji0gxg7qxvmvn60gj9ricv"; libraryHaskellDepends = [ aeson attoparsec base bifunctors bytestring case-insensitive conduit conduit-extra cryptonite deepseq exceptions hashable @@ -2426,799 +2841,799 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Core data types and functionality for Amazonka libraries"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-datapipeline" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-datapipeline"; - version = "1.6.0"; - sha256 = "1b212dd70864ef1ccc45e3a7deca936e0e1803c97aacefc34fad966fd85f3ae5"; + version = "1.6.1"; + sha256 = "6bf752844ec49c59be856bb082b600959ec187cc890f1bb7f7d9641e9b78b122"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Data Pipeline SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-devicefarm" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-devicefarm"; - version = "1.6.0"; - sha256 = "d81b74b8b0c254a487ce464b1d6f0679d774bd42daf32312867e4dd37e35c569"; + version = "1.6.1"; + sha256 = "bed85bba8a891f7c626e0b1e41cb4912974c250a6534e5438a3f51e5379a83ec"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Device Farm SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-directconnect" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-directconnect"; - version = "1.6.0"; - sha256 = "8d85b9ce865eac817610a3a1db2e28100ff0069b85f41c4359a6aa5978533832"; + version = "1.6.1"; + sha256 = "dc61998ad1145118be5138df37bd97cb1a61298e8fbc506ef1a22a33bafa045b"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Direct Connect SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-discovery" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-discovery"; - version = "1.6.0"; - sha256 = "7bc67ad76b1413c2aebe48324d56b2e6f4279db6e7d4951e93bdaa5329199213"; + version = "1.6.1"; + sha256 = "02abc932bf71df3ee03f5503d08414e3c01c49f08b4720e14e1a1e8fa13f449d"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Application Discovery Service SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-dms" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-dms"; - version = "1.6.0"; - sha256 = "a75f19dc2a7642840a97a135f24cd9120d3f5a81ad924aad6a46c514fba180f3"; + version = "1.6.1"; + sha256 = "8c79f617ccd7035f709ae8057a8e1a6c5a89cdab3aa9c3aabaee7c0628e3ed87"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Database Migration Service SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-ds" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-ds"; - version = "1.6.0"; - sha256 = "06fa338938aee62f81f93755cdc7039515dc0c6b32bb7c0bac33d7c92066d389"; + version = "1.6.1"; + sha256 = "fb4807974a865556eafc99b7c030244cf7da0b5b1ade9365fcb8689a48d6c8ff"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Directory Service SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-dynamodb" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-dynamodb"; - version = "1.6.0"; - sha256 = "33f54ee4f898972f1539a00e65a851bb940c8d26058d63ddfcd07fbca57f9a3f"; + version = "1.6.1"; + sha256 = "0420486c88f10636a4407c8732b927498c5a809b235e2da56750d012f05c1d82"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon DynamoDB SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-dynamodb-streams" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-dynamodb-streams"; - version = "1.6.0"; - sha256 = "b3f832ddf70e95232cb79d71633276aa65c72e51c6c553118b4bc9db3a48e57f"; + version = "1.6.1"; + sha256 = "fe2dab6892599dac4ec9f4408283019d670f6ba0a24723914aabe718b14ed959"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon DynamoDB Streams SDK"; - license = stdenv.lib.licenses.mpl20; - }) {}; - "amazonka-ec2" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: - mkDerivation { - pname = "amazonka-ec2"; - version = "1.6.0"; - sha256 = "2221c2c4e188aac9f0c9e4bb2e0bce65eb21102e6199c3783c20f3797da955cc"; - libraryHaskellDepends = [ amazonka-core base ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/brendanhay/amazonka"; - description = "Amazon Elastic Compute Cloud SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-ecr" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-ecr"; - version = "1.6.0"; - sha256 = "42088ad4b4d4c01b87267a372fec706f57db4db19b27c06a3c6826ef62ef8450"; + version = "1.6.1"; + sha256 = "2d0d5dd640f63e11b6009d3b486505e93afd379c5f5738df79582b5eeb6c7358"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon EC2 Container Registry SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-ecs" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-ecs"; - version = "1.6.0"; - sha256 = "309535abe8359475b3430488c84c398ed8d25a05321101c725e4a04d5f4cde3f"; + version = "1.6.1"; + sha256 = "55071129ab02b9bf3feb5b5ca04feb64ea8709a125b67a35fda15b25cc1a1bba"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon EC2 Container Service SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-efs" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-efs"; - version = "1.6.0"; - sha256 = "268456294406d63eb49422027226af8ef15ce08dc2095be9a6657bf9bf41afbb"; + version = "1.6.1"; + sha256 = "741e047eb04c3bbd8dcbb03579bc82e4546abd0ae9a835ae128e2b3843d6b18c"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Elastic File System SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-elasticache" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-elasticache"; - version = "1.6.0"; - sha256 = "e4a74a2ce2d89534fd738c429dc9a0ee7564ee3539bd93488eba211176763969"; + version = "1.6.1"; + sha256 = "4d2d8ae02e7c43eb77ba3a52863a4a2be305fb7f219a568709e830d647feeb60"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon ElastiCache SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-elasticbeanstalk" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-elasticbeanstalk"; - version = "1.6.0"; - sha256 = "c1dc065763475b705aabf61086546bcd312e6802dbb328775b9777e682b2386a"; + version = "1.6.1"; + sha256 = "2ad4f9e80217d544f5fdd837eb2749d54f3ca3b210dcbada70fec1c920879f69"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Elastic Beanstalk SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-elasticsearch" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-elasticsearch"; - version = "1.6.0"; - sha256 = "3429fcae1c6fec5ebbc8acf1597532615b39def394d2296d641614c0225f3083"; + version = "1.6.1"; + sha256 = "9ef91d5db4b13a0164a83674763ce25cb104ba92afd6f8ee5c70aa379006ca13"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Elasticsearch Service SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-elastictranscoder" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-elastictranscoder"; - version = "1.6.0"; - sha256 = "ab12a7c97e09cd1a60e81525e793f5f7b84799f8f9968a2b62bae8b9c9f3c10a"; + version = "1.6.1"; + sha256 = "df80e7de3db78431eddb2d5413ac5e2271ec282c50ee1a23076aca90d697fb5b"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Elastic Transcoder SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-elb" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-elb"; - version = "1.6.0"; - sha256 = "59c974009a2c26f7d267ae9736c71893a82ae69c19f344b87b4e3afd19f97e4d"; + version = "1.6.1"; + sha256 = "5b5eecb81db898daa55ac1628bf65ac124d44e616dca5b33356ced32e6ba109d"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Elastic Load Balancing SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-elbv2" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-elbv2"; - version = "1.6.0"; - sha256 = "2a53d35e29b613ac7261a3202023cb8221607fd8df5f034c572d6aa751c622c9"; + version = "1.6.1"; + sha256 = "6740907fe448cbee8512b91b570204d56018e520239fc9f1689601eb382f7b79"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Elastic Load Balancing SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-emr" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-emr"; - version = "1.6.0"; - sha256 = "e9a07458ee61feadeff2e98fc83c1542320d5b97744225304dc1cc568ad9774f"; + version = "1.6.1"; + sha256 = "4b93c73647239e0bb1f779c876e933126fae48d51777b15ae4c4750dec2d87bc"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Elastic MapReduce SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-gamelift" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-gamelift"; - version = "1.6.0"; - sha256 = "ebcdbd4a43c8d02dc0a0d7302f4b27c8e106a783e910c5cdaa68a7a7ee775ffc"; + version = "1.6.1"; + sha256 = "c9c85550858c9eac54e86b226d31270de09cc8d71099a075829cc512fbe0e3b2"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon GameLift SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-glacier" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-glacier"; - version = "1.6.0"; - sha256 = "5307434d1fbddfba54b56ceb5eea2e5dfa3ece05b9353e61a998788af3e0f913"; + version = "1.6.1"; + sha256 = "5b55cf733d0f987c1b3b61fb3fd0e29cdcfdc2bb7c9fcc0fa3c959d4bd540887"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Glacier SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; + }) {}; + "amazonka-glue" = callPackage + ({ mkDerivation, amazonka-core, base, lib }: + mkDerivation { + pname = "amazonka-glue"; + version = "1.6.1"; + sha256 = "6b2a30379b9727522512a8f259a1e6bd1d22b34ed52669d5558777a81e5be89f"; + libraryHaskellDepends = [ amazonka-core base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/brendanhay/amazonka"; + description = "Amazon Glue SDK"; + license = lib.licenses.mpl20; }) {}; "amazonka-health" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-health"; - version = "1.6.0"; - sha256 = "c216b18e93e998ff04b00a5fc3ab6df8d36ef95d4b9988587eceb837615ba67b"; + version = "1.6.1"; + sha256 = "a2b533d5ac019b7dce0a8cc07f2515b577cabbd3caa613372018a37fa8764677"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Health APIs and Notifications SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-iam" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-iam"; - version = "1.6.0"; - sha256 = "a335813a795c3d28400b95b94f1b14ada3e621e83d07cb9fd9c7e7edb285905d"; + version = "1.6.1"; + sha256 = "1d5106a4af75fae4444a3353b2568d4e1f751e81c7e9e263d26cd81466c3e7d7"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Identity and Access Management SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-importexport" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-importexport"; - version = "1.6.0"; - sha256 = "0951f2bcd74e24c687ab39a044cfc9334b68fdb3c885d54693c918a1c97dcd04"; + version = "1.6.1"; + sha256 = "ce142494cc9d5a063ee93224e488380d3730ab507b57ebc53b215dafb0d6dd8e"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Import/Export SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-inspector" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-inspector"; - version = "1.6.0"; - sha256 = "bcef005e38e63b742c1d7c63de84f582a447042a19ea611b1b617751f3cce13e"; + version = "1.6.1"; + sha256 = "68b4b3c335ce13754d08726a203fc01a5731f8b9147948b8848a986505efb674"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Inspector SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-iot" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-iot"; - version = "1.6.0"; - sha256 = "180b2169c97bd021e5f013cc72b64fe701270a7a5000950e20fa6373d38a26d0"; + version = "1.6.1"; + sha256 = "51763922dbb965d5c01ec60f1090eed03bec959a77e451cef70c55a42a2dc683"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon IoT SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-iot-dataplane" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-iot-dataplane"; - version = "1.6.0"; - sha256 = "aee63bc0e6eca4cc4f76f7c8aa5e20f97e3f98268160006099014c66f4a88742"; + version = "1.6.1"; + sha256 = "7b43f97fe9eb1d81c7ec9ea865fb49c4cd364fa532d4c50d8676306bb8c20b48"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon IoT Data Plane SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-kinesis" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-kinesis"; - version = "1.6.0"; - sha256 = "549e41d29e46ff6aa485676436cb7cf15d2d37c2d0c62e6358b9b12b92e22f38"; + version = "1.6.1"; + sha256 = "5fe3dcf3fbf9aded3e27eb430be32400ebb84a01c0aec237e330a9480cbb5167"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Kinesis SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-kinesis-analytics" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-kinesis-analytics"; - version = "1.6.0"; - sha256 = "7efb5438596ef4541ebca35e4b87adf3c989bf88032be2d2e617bb14a7f685ee"; + version = "1.6.1"; + sha256 = "af589c9afa3f253efefb95b356a5f2a7a280d6abbf5314f182f0beecb1066e99"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Kinesis Analytics SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-kinesis-firehose" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-kinesis-firehose"; - version = "1.6.0"; - sha256 = "120545cdc888c031290b2f8a6745b911ebc6e2e5c077005067683118d197549c"; + version = "1.6.1"; + sha256 = "e4a10bfe3f334c9ec27b86096b671b363357c8b417268444b7600dfdcd68872d"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Kinesis Firehose SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-kms" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-kms"; - version = "1.6.0"; - sha256 = "7aa5333583b494d0a5585f78ead67833a7e72942b264673ee8b91d7be89e8e99"; + version = "1.6.1"; + sha256 = "6d333ec392d1f47c850449e78a1071f2265b46f699f3c58ad9e30bd99c956285"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Key Management Service SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-lambda" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-lambda"; - version = "1.6.0"; - sha256 = "649626896a7572979c5628e9406eb9be090106b7468473455e77aa59cec99b06"; + version = "1.6.1"; + sha256 = "972b5ff15cad609f44761d485563496ca3584884e1fa367193ddaf76260fcca3"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Lambda SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-lightsail" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-lightsail"; - version = "1.6.0"; - sha256 = "741b4c6aff2f0e08fe9868aa858708a8ab36f95859bc0a9eecfdd9bd2060aceb"; + version = "1.6.1"; + sha256 = "7c678ea0f8aa5beee2e0473ac5055a17aeb50c148362739adc84c940beb3931e"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Lightsail SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-marketplace-analytics" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-marketplace-analytics"; - version = "1.6.0"; - sha256 = "4d6c0db0e9c17b5131c6b03cd27bc53fbddb144c3910d46639edfdccbecd5d6a"; + version = "1.6.1"; + sha256 = "6ff582afb73e30d97d1f74e815ae03cdf919c4be4581b23691346a6d48a2137d"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Marketplace Commerce Analytics SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-marketplace-metering" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-marketplace-metering"; - version = "1.6.0"; - sha256 = "672de14acac579673c8c3cf032c3806554355cc84ae1b61882a589af2afb5f77"; + version = "1.6.1"; + sha256 = "928bdbe8fbd3b81429ff4936590f3e04fd3632737fb39048afdc6be8ade85037"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Marketplace Metering SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-ml" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-ml"; - version = "1.6.0"; - sha256 = "9dc12d7b71a72ea720efe9de60668ab904adddfdfbe9c422f5ebda940a556dfe"; + version = "1.6.1"; + sha256 = "b8c7c0b8663ffe570c79a1abc3d387b02e69b61b3f0d39b9ffa39e3049a7b872"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Machine Learning SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-opsworks" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-opsworks"; - version = "1.6.0"; - sha256 = "9a4372339b8ec556331b0198b5faf74bd8116f0816176aa8626d31f3b372d918"; + version = "1.6.1"; + sha256 = "0a1716f0d6e5edaad37d86f2f3c0be043a0b0086d1f7a2f06cdd539f717faa96"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon OpsWorks SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-opsworks-cm" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-opsworks-cm"; - version = "1.6.0"; - sha256 = "4f9e9b755f70fffd15cea08d0dfef5dc23ee4f822471f8e89f4d9b2f77a748f4"; + version = "1.6.1"; + sha256 = "51857803a2f0bee215c92119c3c5899df01e9195c2dc133e3f9774d4b93eca57"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon OpsWorks for Chef Automate SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-pinpoint" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-pinpoint"; - version = "1.6.0"; - sha256 = "b0f8cdaabd9f357d5a687999ce83c7670f43023507ab9b25e94bc717f916b005"; + version = "1.6.1"; + sha256 = "aa38c2d154b7ad3c16f0760c5304fd7d9875b1e8c7d48bb32b87a5616717fc87"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Pinpoint SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-polly" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-polly"; - version = "1.6.0"; - sha256 = "773edcfa2628cb9e616b9f1f5fab461cd6f0e5822dafa43fef4403c54e958ad0"; + version = "1.6.1"; + sha256 = "b0887545cce2a01b16733b1d329570b4c79e6cfd6412813ec5c9c6c0a79fccef"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Polly SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-rds" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-rds"; - version = "1.6.0"; - sha256 = "c793613c53773b3ba8c5db1fa342e68c25fcada39f8557c6ed39feb05f1bc24d"; + version = "1.6.1"; + sha256 = "fcd2400a359093bd075ccfc76e16c42c3f3bdc65828bf4cb24c9e5cfdc389421"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Relational Database Service SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-redshift" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-redshift"; - version = "1.6.0"; - sha256 = "426ab96936e8d42ed85b31f076d99304148a6eb0896edbe90c6b1e570a90b329"; + version = "1.6.1"; + sha256 = "87ea855e565636cc06396172e108df6aeca1e5fac1efc194d7bd98fc56402214"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Redshift SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-rekognition" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-rekognition"; - version = "1.6.0"; - sha256 = "462e427021e5362747b155ba4f77e4c1d99d794087dca273697fae93aff532a8"; + version = "1.6.1"; + sha256 = "3e20fbeea825447a063684e40b3a3a71342ac32df15f9c40a580279fe6a9f8f8"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Rekognition SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-route53" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv, text }: + ({ mkDerivation, amazonka-core, base, lib, text }: mkDerivation { pname = "amazonka-route53"; - version = "1.6.0"; - sha256 = "68ef773bd9c44b28cb6166d86e3e499d9d32581915548ba08670f5cb1caa6317"; + version = "1.6.1"; + sha256 = "7c6442da5b6ded2a26b4f2b642cffe578456ffda8903f424590744f0dbc75773"; libraryHaskellDepends = [ amazonka-core base text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Route 53 SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-route53-domains" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-route53-domains"; - version = "1.6.0"; - sha256 = "f75bfe2f5f57c7367412479f3406cabcafa11a1436dd19f9a00ead6932e1a5ea"; + version = "1.6.1"; + sha256 = "2c2bcd7445c391235d3a8af2fcd8f641d5a4996379fbbdb8645a24c77f4ba2e8"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Route 53 Domains SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-s3" = callPackage - ({ mkDerivation, amazonka-core, base, lens, stdenv, text }: + ({ mkDerivation, amazonka-core, base, lens, lib, text }: mkDerivation { pname = "amazonka-s3"; - version = "1.6.0"; - sha256 = "eca18ebbd0df13a78768d9665827c7624282f76d512b3cf8f0f22a3afd463f47"; + version = "1.6.1"; + sha256 = "47a0b0124eaf34b8f14bdac4a8ed2a61f86984da4f6fc9e34b44acda07167e28"; libraryHaskellDepends = [ amazonka-core base lens text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Simple Storage Service SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-sdb" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-sdb"; - version = "1.6.0"; - sha256 = "b9c28b21326fdb78a0acee0968188ffb6fb156c7fe0faf688a2ec83d3f5fbdfd"; + version = "1.6.1"; + sha256 = "53b4585f2cc3d192ce85163e23b153e605563b3938d9f9da28244fec8db92a7a"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon SimpleDB SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-servicecatalog" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-servicecatalog"; - version = "1.6.0"; - sha256 = "11f8df3b1b2b43ec636eb5a428c43c8534eae9d9554071298688005bcb46f264"; + version = "1.6.1"; + sha256 = "b4d6ad7c79db7f1b106aa79f7477cff6191aa77d7c1c2b614c108b627507f54b"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Service Catalog SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-ses" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-ses"; - version = "1.6.0"; - sha256 = "778d32e738faae3fd1a7e12a67dddce063c0480740b95e1a58b5c23dc052bd02"; + version = "1.6.1"; + sha256 = "054c576d30341d11ce79869ac1ac5bc0d92ecab88f0fffe9895b78f4b614ece8"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Simple Email Service SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-shield" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-shield"; - version = "1.6.0"; - sha256 = "b983a85b2b5a617bc3cbc911bc8d00a3fbf199ddd5dee67bdb3882b23747ebf4"; + version = "1.6.1"; + sha256 = "1b8a71a8ef5055e8c100ba81ee0fb0a6af7af1e2b29020f546f896f712a07519"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Shield SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-sms" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-sms"; - version = "1.6.0"; - sha256 = "fc4d359d2988d7604780a5eca5b3371d3d3034180e96d2cbc6148559f0cda47f"; + version = "1.6.1"; + sha256 = "d6eb434bde9424080f68691775867e119a9f802cb4e7b7761de31e9a800b4b85"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Server Migration Service SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-snowball" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-snowball"; - version = "1.6.0"; - sha256 = "534b30fe9205ba1edf8b1c5c4f4f91dccbe124f95a599f5efdf0cc4cd502ee25"; + version = "1.6.1"; + sha256 = "48c11fb69fed73bb3e7ed7b4cbaba28eb8cd3013b987479d8fb2d35eaa477cd3"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Import/Export Snowball SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-sns" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-sns"; - version = "1.6.0"; - sha256 = "1d16b548031359ed593b14d172e7880847934e76bbedf535d014674414e37573"; + version = "1.6.1"; + sha256 = "db98a53c40addfcff33938cdfc4daf4ca35e49bbab01b804562abfb1e613e735"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Simple Notification Service SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-sqs" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-sqs"; - version = "1.6.0"; - sha256 = "743838707d28707095700afdf2d875ff34c5fe1d90b214f5a7e48be04c900433"; + version = "1.6.1"; + sha256 = "ee067dd46f51af2ad33ee351d5c85a7d9599a669139fde30fcad825ff80843d4"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Simple Queue Service SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-ssm" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-ssm"; - version = "1.6.0"; - sha256 = "11218249760a2d06cfd5ad2b41bf67233b6178f86e2ab979c199088a5a1c701a"; + version = "1.6.1"; + sha256 = "952dff5e1fba8d79cfc5df93c9e6e782e93462554ce446d4ef4e8aaa313cb0af"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Simple Systems Manager (SSM) SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-stepfunctions" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-stepfunctions"; - version = "1.6.0"; - sha256 = "99ac8e545d28d7d765e180a26572d216f88d1e6ab9a2cd0f0a874992fa89acbf"; + version = "1.6.1"; + sha256 = "60af76621df8ba65cd64dcba3a8b0ca54445599accd0de8c54338920577dd013"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Step Functions SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-storagegateway" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-storagegateway"; - version = "1.6.0"; - sha256 = "6f06376650f03107ebd13a622b77b1983da91c6030927e2d10afb4040b48b43d"; + version = "1.6.1"; + sha256 = "1041b53029d829dd11b30c08d21a87af8da0b4ed92e51376b3233327b1817e3f"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Storage Gateway SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-sts" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-sts"; - version = "1.6.0"; - sha256 = "36056b67d6f97a5b137f7ae35f39fb5417c61991333347129ed3e77f79a99a12"; + version = "1.6.1"; + sha256 = "ee2364bb14e931528aa3d271c1688829c0975251bc5ffc5c824710841e1c8fb9"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Security Token Service SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-support" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-support"; - version = "1.6.0"; - sha256 = "7f434aef975f2817d4b9d7aa1c6055d788988e817fdb5c8fae20a787f26853e9"; + version = "1.6.1"; + sha256 = "5a2d0dd5dd00a067b915e5dfb13c1848683ed7b9bdcfd6ac40d712b417c719ba"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Support SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-swf" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-swf"; - version = "1.6.0"; - sha256 = "1f0e437ba9c1511f46c64df16ae4551667fee39ade3c32f251f9e34b2255aa90"; + version = "1.6.1"; + sha256 = "7b9ce6704f7fe46607722daaa35d11dc2c239fa82ab26ae8a456cdc390b8744a"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon Simple Workflow Service SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-test" = callPackage ({ mkDerivation, aeson, amazonka-core, base, bifunctors, bytestring , case-insensitive, conduit, conduit-extra, groom, http-client - , http-types, process, resourcet, stdenv, tasty, tasty-hunit + , http-types, lib, process, resourcet, tasty, tasty-hunit , template-haskell, temporary, text, time, unordered-containers , yaml }: mkDerivation { pname = "amazonka-test"; - version = "1.6.0"; - sha256 = "46a8b77900370524a487f2ca0490473e23d0155664db2461c5504678d275dd28"; + version = "1.6.1"; + sha256 = "751ed583302c4d8dd1dabe8628e8eb8d97b807a899bb71fe208158fe44f222a9"; libraryHaskellDepends = [ aeson amazonka-core base bifunctors bytestring case-insensitive conduit conduit-extra groom http-client http-types process @@ -3229,56 +3644,56 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Common functionality for Amazonka library test-suites"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-waf" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-waf"; - version = "1.6.0"; - sha256 = "880b9ec52be2d8fb0f5711d1e5357b0ce566e98b775e3bb7921e8f4295bbb980"; + version = "1.6.1"; + sha256 = "45c2f517d858891fa85e70e73969721c97ee22236d6932f0df87cd139255516a"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon WAF SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-workspaces" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-workspaces"; - version = "1.6.0"; - sha256 = "56cf348d8c519a4db23693e81cccf822975ec5b37e74dda54f9f020415c91c84"; + version = "1.6.1"; + sha256 = "e589385b8a86f9997d0831ca350d5591484b9e1245374d3e0e88ab45d45c37bf"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon WorkSpaces SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amazonka-xray" = callPackage - ({ mkDerivation, amazonka-core, base, stdenv }: + ({ mkDerivation, amazonka-core, base, lib }: mkDerivation { pname = "amazonka-xray"; - version = "1.6.0"; - sha256 = "8f510075361aa600cd7759763f4de55aed07b8a7cce65eb445dfcf9f475590f0"; + version = "1.6.1"; + sha256 = "348cf06a7529d78a1b48d84e46a9c527b590355b4133473e8091052b34a5d00d"; libraryHaskellDepends = [ amazonka-core base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/amazonka"; description = "Amazon X-Ray SDK"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "amqp" = callPackage ({ mkDerivation, base, binary, bytestring, clock, connection - , containers, data-binary-ieee754, monad-control, network - , network-uri, split, stdenv, stm, text, vector, xml + , containers, data-binary-ieee754, lib, monad-control, network + , network-uri, split, stm, text, vector, xml }: mkDerivation { pname = "amqp"; - version = "0.18.1"; - sha256 = "4678e2eb976df97e27cacbc4b1feafeb5a1800a9779b0a36666f04804f43e248"; + version = "0.22.0"; + sha256 = "62a60c414f77e1af506e737dc9b8233f933715bf35db94e32a575959f90d28fb"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -3291,10 +3706,31 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/hreinhardt/amqp"; description = "Client library for AMQP servers (currently only RabbitMQ)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "amqp-utils" = callPackage + ({ mkDerivation, amqp, base, bytestring, connection, containers + , data-default-class, directory, hinotify, lib, magic, network + , process, text, time, tls, unix, utf8-string, x509-system + }: + mkDerivation { + pname = "amqp-utils"; + version = "0.6.1.1"; + sha256 = "0c90a4fc458363358376f5e8adb076d38a8ad031b5587cca1c67eee5cd61ced1"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ + amqp base bytestring connection containers data-default-class + directory hinotify magic network process text time tls unix + utf8-string x509-system + ]; + doHaddock = false; + doCheck = false; + description = "AMQP toolset for the command line"; + license = lib.licenses.gpl3Only; }) {}; "annotated-wl-pprint" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "annotated-wl-pprint"; version = "0.7.0"; @@ -3306,14 +3742,14 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/david-christiansen/annotated-wl-pprint"; description = "The Wadler/Leijen Pretty Printer, with annotation support"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "ansi-terminal" = callPackage - ({ mkDerivation, base, colour, stdenv }: + ({ mkDerivation, base, colour, lib }: mkDerivation { pname = "ansi-terminal"; - version = "0.8.2"; - sha256 = "90a7324811e7da0d0aecd66454b1622e3b1ee22ed09bbdae379c0ff079d2fa90"; + version = "0.11"; + sha256 = "c6611b9e51add41db3f79eac30066c06b33a6ca2a09e586b4b361d7f98303793"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base colour ]; @@ -3321,14 +3757,16 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/feuerbach/ansi-terminal"; description = "Simple ANSI terminal support, with Windows compatibility"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "ansi-wl-pprint" = callPackage - ({ mkDerivation, ansi-terminal, base, stdenv }: + ({ mkDerivation, ansi-terminal, base, lib }: mkDerivation { pname = "ansi-wl-pprint"; - version = "0.6.8.2"; - sha256 = "a630721bd57678c3bfeb6c703f8249e434cbf85f40daceec4660fb8c6725cb3e"; + version = "0.6.9"; + sha256 = "a7b2e8e7cd3f02f2954e8b17dc60a0ccd889f49e2068ebb15abfa1d42f7a4eac"; + revision = "2"; + editedCabalFile = "1xrv66v5hqchjhj8a0g3awy1qpsswk2jqb4w4yh3mm1py5s0dlr0"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ ansi-terminal base ]; @@ -3336,210 +3774,74 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "http://github.com/ekmett/ansi-wl-pprint"; description = "The Wadler/Leijen Pretty Printer for colored ANSI terminal output"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "antiope-athena" = callPackage - ({ mkDerivation, amazonka, amazonka-athena, amazonka-core, base - , lens, resourcet, stdenv, text, unliftio-core - }: - mkDerivation { - pname = "antiope-athena"; - version = "6.2.0"; - sha256 = "b103fd481fb7b35e3b774f02f8ce9ab41b230b8a737b85a464ade594860ea34d"; - libraryHaskellDepends = [ - amazonka amazonka-athena amazonka-core base lens resourcet text - unliftio-core - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/arbor/antiope#readme"; - license = stdenv.lib.licenses.mit; - }) {}; - "antiope-core" = callPackage - ({ mkDerivation, amazonka, amazonka-core, base, bytestring - , exceptions, generic-lens, http-client, http-types, lens - , monad-logger, mtl, resourcet, stdenv, text, transformers - , unliftio-core - }: - mkDerivation { - pname = "antiope-core"; - version = "6.2.0"; - sha256 = "2357897649729286a5647f4176d699642d390a60126ea5132c6ddab611846b3c"; - libraryHaskellDepends = [ - amazonka amazonka-core base bytestring exceptions generic-lens - http-client http-types lens monad-logger mtl resourcet text - transformers unliftio-core - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/arbor/antiope#readme"; - license = stdenv.lib.licenses.mit; - }) {}; - "antiope-dynamodb" = callPackage - ({ mkDerivation, amazonka, amazonka-core, amazonka-dynamodb - , antiope-core, base, generic-lens, lens, stdenv, text - , unliftio-core, unordered-containers - }: - mkDerivation { - pname = "antiope-dynamodb"; - version = "6.2.0"; - sha256 = "5266d990b35e4b3d3ae1204d8e6eba5980ef3f783a21f2ff5b2e0964168c66cf"; - libraryHaskellDepends = [ - amazonka amazonka-core amazonka-dynamodb antiope-core base - generic-lens lens text unliftio-core unordered-containers - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/arbor/antiope#readme"; - license = stdenv.lib.licenses.mit; - }) {}; - "antiope-messages" = callPackage - ({ mkDerivation, aeson, amazonka, amazonka-core, amazonka-s3 - , amazonka-sqs, antiope-s3, base, generic-lens, lens, lens-aeson - , monad-loops, network-uri, stdenv, text, unliftio-core - }: - mkDerivation { - pname = "antiope-messages"; - version = "6.2.0"; - sha256 = "bffd6c5b27ea376fba61b028f1f8f00190ef8729109a91edef583b03b6f3f387"; - libraryHaskellDepends = [ - aeson amazonka amazonka-core amazonka-s3 amazonka-sqs antiope-s3 - base generic-lens lens lens-aeson monad-loops network-uri text - unliftio-core - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/arbor/antiope#readme"; - license = stdenv.lib.licenses.mit; - }) {}; - "antiope-s3" = callPackage - ({ mkDerivation, amazonka, amazonka-core, amazonka-s3, antiope-core - , attoparsec, base, bytestring, conduit, conduit-extra, exceptions - , generic-lens, http-types, lens, monad-logger, mtl, network-uri - , resourcet, stdenv, text, unliftio-core - }: - mkDerivation { - pname = "antiope-s3"; - version = "6.2.0"; - sha256 = "12e77e8d966cb90637a359ea7a1e365af05b86929a90c7ec9fd8dc57e4f569bd"; - libraryHaskellDepends = [ - amazonka amazonka-core amazonka-s3 antiope-core attoparsec base - bytestring conduit conduit-extra exceptions generic-lens http-types - lens monad-logger mtl network-uri resourcet text unliftio-core - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/arbor/antiope#readme"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.bsd3; }) {}; - "antiope-sns" = callPackage - ({ mkDerivation, aeson, amazonka, amazonka-core, amazonka-sns, base - , generic-lens, lens, stdenv, text, unliftio-core - }: - mkDerivation { - pname = "antiope-sns"; - version = "6.2.0"; - sha256 = "7b56576a1153a7e285f835893f35d054ea5b6037ac73ed398ed20ab7074ef55a"; - libraryHaskellDepends = [ - aeson amazonka amazonka-core amazonka-sns base generic-lens lens - text unliftio-core - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/arbor/antiope#readme"; - license = stdenv.lib.licenses.mit; - }) {}; - "antiope-sqs" = callPackage - ({ mkDerivation, aeson, amazonka, amazonka-core, amazonka-s3 - , amazonka-sqs, antiope-messages, antiope-s3, base, generic-lens - , lens, lens-aeson, monad-loops, network-uri, stdenv, text - , unliftio-core - }: - mkDerivation { - pname = "antiope-sqs"; - version = "6.2.0"; - sha256 = "45a035ee3cc2988c8b6dd60c988fc1f22a42fd829c8849565a6e7386786c636c"; - libraryHaskellDepends = [ - aeson amazonka amazonka-core amazonka-s3 amazonka-sqs - antiope-messages antiope-s3 base generic-lens lens lens-aeson - monad-loops network-uri text unliftio-core - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/arbor/antiope#readme"; - license = stdenv.lib.licenses.mit; - }) {}; - "aos-signature" = callPackage - ({ mkDerivation, base, bytestring, cryptonite, memory, mtl - , protolude, random, stdenv - }: + "ap-normalize" = callPackage + ({ mkDerivation, base, lib }: mkDerivation { - pname = "aos-signature"; - version = "0.1.1"; - sha256 = "c38a353c8bedd9710aa56f9aa8caf17db4313997afd9733921d1c5917511a9ea"; - libraryHaskellDepends = [ - base bytestring cryptonite memory mtl protolude random - ]; + pname = "ap-normalize"; + version = "0.1.0.1"; + sha256 = "820613b12ce759c8c8a254c78a0e4c474b2cd4cfd08fc0c1d4d5584c58ff2288"; + libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/adjoint-io/aos-signature#readme"; - description = "An implementation of the AOS signatures"; - license = stdenv.lib.licenses.asl20; + description = "Self-normalizing applicative expressions"; + license = lib.licenses.mit; }) {}; "apecs" = callPackage - ({ mkDerivation, base, containers, mtl, stdenv, template-haskell - , vector + ({ mkDerivation, array, base, containers, exceptions, lib, mtl + , template-haskell, vector }: mkDerivation { pname = "apecs"; - version = "0.7.1"; - sha256 = "47dec2adc2d269c863767be5524a1178b9b3f8a4a5bb1903b8fbcbf5cdc67233"; + version = "0.9.2"; + sha256 = "088f57680d445b5c253b5f6367a704c21942312e659f838791544b60eee549b1"; libraryHaskellDepends = [ - base containers mtl template-haskell vector + array base containers exceptions mtl template-haskell vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/jonascarpay/apecs#readme"; - description = "Fast ECS framework for game programming"; - license = stdenv.lib.licenses.bsd3; + description = "Fast Entity-Component-System library for game programming"; + license = lib.licenses.bsd3; }) {}; "apecs-gloss" = callPackage - ({ mkDerivation, apecs, apecs-physics, base, containers, gloss - , linear, stdenv + ({ mkDerivation, apecs, apecs-physics, base, containers, gloss, lib + , linear }: mkDerivation { pname = "apecs-gloss"; - version = "0.2.0"; - sha256 = "70bbaa46929fce5cc3d2db8645abd71c86c6a0cdbc2313f2ef90dbbcac926d62"; + version = "0.2.4"; + sha256 = "6720963044f61f53ac0320457b8c51ed336d622e3815a5d6a7db88b794f58a37"; libraryHaskellDepends = [ apecs apecs-physics base containers gloss linear ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/jonascarpay/apecs-physics#readme"; + homepage = "https://github.com/jonascarpay/apecs/apecs-gloss"; description = "Simple gloss renderer for apecs"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "apecs-physics" = callPackage - ({ mkDerivation, apecs, base, Cabal, containers, inline-c, linear - , stdenv, template-haskell, vector + ({ mkDerivation, apecs, base, Cabal, containers, inline-c, lib + , linear, template-haskell, vector }: mkDerivation { pname = "apecs-physics"; - version = "0.3.1"; - sha256 = "f29db921206b594e9549838f3206a7b2f02393ce1f42049d3d2dabbcd3e64846"; + version = "0.4.5"; + sha256 = "a5db53b53b33bdd03dd7252c206c644cea322b0ad48b4c477c9aa1947ae95dcf"; setupHaskellDepends = [ base Cabal ]; libraryHaskellDepends = [ apecs base containers inline-c linear template-haskell vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/jonascarpay/apecs-physics#readme"; + homepage = "https://github.com/jonascarpay/apecs#readme"; description = "2D physics for apecs"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "api-field-json-th" = callPackage - ({ mkDerivation, aeson, base, lens, split, stdenv, template-haskell + ({ mkDerivation, aeson, base, lens, lib, split, template-haskell , text }: mkDerivation { @@ -3553,10 +3855,30 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/nakaji-dayo/api-field-json-th"; description = "option of aeson's deriveJSON"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "api-maker" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers, http-client + , http-client-tls, http-types, lens, lib, monad-control, mtl, req + , text, transformers, transformers-base + }: + mkDerivation { + pname = "api-maker"; + version = "0.1.0.0"; + sha256 = "d9f86a4b0b2712f10d90fc22e1836160b9214720415eece8a453e61fb0af330b"; + libraryHaskellDepends = [ + aeson base bytestring containers http-client http-client-tls + http-types lens monad-control mtl req text transformers + transformers-base + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/schnecki/api-maker#readme"; + description = "Package to make APIs"; + license = lib.licenses.bsd3; }) {}; "app-settings" = callPackage - ({ mkDerivation, base, containers, directory, mtl, parsec, stdenv + ({ mkDerivation, base, containers, directory, lib, mtl, parsec , text }: mkDerivation { @@ -3570,22 +3892,22 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/emmanueltouzery/app-settings"; description = "A library to manage application settings (INI file-like)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "appar" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "appar"; - version = "0.1.7"; - sha256 = "f6de4f1d1332d665057a9fd1af6b805f66cf04299b03f53696f3c9db4f7ff21f"; + version = "0.1.8"; + sha256 = "c4ceeddc26525b58d82c41b6d3e32141371a200a6794aae185b6266ccc81631f"; libraryHaskellDepends = [ base bytestring ]; doHaddock = false; doCheck = false; description = "A simple applicative parser"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "appendmap" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "appendmap"; version = "0.1.5"; @@ -3595,35 +3917,37 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/koterpillar/appendmap#readme"; description = "Map with a Semigroup and Monoid instances delegating to Semigroup of the elements"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "apply-refact" = callPackage - ({ mkDerivation, base, containers, directory, filemanip, filepath - , ghc, ghc-exactprint, mtl, optparse-applicative, process, refact - , stdenv, syb, temporary, transformers, unix-compat + ({ mkDerivation, base, containers, directory, extra, filemanip + , filepath, ghc, ghc-boot-th, ghc-exactprint, lib + , optparse-applicative, process, refact, syb, transformers + , uniplate, unix-compat }: mkDerivation { pname = "apply-refact"; - version = "0.6.0.0"; - sha256 = "2fbe0e3d4dca8f67e4a423116a947e2a7cf40ef620bf8f66653f64cce4c3555c"; + version = "0.9.3.0"; + sha256 = "fcd4b5d271330c6a023d68ed62e8cfdfdc1883313591e9df23aaa3aec379c5ea"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - base containers directory filemanip ghc ghc-exactprint mtl process - refact syb temporary transformers unix-compat + base containers directory extra filemanip ghc ghc-boot-th + ghc-exactprint process refact syb transformers uniplate unix-compat ]; executableHaskellDepends = [ - base containers directory filemanip filepath ghc ghc-exactprint mtl - optparse-applicative process refact syb temporary transformers - unix-compat + base containers directory extra filemanip filepath ghc ghc-boot-th + ghc-exactprint optparse-applicative process refact syb transformers + uniplate unix-compat ]; doHaddock = false; doCheck = false; + homepage = "https://github.com/mpickering/apply-refact"; description = "Perform refactorings specified by the refact library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "apportionment" = callPackage - ({ mkDerivation, base, containers, stdenv, utility-ht }: + ({ mkDerivation, base, containers, lib, utility-ht }: mkDerivation { pname = "apportionment"; version = "0.0.0.3"; @@ -3633,18 +3957,17 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "http://hub.darcs.net/thielema/apportionment"; description = "Round a set of numbers while maintaining its sum"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "approximate" = callPackage - ({ mkDerivation, base, binary, bytes, Cabal, cabal-doctest, cereal - , comonad, deepseq, ghc-prim, hashable, lens, log-domain, pointed - , safecopy, semigroupoids, semigroups, stdenv, vector + ({ mkDerivation, base, binary, bytes, cereal, comonad, deepseq + , ghc-prim, hashable, lens, lib, log-domain, pointed, safecopy + , semigroupoids, semigroups, vector }: mkDerivation { pname = "approximate"; - version = "0.3.1"; - sha256 = "d837f716d9e73d68a53a17321f0433dd9ffe71df24d550aed6a34ec1c2ad2ea2"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "0.3.4"; + sha256 = "6dcd22925bf1bb7a8aef3ba3616af2653f9cb49607f531ad7dd31ae36b5e5319"; libraryHaskellDepends = [ base binary bytes cereal comonad deepseq ghc-prim hashable lens log-domain pointed safecopy semigroupoids semigroups vector @@ -3653,45 +3976,57 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "http://github.com/analytics/approximate/"; description = "Approximate discrete values and numbers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "approximate-equality" = callPackage + ({ mkDerivation, base, lib, type-level-natural-number }: + mkDerivation { + pname = "approximate-equality"; + version = "1.1.0.2"; + sha256 = "03a11e2bde0b81fcb97947d5dc4302d6712af9d9d405a4968e006ea3caf2bb5f"; + libraryHaskellDepends = [ base type-level-natural-number ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/gcross/approximate-equality"; + description = "Newtype wrappers for approximate equality"; + license = lib.licenses.bsd3; }) {}; "arbor-lru-cache" = callPackage - ({ mkDerivation, base, containers, generic-lens, lens, stdenv, stm - }: + ({ mkDerivation, base, containers, lib, stm }: mkDerivation { pname = "arbor-lru-cache"; - version = "0.1.1.0"; - sha256 = "8f47df22ec2d1fa8b39e5234c3db229be681f8d3979bef55bf98c0686762fe5a"; - libraryHaskellDepends = [ base containers generic-lens lens stm ]; + version = "0.1.1.1"; + sha256 = "602f4969a88c630bff1a4e96acf326c455fdd79ada94c9de134bf4734b33d92b"; + libraryHaskellDepends = [ base containers stm ]; doHaddock = false; doCheck = false; homepage = "https://github.com/arbor/arbor-lru-cache#readme"; - license = stdenv.lib.licenses.mit; + description = "LRU cache based on STM"; + license = lib.licenses.mit; }) {}; "arithmoi" = callPackage - ({ mkDerivation, array, base, containers, deepseq, exact-pi - , ghc-prim, integer-gmp, integer-logarithms, random, stdenv - , transformers, vector + ({ mkDerivation, array, base, chimera, constraints, containers + , deepseq, exact-pi, integer-gmp, integer-logarithms, integer-roots + , lib, mod, random, semirings, transformers, vector }: mkDerivation { pname = "arithmoi"; - version = "0.8.0.0"; - sha256 = "82d33a3c8deb52f8efc7d0192e468eba125c0ba1b48c82b881182c979005d39e"; - revision = "2"; - editedCabalFile = "1jv5ch28pjiq3a83hyvknzfwmsbwgqs6g9618z79ss3385k0cwl9"; + version = "0.12.0.0"; + sha256 = "6ef092fe87feab2a0f5a80d15e302ed9c0085fbbe124d490740a6ef1497ef0d1"; configureFlags = [ "-f-llvm" ]; libraryHaskellDepends = [ - array base containers deepseq exact-pi ghc-prim integer-gmp - integer-logarithms random transformers vector + array base chimera constraints containers deepseq exact-pi + integer-gmp integer-logarithms integer-roots mod random semirings + transformers vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/cartazio/arithmoi"; + homepage = "https://github.com/Bodigrim/arithmoi"; description = "Efficient basic number-theoretic functions"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "array-memoize" = callPackage - ({ mkDerivation, array, base, stdenv }: + ({ mkDerivation, array, base, lib }: mkDerivation { pname = "array-memoize"; version = "0.6.0"; @@ -3700,10 +4035,10 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doHaddock = false; doCheck = false; description = "Memoization combinators using arrays for finite sub-domains of functions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "arrow-extras" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "arrow-extras"; version = "0.1.0.1"; @@ -3713,11 +4048,95 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/louispan/arrow-extras#readme"; description = "Extra functions for Control.Arrow"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "arrows" = callPackage + ({ mkDerivation, base, lib, Stream }: + mkDerivation { + pname = "arrows"; + version = "0.4.4.2"; + sha256 = "f65ac93306629e70ae0d92914cc04d6ab499de3168036f0623aba3fffd22ab09"; + libraryHaskellDepends = [ base Stream ]; + doHaddock = false; + doCheck = false; + homepage = "http://www.haskell.org/arrows/"; + description = "Arrow classes and transformers"; + license = lib.licenses.bsd3; + }) {}; + "ascii" = callPackage + ({ mkDerivation, ascii-case, ascii-char, ascii-group + , ascii-predicates, ascii-superset, ascii-th, base, bytestring + , data-ascii, lib, text + }: + mkDerivation { + pname = "ascii"; + version = "1.0.1.4"; + sha256 = "1c0a524c4ba733805d5be38cb74de6627a5f29654139ebc496b44e8243ea0c48"; + libraryHaskellDepends = [ + ascii-case ascii-char ascii-group ascii-predicates ascii-superset + ascii-th base bytestring data-ascii text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/typeclasses/ascii"; + description = "The ASCII character set and encoding"; + license = lib.licenses.asl20; + }) {}; + "ascii-case" = callPackage + ({ mkDerivation, ascii-char, base, hashable, lib }: + mkDerivation { + pname = "ascii-case"; + version = "1.0.0.4"; + sha256 = "aa839962d5dc80462540582a744c410abe9395a1f0e0966f0c6e20adc6f00591"; + libraryHaskellDepends = [ ascii-char base hashable ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/typeclasses/ascii"; + description = "ASCII letter case"; + license = lib.licenses.asl20; + }) {}; + "ascii-char" = callPackage + ({ mkDerivation, base, hashable, lib }: + mkDerivation { + pname = "ascii-char"; + version = "1.0.0.8"; + sha256 = "0d9437d5c9c83f8f687315768ef42c15c25fae25b41d177de19c8016f09f57aa"; + libraryHaskellDepends = [ base hashable ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/typeclasses/ascii"; + description = "A Char type representing an ASCII character"; + license = lib.licenses.asl20; + }) {}; + "ascii-group" = callPackage + ({ mkDerivation, ascii-char, base, hashable, lib }: + mkDerivation { + pname = "ascii-group"; + version = "1.0.0.4"; + sha256 = "8529346c5ca9f69f7edada5259f2007da0379c3d29288e6badca0f4f6b033e40"; + libraryHaskellDepends = [ ascii-char base hashable ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/typeclasses/ascii"; + description = "ASCII character groups"; + license = lib.licenses.asl20; + }) {}; + "ascii-predicates" = callPackage + ({ mkDerivation, ascii-char, base, lib }: + mkDerivation { + pname = "ascii-predicates"; + version = "1.0.0.4"; + sha256 = "f8cdb326bb16f5019ca59d1071906b8f929fe759aebb3b863dbcff187c184330"; + libraryHaskellDepends = [ ascii-char base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/typeclasses/ascii"; + description = "Various categorizations of ASCII characters"; + license = lib.licenses.asl20; }) {}; "ascii-progress" = callPackage - ({ mkDerivation, async, base, concurrent-output, data-default - , stdenv, time + ({ mkDerivation, async, base, concurrent-output, data-default, lib + , time }: mkDerivation { pname = "ascii-progress"; @@ -3732,22 +4151,58 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/yamadapc/haskell-ascii-progress"; description = "A simple progress bar for the console"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "ascii-superset" = callPackage + ({ mkDerivation, ascii-char, base, bytestring, hashable, lib, text + }: + mkDerivation { + pname = "ascii-superset"; + version = "1.0.1.4"; + sha256 = "b3d71249faf48ef5a1ec56e3f9185ac46a997ec0a91569f32398a22bbe8d53ae"; + libraryHaskellDepends = [ + ascii-char base bytestring hashable text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/typeclasses/ascii"; + description = "Representing ASCII with refined supersets"; + license = lib.licenses.asl20; + }) {}; + "ascii-th" = callPackage + ({ mkDerivation, ascii-char, ascii-superset, base, lib + , template-haskell + }: + mkDerivation { + pname = "ascii-th"; + version = "1.0.0.4"; + sha256 = "c13644a7fc569e6eeec587ef7f2c55c2bea1185e19cb57121dea5e709ff06e23"; + libraryHaskellDepends = [ + ascii-char ascii-superset base template-haskell + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/typeclasses/ascii"; + description = "Template Haskell support for ASCII"; + license = lib.licenses.asl20; }) {}; "asciidiagram" = callPackage ({ mkDerivation, base, bytestring, containers, directory, filepath - , FontyFruity, JuicyPixels, lens, linear, mtl, optparse-applicative - , rasterific-svg, stdenv, svg-tree, text, vector + , FontyFruity, JuicyPixels, lens, lib, linear, mtl + , optparse-applicative, pandoc-types, rasterific-svg, svg-tree + , text, vector }: mkDerivation { pname = "asciidiagram"; - version = "1.3.3.2"; - sha256 = "2b343441f4c7f6e0260d0810d3b22848512c3dd11a80e949076dfbc6b5246e4d"; + version = "1.3.3.3"; + sha256 = "019f1e781143a19434baeffc49ed0ebdf46e05179b36b753772276a0549b6126"; + revision = "1"; + editedCabalFile = "1j7p9smyfmkayx6n7inssxcg9cr4zdm6329fpvba7504b96aprdk"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base bytestring containers FontyFruity JuicyPixels lens linear mtl - rasterific-svg svg-tree text vector + pandoc-types rasterific-svg svg-tree text vector ]; executableHaskellDepends = [ base bytestring directory filepath FontyFruity JuicyPixels @@ -3756,60 +4211,64 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doHaddock = false; doCheck = false; description = "Pretty rendering of Ascii diagram into svg or png"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "asif" = callPackage ({ mkDerivation, attoparsec, base, binary, bytestring, conduit , conduit-combinators, conduit-extra, containers, cpu, directory - , either, exceptions, generic-lens, hw-bits, hw-ip, iproute, lens - , network, old-locale, optparse-applicative, resourcet, stdenv - , temporary-resourcet, text, thyme, vector + , either, exceptions, foldl, generic-lens, hw-bits, hw-ip, lens + , lib, network, old-locale, optparse-applicative, profunctors + , resourcet, temporary-resourcet, text, thyme, transformers, vector }: mkDerivation { pname = "asif"; - version = "3.2.0"; - sha256 = "00430428ae65728721b7509edfffe31dd697eb83ec424091c809c5437319cf67"; + version = "6.0.4"; + sha256 = "03e8f784df914d7f311efd594d89e455b2177492a8491ff503f870a741ca2398"; + revision = "1"; + editedCabalFile = "02gz317ivpmb5yzifm3fv62cik4fh77j7ilb027z6dpx4r041p9w"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ attoparsec base binary bytestring conduit conduit-combinators - conduit-extra containers cpu either exceptions generic-lens hw-bits - hw-ip iproute lens network old-locale resourcet temporary-resourcet - text thyme vector + conduit-extra containers cpu either exceptions foldl generic-lens + hw-bits hw-ip lens network old-locale profunctors resourcet + temporary-resourcet text thyme transformers vector ]; executableHaskellDepends = [ attoparsec base binary bytestring conduit conduit-combinators - conduit-extra containers cpu directory either exceptions - generic-lens hw-bits hw-ip iproute lens network old-locale - optparse-applicative resourcet temporary-resourcet text thyme - vector + conduit-extra containers cpu directory either exceptions foldl + generic-lens hw-bits hw-ip lens network old-locale + optparse-applicative profunctors resourcet temporary-resourcet text + thyme transformers vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/packetloop/asif#readme"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/arbor/asif#readme"; + description = "Library for creating and querying segmented feeds"; + license = lib.licenses.mit; }) {}; "asn1-encoding" = callPackage - ({ mkDerivation, asn1-types, base, bytestring, hourglass, stdenv }: + ({ mkDerivation, asn1-types, base, bytestring, hourglass, lib }: mkDerivation { pname = "asn1-encoding"; - version = "0.9.5"; - sha256 = "1e863bfd363f6c3760cc80f2c0d422e17845a9f79fe006030db202ecab5aaf29"; + version = "0.9.6"; + sha256 = "d9f8deabd3b908e5cf83c0d813c08dc0143b3ec1c0d97f660d2cfa02c1c8da0a"; + revision = "2"; + editedCabalFile = "16503ryhq15f2rfdav2qnkq11dg2r3vk3f9v64q9dmxf8dh8zv97"; libraryHaskellDepends = [ asn1-types base bytestring hourglass ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/vincenthz/hs-asn1"; + homepage = "https://github.com/vincenthz/hs-asn1"; description = "ASN1 data reader and writer in RAW, BER and DER forms"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "asn1-parse" = callPackage - ({ mkDerivation, asn1-encoding, asn1-types, base, bytestring - , stdenv + ({ mkDerivation, asn1-encoding, asn1-types, base, bytestring, lib }: mkDerivation { pname = "asn1-parse"; - version = "0.9.4"; - sha256 = "c6a328f570c69db73f8d2416f9251e8a03753f90d5d19e76cbe69509a3ceb708"; + version = "0.9.5"; + sha256 = "8f1fe1344d30b39dc594d74df2c55209577722af1497204b4c2b6d6e8747f39e"; libraryHaskellDepends = [ asn1-encoding asn1-types base bytestring ]; @@ -3817,56 +4276,68 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/vincenthz/hs-asn1"; description = "Simple monadic parser for ASN1 stream types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "asn1-types" = callPackage - ({ mkDerivation, base, bytestring, hourglass, memory, stdenv }: + ({ mkDerivation, base, bytestring, hourglass, lib, memory }: mkDerivation { pname = "asn1-types"; - version = "0.3.2"; - sha256 = "0c571fff4a10559c6a630d4851ba3cdf1d558185ce3dcfca1136f9883d647217"; + version = "0.3.4"; + sha256 = "78ee92a251379298ca820fa53edbf4b33c539b9fcd887c86f520c30e3b4e21a8"; libraryHaskellDepends = [ base bytestring hourglass memory ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/vincenthz/hs-asn1-types"; + homepage = "http://github.com/vincenthz/hs-asn1"; description = "ASN.1 types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "assert-failure" = callPackage - ({ mkDerivation, base, pretty-show, stdenv, text }: + ({ mkDerivation, base, lib, pretty-show, text }: mkDerivation { pname = "assert-failure"; - version = "0.1.2.2"; - sha256 = "f69416fd527b4f6933586edfc9ee741a2163c3741471e9b8e46a244495bd4a9d"; + version = "0.1.2.5"; + sha256 = "f52e926336ad436377f5b7a6de124f7e2c499d857b0a7f650345ea26d03b0a4d"; enableSeparateDataOutput = true; libraryHaskellDepends = [ base pretty-show text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/Mikolaj/assert-failure"; description = "Syntactic sugar improving 'assert' and 'error'"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "assoc" = callPackage + ({ mkDerivation, base, bifunctors, lib, tagged }: + mkDerivation { + pname = "assoc"; + version = "1.0.2"; + sha256 = "d8988dc6e8718c7a3456515b769c9336aeeec730cf86fc5175247969ff8f144f"; + revision = "1"; + editedCabalFile = "17ycclzwnysca80frsyyb6sdd2r5p83lkgwxjjnjg6j62pvf8958"; + libraryHaskellDepends = [ base bifunctors tagged ]; + doHaddock = false; + doCheck = false; + description = "swap and assoc: Symmetric and Semigroupy Bifunctors"; + license = lib.licenses.bsd3; }) {}; "astro" = callPackage - ({ mkDerivation, base, matrix, stdenv, time }: + ({ mkDerivation, base, lib, matrix, time }: mkDerivation { pname = "astro"; - version = "0.4.2.1"; - sha256 = "da5dde1bcf42e4f48f5f23dbf3a890a2904ecaf86df3d75e365e071b924afe29"; + version = "0.4.3.0"; + sha256 = "65cfe23933fb1c6191c2e5598ebdb984a9cc385f87b5c43748210342015779fd"; libraryHaskellDepends = [ base matrix time ]; doHaddock = false; doCheck = false; homepage = "https://github.com/aligusnet/astro"; description = "Amateur astronomical computations"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "async" = callPackage - ({ mkDerivation, base, hashable, stdenv, stm }: + ({ mkDerivation, base, hashable, lib, stm }: mkDerivation { pname = "async"; - version = "2.2.1"; - sha256 = "8f0b86022a1319d3c1c68655790da4b7f98017982e27ec3f3dbfe01029d39027"; - revision = "1"; - editedCabalFile = "0lg8c3iixm7vjjq2nydkqswj78i4iyx2k83hgs12z829yj196y31"; + version = "2.2.3"; + sha256 = "467af3a0037947a5232ecf5f4efbd4cf2118aaa2310566d7f40ac82b0e32935c"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base hashable stm ]; @@ -3874,10 +4345,10 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/simonmar/async"; description = "Run IO operations asynchronously and wait for their results"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "async-extra" = callPackage - ({ mkDerivation, async, base, deepseq, split, stdenv }: + ({ mkDerivation, async, base, deepseq, lib, split }: mkDerivation { pname = "async-extra"; version = "0.2.0.0"; @@ -3887,12 +4358,29 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/agrafix/async-extra#readme"; description = "Useful concurrent combinators"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "async-pool" = callPackage + ({ mkDerivation, async, base, containers, fgl, lib, monad-control + , stm, transformers, transformers-base + }: + mkDerivation { + pname = "async-pool"; + version = "0.9.1"; + sha256 = "a8b25c0f3e3411943d4bbb8304d02a748a7c2a7d5c4db8ac7326a45a2e79d186"; + libraryHaskellDepends = [ + async base containers fgl monad-control stm transformers + transformers-base + ]; + doHaddock = false; + doCheck = false; + description = "A modified version of async that supports worker groups and many-to-many task dependencies"; + license = lib.licenses.mit; }) {}; "async-refresh" = callPackage - ({ mkDerivation, base, formatting, lifted-async, microlens - , microlens-th, monad-logger, safe-exceptions, stdenv, stm, text - , unliftio, unliftio-core + ({ mkDerivation, base, formatting, lib, lifted-async, microlens + , microlens-th, monad-logger, safe-exceptions, stm, text, unliftio + , unliftio-core }: mkDerivation { pname = "async-refresh"; @@ -3906,12 +4394,12 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/mtesseract/async-refresh"; description = "Package implementing core logic for refreshing of expiring data"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "async-refresh-tokens" = callPackage - ({ mkDerivation, async-refresh, base, bytestring, formatting - , microlens, microlens-th, monad-logger, safe-exceptions, stdenv - , text, unliftio, unliftio-core + ({ mkDerivation, async-refresh, base, bytestring, formatting, lib + , microlens, microlens-th, monad-logger, safe-exceptions, text + , unliftio, unliftio-core }: mkDerivation { pname = "async-refresh-tokens"; @@ -3925,28 +4413,11 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/mtesseract/async-refresh-tokens#readme"; description = "Package implementing core logic for refreshing of expiring access tokens"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "async-timer" = callPackage - ({ mkDerivation, async, base, safe-exceptions, stdenv, unliftio - , unliftio-core - }: - mkDerivation { - pname = "async-timer"; - version = "0.2.0.0"; - sha256 = "0632bfc4c141aa47c461747b3edb59f76ef5523a66ac03be0f32868a5e04cee0"; - libraryHaskellDepends = [ - async base safe-exceptions unliftio unliftio-core - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/mtesseract/async-timer#readme"; - description = "Provides API for timer based execution of IO actions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "atom-basic" = callPackage - ({ mkDerivation, base, base64-bytestring, bytestring, network - , network-uri, stdenv, text, time + ({ mkDerivation, base, base64-bytestring, bytestring, lib, network + , network-uri, text, time }: mkDerivation { pname = "atom-basic"; @@ -3958,31 +4429,29 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doHaddock = false; doCheck = false; description = "Basic Atom feed construction"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "atomic-primops" = callPackage - ({ mkDerivation, base, ghc-prim, primitive, stdenv }: + ({ mkDerivation, base, ghc-prim, lib, primitive }: mkDerivation { pname = "atomic-primops"; - version = "0.8.2"; - sha256 = "67f8872e0c1e634d819a967365eb4ad514e9b2cde967fbc710da7cdc4d17d933"; - revision = "1"; - editedCabalFile = "0gdcd84x2s4jiry0was74rzv9l53an1q6ad8jiaj37fr4fim0wcc"; + version = "0.8.4"; + sha256 = "22a8617eb9e221b5daee1ae26ccce279ce3d7a53d76e82c767708f90a6c72d3e"; libraryHaskellDepends = [ base ghc-prim primitive ]; doHaddock = false; doCheck = false; homepage = "https://github.com/rrnewton/haskell-lockfree/wiki"; description = "A safe approach to CAS and other atomic ops in Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "atomic-write" = callPackage - ({ mkDerivation, base, bytestring, directory, filepath, stdenv + ({ mkDerivation, base, bytestring, directory, filepath, lib , temporary, text, unix-compat }: mkDerivation { pname = "atomic-write"; - version = "0.2.0.6"; - sha256 = "d4634b777ea8df551bc619125b6240047c74b6454c1a3caaad10496a39d443f7"; + version = "0.2.0.7"; + sha256 = "b5f5c77884bc0332306fab89acf1c8a8582d76eabaa303c91b1c4072621c960d"; libraryHaskellDepends = [ base bytestring directory filepath temporary text unix-compat ]; @@ -3990,31 +4459,30 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/stackbuilders/atomic-write"; description = "Atomically write to a file"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "attoparsec" = callPackage ({ mkDerivation, array, base, bytestring, containers, deepseq - , scientific, stdenv, text, transformers + , ghc-prim, lib, scientific, text, transformers }: mkDerivation { pname = "attoparsec"; - version = "0.13.2.2"; - sha256 = "dd93471eb969172cc4408222a3842d867adda3dd7fb39ad8a4df1b121a67d848"; - revision = "2"; - editedCabalFile = "1j06na26rsahrbkzrs71nl7ym8fk390pnvh577wlxs4ik6hsn2va"; + version = "0.13.2.5"; + sha256 = "21e0f38eaa1957bf471276afa17651c125a38924575f12c2cbd2fa534b45686f"; + revision = "1"; + editedCabalFile = "180r53j8z1p6z2l63qmhqyl1h27l5j3vrhanwfmwchrj7xf1k23w"; libraryHaskellDepends = [ - array base bytestring containers deepseq scientific text + array base bytestring containers deepseq ghc-prim scientific text transformers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/bos/attoparsec"; + homepage = "https://github.com/bgamari/attoparsec"; description = "Fast combinator parsing for bytestrings and text"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "attoparsec-base64" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, stdenv, text, word8 - }: + ({ mkDerivation, attoparsec, base, bytestring, lib, text, word8 }: mkDerivation { pname = "attoparsec-base64"; version = "0.0.0"; @@ -4024,10 +4492,10 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/athanclark/attoparsec-base64#readme"; description = "Fetch only base64 characters, erroring in the attoparsec monad on failure"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "attoparsec-binary" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, stdenv }: + ({ mkDerivation, attoparsec, base, bytestring, lib }: mkDerivation { pname = "attoparsec-binary"; version = "0.2"; @@ -4036,49 +4504,43 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doHaddock = false; doCheck = false; description = "Binary processing extensions to Attoparsec"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "attoparsec-expr" = callPackage - ({ mkDerivation, attoparsec, base, stdenv }: + ({ mkDerivation, attoparsec, base, lib }: mkDerivation { pname = "attoparsec-expr"; version = "0.1.1.2"; sha256 = "8d4cd436112ce9007d2831776d4c5102a5322c48993229d2d41e259c07bb457c"; + revision = "1"; + editedCabalFile = "1cpgzd24fvrpsly113ck8rhrc33pfw8qhfpk4wn85qj95763faqb"; libraryHaskellDepends = [ attoparsec base ]; doHaddock = false; doCheck = false; description = "Port of parsec's expression parser to attoparsec"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "attoparsec-ip" = callPackage - ({ mkDerivation, attoparsec, base, ip, stdenv, vector }: - mkDerivation { - pname = "attoparsec-ip"; - version = "0.0.5"; - sha256 = "f5864859694fb9faa64cabea17fdf8f506e325fa4704c23036ea1cc17102c76f"; - libraryHaskellDepends = [ attoparsec base ip vector ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/athanclark/attoparsec-ip#readme"; - description = "Parse IP data types with attoparsec"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "attoparsec-iso8601" = callPackage - ({ mkDerivation, attoparsec, base, base-compat, stdenv, text, time + ({ mkDerivation, attoparsec, base, base-compat-batteries, lib, text + , time, time-compat }: mkDerivation { pname = "attoparsec-iso8601"; - version = "1.0.1.0"; - sha256 = "499ffbd2d39e79cc4fda5ad0129dbf94fdb72a84aa932dfe2a5f5c5c02074142"; - libraryHaskellDepends = [ attoparsec base base-compat text time ]; + version = "1.0.2.0"; + sha256 = "02952d77c78e95710eea855f4e86ca048ab9fda83c6c08dd9215f21a40604f98"; + revision = "1"; + editedCabalFile = "1c43ynmjfljp3nsp67521nrnb0d4vzwr33dfqf15xh02gifcf9ma"; + libraryHaskellDepends = [ + attoparsec base base-compat-batteries text time time-compat + ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/bos/aeson"; + homepage = "https://github.com/haskell/aeson"; description = "Parsing of ISO 8601 dates, originally from aeson"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "attoparsec-path" = callPackage - ({ mkDerivation, attoparsec, base, path, stdenv, text }: + ({ mkDerivation, attoparsec, base, lib, path, text }: mkDerivation { pname = "attoparsec-path"; version = "0.0.0.1"; @@ -4088,29 +4550,11 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/athanclark/attoparsec-path#readme"; description = "Convenience bindings between path and attoparsec"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "attoparsec-uri" = callPackage - ({ mkDerivation, attoparsec, attoparsec-ip, base, bytedump, ip - , QuickCheck, quickcheck-instances, stdenv, strict, text, vector - }: - mkDerivation { - pname = "attoparsec-uri"; - version = "0.0.7"; - sha256 = "369d49c342f90bcc5e07c53b12dc642d6e03aa991900262abc48127d4b25725c"; - libraryHaskellDepends = [ - attoparsec attoparsec-ip base bytedump ip QuickCheck - quickcheck-instances strict text vector - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/athanclark/attoparsec-uri#readme"; - description = "URI parser / printer using attoparsec"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "audacity" = callPackage ({ mkDerivation, base, bytestring, deepseq, directory - , explicit-exception, filepath, non-empty, semigroups, stdenv + , explicit-exception, filepath, lib, non-empty, semigroups , storable-record, storablevector, tagchup, transformers , utility-ht, xml-basic }: @@ -4129,41 +4573,89 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "http://hub.darcs.net/thielema/audacity"; description = "Interchange with the Audacity sound signal editor"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "aur" = callPackage + ({ mkDerivation, aeson, base, bytestring, hashable, http-client + , http-types, lib, text + }: + mkDerivation { + pname = "aur"; + version = "7.0.6"; + sha256 = "be4922084c87b1ef6ab8e7d03d36531a4a44554a54a0c28fe4fdb0f2a07f0267"; + libraryHaskellDepends = [ + aeson base bytestring hashable http-client http-types text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/fosskers/aura"; + description = "Access metadata from the Arch Linux User Repository"; + license = lib.licenses.gpl3Only; + }) {}; + "aura" = callPackage + ({ mkDerivation, aeson, algebraic-graphs, aur, base, bytestring + , containers, filepath, hashable, http-client, http-client-tls + , http-types, language-bash, lib, megaparsec, network-uri + , optparse-applicative, prettyprinter, prettyprinter-ansi-terminal + , rio, scheduler, stm, text, time, transformers, typed-process + , versions + }: + mkDerivation { + pname = "aura"; + version = "3.2.5"; + sha256 = "191e5469e824b28dc0efa9b146b646bf0b4948ca4e7c0bd5057e405837933aff"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson algebraic-graphs aur base bytestring containers filepath + hashable http-client http-types language-bash megaparsec + network-uri prettyprinter prettyprinter-ansi-terminal rio scheduler + stm text time transformers typed-process versions + ]; + executableHaskellDepends = [ + aeson aur base bytestring containers http-client http-client-tls + megaparsec optparse-applicative prettyprinter + prettyprinter-ansi-terminal rio scheduler text transformers + typed-process versions + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/fosskers/aura"; + description = "A secure package manager for Arch Linux and the AUR"; + license = lib.licenses.gpl3Only; }) {}; "authenticate" = callPackage ({ mkDerivation, aeson, attoparsec, base, blaze-builder, bytestring - , case-insensitive, conduit, containers, http-conduit, http-types - , network-uri, resourcet, stdenv, tagstream-conduit, text - , transformers, unordered-containers, xml-conduit + , case-insensitive, conduit, containers, html-conduit, http-conduit + , http-types, lib, network-uri, resourcet, text, transformers + , unordered-containers, xml-conduit }: mkDerivation { pname = "authenticate"; - version = "1.3.4"; - sha256 = "3fd566dbfdf75d81ad1bebd19facb9f01509ead6e27d9aed802404ecde932fb8"; + version = "1.3.5"; + sha256 = "5f13043155a53b14da9b3625e512480110a5d906b0fd8eca2d2493c63c20ae81"; libraryHaskellDepends = [ aeson attoparsec base blaze-builder bytestring case-insensitive - conduit containers http-conduit http-types network-uri resourcet - tagstream-conduit text transformers unordered-containers - xml-conduit + conduit containers html-conduit http-conduit http-types network-uri + resourcet text transformers unordered-containers xml-conduit ]; doHaddock = false; doCheck = false; homepage = "http://github.com/yesodweb/authenticate"; description = "Authentication methods for Haskell web applications"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "authenticate-oauth" = callPackage ({ mkDerivation, base, base64-bytestring, blaze-builder, bytestring - , crypto-pubkey-types, data-default, http-client, http-types - , random, RSA, SHA, stdenv, time, transformers, transformers-compat + , crypto-pubkey-types, data-default, http-client, http-types, lib + , random, RSA, SHA, time, transformers, transformers-compat }: mkDerivation { pname = "authenticate-oauth"; - version = "1.6"; - sha256 = "d26d9f10fd57e06fa2af066df65e578ff3ec7541efc3e6648b29a743b13f8375"; - revision = "1"; - editedCabalFile = "1fxwn8bn6qs8dhxq0q04psq7zp1qvw1b6g3vmsclgyj9p7kr77ms"; + version = "1.6.0.1"; + sha256 = "e0520fb4255ac8d6ff30f06a2b91a9fdc478aa799e254e52747ebd13d70f3ec3"; + revision = "2"; + editedCabalFile = "08i6mmk2jqlrd1aksjx02arly7dfpkwc0dwxpr7hs4rbxajbckyr"; libraryHaskellDepends = [ base base64-bytestring blaze-builder bytestring crypto-pubkey-types data-default http-client http-types random RSA SHA time @@ -4173,200 +4665,130 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "http://github.com/yesodweb/authenticate"; description = "Library to authenticate with OAuth for Haskell web applications"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "auto" = callPackage - ({ mkDerivation, base, base-orphans, bytestring, cereal, containers - , deepseq, MonadRandom, profunctors, random, semigroups, stdenv - , transformers - }: - mkDerivation { - pname = "auto"; - version = "0.4.3.1"; - sha256 = "c6e26d1cbb17e3645e55bc8e9432b124520fbcba5ff32445acd4260c25cd3b41"; - libraryHaskellDepends = [ - base base-orphans bytestring cereal containers deepseq MonadRandom - profunctors random semigroups transformers - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/mstksg/auto"; - description = "Denotative, locally stateful programming DSL & platform"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.bsd3; }) {}; "auto-update" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "auto-update"; - version = "0.1.4"; - sha256 = "5e96c151024e8bcaf4eaa932e16995872b2017f46124b967e155744d9580b425"; + version = "0.1.6"; + sha256 = "f4e023dc8713c387ecf20d851247597fd012cabea3872310b35e911105eb66c4"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/yesodweb/wai"; description = "Efficiently run periodic, on-demand actions"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "autoexporter" = callPackage - ({ mkDerivation, base, Cabal, directory, filepath, stdenv }: + ({ mkDerivation, base, Cabal, directory, filepath, lib }: mkDerivation { pname = "autoexporter"; - version = "1.1.13"; - sha256 = "7bb6fbf567f56a5a3ec53036fe82aa8e17452c46778a34e9dd00477e5cdcaf16"; + version = "1.1.20"; + sha256 = "81e1047d9cb31ad664136ce0ae820b84c26c5a5d15d9d0bda0d09cd5b5e591a9"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base Cabal directory filepath ]; - executableHaskellDepends = [ base Cabal directory filepath ]; + executableHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/tfausak/autoexporter#readme"; description = "Automatically re-export modules"; - license = stdenv.lib.licenses.mit; - }) {}; - "avers" = callPackage - ({ mkDerivation, aeson, attoparsec, base, bytestring, clock - , containers, cryptonite, filepath, inflections, memory - , MonadRandom, mtl, network, network-uri, resource-pool - , rethinkdb-client-driver, safe, scrypt, stdenv, stm - , template-haskell, text, time, unordered-containers, vector - }: - mkDerivation { - pname = "avers"; - version = "0.0.17.1"; - sha256 = "1b45d8aa036b3c2ec7ea180327ff3cdce28dc1e1ef319c062be79f0ffa7626f5"; - revision = "28"; - editedCabalFile = "1x653r0x4frpp78jncvr91kc7g41i9c3s561cizyh518318lvsnr"; - libraryHaskellDepends = [ - aeson attoparsec base bytestring clock containers cryptonite - filepath inflections memory MonadRandom mtl network network-uri - resource-pool rethinkdb-client-driver safe scrypt stm - template-haskell text time unordered-containers vector - ]; - doHaddock = false; - doCheck = false; - description = "Server-side implementation of the Avers storage model"; - license = stdenv.lib.licenses.gpl3; - }) {}; - "avers-api" = callPackage - ({ mkDerivation, aeson, avers, base, bytestring, cookie - , http-api-data, servant, stdenv, text, time, vector - }: - mkDerivation { - pname = "avers-api"; - version = "0.1.0"; - sha256 = "5c1765976fd1ac49444023452e31cbe5200fd9c8480e1927aa4334e8752d5a3e"; - libraryHaskellDepends = [ - aeson avers base bytestring cookie http-api-data servant text time - vector - ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/wereHamster/avers-api"; - description = "Types describing the core and extended Avers APIs"; - license = stdenv.lib.licenses.mit; - }) {}; - "avers-server" = callPackage - ({ mkDerivation, aeson, avers, avers-api, base, base64-bytestring - , bytestring, bytestring-conversion, containers, cookie, cryptonite - , http-types, memory, mtl, resource-pool, servant, servant-server - , stdenv, stm, text, time, transformers, wai, wai-websockets - , websockets - }: - mkDerivation { - pname = "avers-server"; - version = "0.1.0.1"; - sha256 = "becd96d702ba85bfa105f799da27e9fb1e483b59643345503e60888a8860518e"; - libraryHaskellDepends = [ - aeson avers avers-api base base64-bytestring bytestring - bytestring-conversion containers cookie cryptonite http-types - memory mtl resource-pool servant servant-server stm text time - transformers wai wai-websockets websockets - ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/wereHamster/avers-server"; - description = "Server implementation of the Avers API"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "avro" = callPackage ({ mkDerivation, aeson, array, base, base16-bytestring, bifunctors - , binary, bytestring, containers, data-binary-ieee754, fail - , hashable, mtl, pure-zlib, scientific, semigroups, stdenv, tagged - , template-haskell, text, tf-random, unordered-containers, vector + , binary, bytestring, containers, data-binary-ieee754, deepseq + , fail, HasBigDecimal, hashable, lib, mtl, raw-strings-qq + , scientific, semigroups, tagged, template-haskell, text, tf-random + , time, unordered-containers, uuid, vector, zlib }: mkDerivation { pname = "avro"; - version = "0.4.1.2"; - sha256 = "62c7ef79265a9984964995e27a50cf3e25a62b7128d2ad1da85573f7ec60531d"; + version = "0.5.2.0"; + sha256 = "2186adfa5351b9a0ec2a6c44f1772ff4c6ae21514877eccf2a7dc646bcc5fbaa"; + revision = "1"; + editedCabalFile = "0081mnhn26824rbdsz1n74i9m21yfkh6y4g3v7ksh933dxagyiij"; libraryHaskellDepends = [ aeson array base base16-bytestring bifunctors binary bytestring - containers data-binary-ieee754 fail hashable mtl pure-zlib - scientific semigroups tagged template-haskell text tf-random - unordered-containers vector + containers data-binary-ieee754 deepseq fail HasBigDecimal hashable + mtl raw-strings-qq scientific semigroups tagged template-haskell + text tf-random time unordered-containers uuid vector zlib ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-works/avro#readme"; description = "Avro serialization support for Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "avwx" = callPackage - ({ mkDerivation, attoparsec, base, HTTP, lens, optparse-applicative - , parsers, pretty-show, stdenv, text + "aws-cloudfront-signed-cookies" = callPackage + ({ mkDerivation, aeson, aeson-pretty, asn1-encoding, asn1-types + , base, base64-bytestring, bytestring, cookie, cryptonite, lens + , lens-aeson, lib, optparse-applicative, pem, text, time + , unordered-containers, vector }: mkDerivation { - pname = "avwx"; - version = "0.3.0.2"; - sha256 = "b4299cc4e05a4c94f53d06f05b30baac1e15c59663b59afd1dd32417a280fb0a"; + pname = "aws-cloudfront-signed-cookies"; + version = "0.2.0.8"; + sha256 = "4c0d675478581d028cbf0fa5aa95e4468a9542070534b43fc6fb19b2b502c41c"; isLibrary = true; isExecutable = true; - libraryHaskellDepends = [ attoparsec base HTTP lens parsers text ]; - executableHaskellDepends = [ - base optparse-applicative pretty-show text + libraryHaskellDepends = [ + aeson aeson-pretty asn1-encoding asn1-types base base64-bytestring + bytestring cookie cryptonite lens lens-aeson optparse-applicative + pem text time unordered-containers vector ]; + executableHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://www.hcesperer.org/posts/2016-09-20-avwx.html"; - description = "Parse aviation weather reports"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/typeclasses/aws-cloudfront-signed-cookies"; + description = "Generate signed cookies for AWS CloudFront"; + license = lib.licenses.mit; }) {}; - "axel" = callPackage - ({ mkDerivation, base, bytestring, containers, directory, filepath - , freer-simple, ghcid, haskell-src-exts, lens, lens-aeson - , optparse-applicative, parsec, process, regex-pcre, singletons - , stdenv, strict, template-haskell, text, typed-process, vector - , yaml + "aws-xray-client" = callPackage + ({ mkDerivation, aeson, base, bytestring, deepseq, http-types, lens + , lib, network, random, text, time }: mkDerivation { - pname = "axel"; - version = "0.0.9"; - sha256 = "ee5c222094c86eac3b6fe85f619b2ee69f2eb4cdcd8aeabf74b40d21e98a274f"; - isLibrary = true; - isExecutable = true; - enableSeparateDataOutput = true; + pname = "aws-xray-client"; + version = "0.1.0.1"; + sha256 = "3233c3546c50173266ad294a964af08a04fcd9dbaf76bbc5897d7025464c27ac"; libraryHaskellDepends = [ - base bytestring containers directory filepath freer-simple ghcid - haskell-src-exts lens lens-aeson optparse-applicative parsec - process regex-pcre singletons strict template-haskell text - typed-process vector yaml + aeson base bytestring deepseq http-types lens network random text + time ]; - executableHaskellDepends = [ - base containers freer-simple optparse-applicative + doHaddock = false; + doCheck = false; + homepage = "https://github.com/freckle/aws-xray-client#readme"; + description = "A client for AWS X-Ray"; + license = lib.licenses.mit; + }) {}; + "aws-xray-client-wai" = callPackage + ({ mkDerivation, aws-xray-client, base, bytestring, containers + , http-types, lens, lib, random, text, time, unliftio + , unliftio-core, vault, wai + }: + mkDerivation { + pname = "aws-xray-client-wai"; + version = "0.1.0.1"; + sha256 = "779f21e06f6095798e89ff40488d7ec6109e3bd5153bae93fdf84c3c34b5592c"; + libraryHaskellDepends = [ + aws-xray-client base bytestring containers http-types lens random + text time unliftio unliftio-core vault wai ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/axellang/axel#readme"; - description = "The Axel programming language"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/freckle/aws-xray-client#readme"; + description = "A client for AWS X-Ray integration with WAI"; + license = lib.licenses.mit; }) {}; "backprop" = callPackage - ({ mkDerivation, base, containers, deepseq, microlens, primitive - , reflection, stdenv, transformers, vector, vinyl + ({ mkDerivation, base, containers, deepseq, lib, microlens + , primitive, reflection, transformers, vector, vinyl }: mkDerivation { pname = "backprop"; - version = "0.2.6.1"; - sha256 = "d22261e11129c43e68ead4f0a82b82d504085e3176fb79be5f00f4c89513c7e6"; + version = "0.2.6.4"; + sha256 = "69a342da7b71eb82f340b4fd59ae4c39f25e4e0bce9c5de8d5f3e1424d0e8771"; libraryHaskellDepends = [ base containers deepseq microlens primitive reflection transformers vector vinyl @@ -4375,148 +4797,196 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://backprop.jle.im"; description = "Heterogeneous automatic differentation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "backtracking" = callPackage + ({ mkDerivation, base, lib, transformers }: + mkDerivation { + pname = "backtracking"; + version = "0.1.0"; + sha256 = "eb14901d9f962b1f446e1fcd2f4ef0ec05b351fbc64d2cd1d2b9a146add53150"; + libraryHaskellDepends = [ base transformers ]; + doHaddock = false; + doCheck = false; + description = "A backtracking monad"; + license = lib.licenses.bsd3; }) {}; "bank-holidays-england" = callPackage - ({ mkDerivation, base, containers, stdenv, time }: + ({ mkDerivation, base, containers, lib, time }: mkDerivation { pname = "bank-holidays-england"; - version = "0.1.0.8"; - sha256 = "3219472077c4093809dc7c986b693aee2b76c12d44b6063d1b7055af3aa9672a"; + version = "0.2.0.6"; + sha256 = "5a93baae0cf4405d0c4fd5534958697e86fb4819cc557b9bb36ac6ee57301dbd"; libraryHaskellDepends = [ base containers time ]; doHaddock = false; doCheck = false; - homepage = "https://bitbucket.org/davecturner/bank-holidays-england"; + homepage = "https://github.com/DaveCTurner/bank-holidays-england"; description = "Calculation of bank holidays in England and Wales"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "barbies" = callPackage - ({ mkDerivation, base, bifunctors, stdenv }: + ({ mkDerivation, base, distributive, lib, transformers }: mkDerivation { pname = "barbies"; - version = "1.1.0.0"; - sha256 = "9a857f00dfd7dc0a1471eda450d5b09f16a4066d70c24c4910b91c5b9cc0960a"; - libraryHaskellDepends = [ base bifunctors ]; + version = "2.0.3.0"; + sha256 = "95e85b226dc2fca01aaeb2f39cafbbc3f28eebd646ae72a774d873bd49bb242f"; + libraryHaskellDepends = [ base distributive transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/jcpetruzza/barbies#readme"; description = "Classes for working with types that can change clothes"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "barrier" = callPackage - ({ mkDerivation, base, blaze-svg, bytestring, stdenv - , template-haskell, text, unordered-containers - }: - mkDerivation { - pname = "barrier"; - version = "0.1.1"; - sha256 = "6395da01eea1984c7bcc85c624b1b5dfbe0b6b764adeed7b04c9fa4d8de91ed9"; - revision = "1"; - editedCabalFile = "167akvi72l47gcqbq5609m24469pq0xmv0kjbmivnrxs796gh890"; - isLibrary = true; - isExecutable = true; - enableSeparateDataOutput = true; - libraryHaskellDepends = [ - base blaze-svg bytestring template-haskell text - unordered-containers - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/philopon/barrier"; - description = "Shields.io style badge generator"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.bsd3; }) {}; "base-compat" = callPackage - ({ mkDerivation, base, stdenv, unix }: + ({ mkDerivation, base, lib, unix }: mkDerivation { pname = "base-compat"; - version = "0.10.5"; - sha256 = "990aea21568956d44ab018c5dbfbaea014b9a0d5295d29ca7550149419a6fb41"; + version = "0.11.2"; + sha256 = "53a6b5145442fba5a4bad6db2bcdede17f164642b48bc39b95015422a39adbdb"; libraryHaskellDepends = [ base unix ]; doHaddock = false; doCheck = false; description = "A compatibility layer for base"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "base-compat-batteries" = callPackage - ({ mkDerivation, base, base-compat, stdenv }: + ({ mkDerivation, base, base-compat, lib }: mkDerivation { pname = "base-compat-batteries"; - version = "0.10.5"; - sha256 = "175dcfd1453bd02ec955c05181cbf4278af145183b5899c62d3be29d866170ee"; + version = "0.11.2"; + sha256 = "31e066a5aa96af94fe6465adb959c38d63a49e01357641aa4322c754a94d3023"; libraryHaskellDepends = [ base base-compat ]; doHaddock = false; doCheck = false; description = "base-compat with extra batteries"; - license = stdenv.lib.licenses.mit; - }) {}; - "base-noprelude" = callPackage - ({ mkDerivation, base, stdenv }: - mkDerivation { - pname = "base-noprelude"; - version = "4.12.0.0"; - sha256 = "abfa32167a9b4a68d4ae5acda2e9d66ffe883cdb780c4e626794cc44a42d62c1"; - libraryHaskellDepends = [ base ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/hvr/base-noprelude"; - description = "\"base\" package sans \"Prelude\" module"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; "base-orphans" = callPackage - ({ mkDerivation, base, ghc-prim, stdenv }: + ({ mkDerivation, base, ghc-prim, lib }: mkDerivation { pname = "base-orphans"; - version = "0.8"; - sha256 = "aceec656bfb4222ad3035c3d87d80130b42b595b72888f9ab59c6dbb7ed24817"; + version = "0.8.4"; + sha256 = "37b2b59356c03400a2d509862677393c5ff706a0aabf826c104f6fe03d93bbb3"; libraryHaskellDepends = [ base ghc-prim ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-compat/base-orphans#readme"; description = "Backwards-compatible orphan instances for base"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "base-prelude" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "base-prelude"; - version = "1.3"; - sha256 = "e3cc66e99d6c83aac548c4d8e6a166e5bd9cf557947cde49161026d0341267fe"; + version = "1.4"; + sha256 = "3a7fc639f3e5293509369d0b217f9d9b9662373b151411841df1d099bcd8c55a"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nikita-volkov/base-prelude"; description = "The most complete prelude formed solely from the \"base\" package"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "base-unicode-symbols" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "base-unicode-symbols"; - version = "0.2.3"; - sha256 = "ee7bbe2bd314e8860a641264e956c2b5100ef5b2d5b847a69a3f3c894fa446c5"; + version = "0.2.4.2"; + sha256 = "4364d6c403616e9ec0c240c4cb450c66af43ea8483d73c315e96f4ba3cb97062"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "http://haskell.org/haskellwiki/Unicode-symbols"; description = "Unicode alternatives for common functions and operators"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "base16" = callPackage + ({ mkDerivation, base, bytestring, deepseq, lib, primitive, text + , text-short + }: + mkDerivation { + pname = "base16"; + version = "0.3.0.1"; + sha256 = "cdbeaf20891dcb51d811235f91604dcb7208c585f0fce82659936855134c2d82"; + revision = "4"; + editedCabalFile = "05fpdw8qkdg7cfyfsnk5npcxqgjgasd8hi096nh6czj96xn4s1b6"; + libraryHaskellDepends = [ + base bytestring deepseq primitive text text-short + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/emilypi/base16"; + description = "Fast RFC 4648-compliant Base16 encoding"; + license = lib.licenses.bsd3; }) {}; "base16-bytestring" = callPackage - ({ mkDerivation, base, bytestring, ghc-prim, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "base16-bytestring"; - version = "0.1.1.6"; - sha256 = "5afe65a152c5418f5f4e3579a5e0d5ca19c279dc9bf31c1a371ccbe84705c449"; - libraryHaskellDepends = [ base bytestring ghc-prim ]; + version = "1.0.1.0"; + sha256 = "c0c70a4b58be53d36971bd7361ba300f82a5d5ebf7f50e1a2d7bfc8838bdd6fa"; + libraryHaskellDepends = [ base bytestring ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/haskell/base16-bytestring"; + description = "RFC 4648-compliant Base16 encodings for ByteStrings"; + license = lib.licenses.bsd3; + }) {}; + "base16-lens" = callPackage + ({ mkDerivation, base, base16, bytestring, lens, lib, text + , text-short + }: + mkDerivation { + pname = "base16-lens"; + version = "0.1.3.2"; + sha256 = "d289ca0c8cbdbadce77477e691dd94981c78f1a579c8307557742793ea431f13"; + libraryHaskellDepends = [ + base base16 bytestring lens text text-short + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/emilypi/base16-lens"; + description = "Optics for the Base16 library"; + license = lib.licenses.bsd3; + }) {}; + "base32" = callPackage + ({ mkDerivation, base, bytestring, deepseq, ghc-byteorder, lib + , text, text-short + }: + mkDerivation { + pname = "base32"; + version = "0.2.1.0"; + sha256 = "97de34f8f0430da48369dfbb95bddb941b6f97cc1b99cc42150b5513f3fa38b0"; + revision = "1"; + editedCabalFile = "0apyphnlsnr16s5xb9b9g7d5aw3ny4qx8nz8y71zpglk63sy0cq0"; + libraryHaskellDepends = [ + base bytestring deepseq ghc-byteorder text text-short + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/emilypi/base32"; + description = "Fast RFC 4648-compliant Base32 encoding"; + license = lib.licenses.bsd3; + }) {}; + "base32-lens" = callPackage + ({ mkDerivation, base, base32, bytestring, lens, lib, text + , text-short + }: + mkDerivation { + pname = "base32-lens"; + version = "0.1.1.1"; + sha256 = "462f149520a3d70d3c8b0b3a6e5bd410e3f4ead295971164cebafc7d6a125571"; + libraryHaskellDepends = [ + base base32 bytestring lens text text-short + ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/bos/base16-bytestring"; - description = "Fast base16 (hex) encoding and decoding for ByteStrings"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/emilypi/base32-lens"; + description = "Optics for the Base32 library"; + license = lib.licenses.bsd3; }) {}; "base32string" = callPackage - ({ mkDerivation, aeson, base, binary, bytestring, stdenv, text }: + ({ mkDerivation, aeson, base, binary, bytestring, lib, text }: mkDerivation { pname = "base32string"; version = "0.9.1"; @@ -4527,10 +4997,23 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "http://www.leonmergen.com/opensource.html"; description = "Fast and safe representation of a Base-32 string"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "base58-bytestring" = callPackage + ({ mkDerivation, base, bytestring, lib }: + mkDerivation { + pname = "base58-bytestring"; + version = "0.1.0"; + sha256 = "c2dbf598f3415053e12cca84b90fa7c0c1b02f3b784cce0157264baebf2d40d3"; + libraryHaskellDepends = [ base bytestring ]; + doHaddock = false; + doCheck = false; + homepage = "https://bitbucket.org/s9gf4ult/base58-bytestring"; + description = "Implementation of BASE58 transcoding for ByteStrings"; + license = lib.licenses.publicDomain; }) {}; "base58string" = callPackage - ({ mkDerivation, aeson, base, binary, bytestring, stdenv, text }: + ({ mkDerivation, aeson, base, binary, bytestring, lib, text }: mkDerivation { pname = "base58string"; version = "0.10.0"; @@ -4541,44 +5024,80 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "http://www.leonmergen.com/opensource.html"; description = "Fast and safe representation of a Base-58 string"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "base64" = callPackage + ({ mkDerivation, base, bytestring, deepseq, ghc-byteorder, lib + , text, text-short + }: + mkDerivation { + pname = "base64"; + version = "0.4.2.3"; + sha256 = "bcbf21179841fbf657772792bef453773e01ea8229ed42a7422fcb073bd7b8c1"; + revision = "1"; + editedCabalFile = "10s7nw79q385f74x76rh8cy0dxfj7idzrj77ng9x32bf8h7jpa6q"; + libraryHaskellDepends = [ + base bytestring deepseq ghc-byteorder text text-short + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/emilypi/base64"; + description = "A modern RFC 4648-compliant Base64 library"; + license = lib.licenses.bsd3; }) {}; "base64-bytestring" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "base64-bytestring"; - version = "1.0.0.2"; - sha256 = "193654ed9bd9e7f20163c9b70bab32d33010be50a5e1e8e2258229faf32a608c"; + version = "1.1.0.0"; + sha256 = "210d6c9042241ca52ee5d89cf221dbeb4d0e64b37391345369035ad2d9b4aca9"; libraryHaskellDepends = [ base bytestring ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell/base64-bytestring"; description = "Fast base64 encoding and decoding for ByteStrings"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "base64-bytestring-type" = callPackage ({ mkDerivation, aeson, base, base-compat, base64-bytestring - , binary, bytestring, cereal, deepseq, hashable, QuickCheck, stdenv - , text + , binary, bytestring, cereal, deepseq, hashable, http-api-data, lib + , QuickCheck, serialise, text }: mkDerivation { pname = "base64-bytestring-type"; - version = "1"; - sha256 = "74019bd11f8012ae5ccc88c206bc5a8024f7605130099aabbac012073160e440"; - revision = "4"; - editedCabalFile = "0yfhy4a9n67l9w3amqrzzy79q47yyj6qbv5i5lqym5z7ygwmlzn6"; + version = "1.0.1"; + sha256 = "f607d07c4aab227b4536c495fa7c07b35ddc9c2c013d385c16c02f236526780e"; + revision = "8"; + editedCabalFile = "196m1ylkl9d03iymld08fhfnfcdydzd824v7ffl67ijmfxcvzcyn"; libraryHaskellDepends = [ aeson base base-compat base64-bytestring binary bytestring cereal - deepseq hashable QuickCheck text + deepseq hashable http-api-data QuickCheck serialise text ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/futurice/haskell-base64-bytestring-type#readme"; + homepage = "https://github.com/phadej/base64-bytestring-type#readme"; description = "A newtype around ByteString, for base64 encoding"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "base64-lens" = callPackage + ({ mkDerivation, base, base64, bytestring, lens, lib, text + , text-short + }: + mkDerivation { + pname = "base64-lens"; + version = "0.3.1"; + sha256 = "36c3ff8cc1e66edd7d59d438c9567f395040c949de290631cfec402118dd5fc7"; + libraryHaskellDepends = [ + base base64 bytestring lens text text-short + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/emilypi/base64-lens"; + description = "Optics for the Base64 library"; + license = lib.licenses.bsd3; }) {}; "base64-string" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "base64-string"; version = "0.2"; @@ -4589,26 +5108,26 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; homepage = "http://urchin.earth.li/~ian/cabal/base64-string/"; description = "Base64 implementation for String's"; license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; + hydraPlatforms = lib.platforms.none; }) {}; "basement" = callPackage - ({ mkDerivation, base, ghc-prim, stdenv }: + ({ mkDerivation, base, ghc-prim, lib }: mkDerivation { pname = "basement"; - version = "0.0.8"; - sha256 = "c7f41b97f2b0a71804c3c7d760047dc9adc9734e789084ca1198c4764ce192a4"; + version = "0.0.12"; + sha256 = "53c4435b17b7df398c730406263957977fe0616b66529dafa8d1a0fd66b7fa8b"; revision = "1"; - editedCabalFile = "005w4d6bkx6xq1whgwna4rqmxc36vgjbvb8q35sh1z2s76l89ajy"; + editedCabalFile = "1gr3zqf9xl3wlr2ajc03h9iya3jpx2h4jyjv2vhqxdvm6myiiffb"; libraryHaskellDepends = [ base ghc-prim ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-foundation/foundation#readme"; description = "Foundation scrap box of array & string"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "basic-prelude" = callPackage ({ mkDerivation, base, bytestring, containers, filepath, hashable - , stdenv, text, transformers, unordered-containers, vector + , lib, text, transformers, unordered-containers, vector }: mkDerivation { pname = "basic-prelude"; @@ -4622,26 +5141,26 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/snoyberg/basic-prelude#readme"; description = "An enhanced core prelude; a common foundation for alternate preludes"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "bazel-runfiles" = callPackage - ({ mkDerivation, base, directory, filepath, stdenv }: + ({ mkDerivation, base, directory, filepath, lib, transformers }: mkDerivation { pname = "bazel-runfiles"; - version = "0.7.0.1"; - sha256 = "4d217f74a7eee5dced014d74ac8a3be886d9d0c5ce8e556d8ef16535bde40a00"; + version = "0.12"; + sha256 = "758abec4b6d9256dd17a3d9d3de1279e01f04a8662ef5fbd523d83e58b343cf5"; isLibrary = true; isExecutable = true; - libraryHaskellDepends = [ base directory filepath ]; + libraryHaskellDepends = [ base directory filepath transformers ]; executableHaskellDepends = [ base filepath ]; doHaddock = false; doCheck = false; homepage = "https://github.com/tweag/rules_haskell#readme"; description = "Locate Bazel runfiles location"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; }) {}; "bbdb" = callPackage - ({ mkDerivation, base, parsec, stdenv }: + ({ mkDerivation, base, lib, parsec }: mkDerivation { pname = "bbdb"; version = "0.8"; @@ -4651,11 +5170,47 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/henrylaxen/bbdb"; description = "Ability to read, write, and modify BBDB files"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; + }) {}; + "bcp47" = callPackage + ({ mkDerivation, aeson, base, containers, country + , generic-arbitrary, iso639, lib, megaparsec, QuickCheck, text + }: + mkDerivation { + pname = "bcp47"; + version = "0.2.0.4"; + sha256 = "4772c5a44a889d4fa3aa44586fb604c4e0a3737c2960ae9cd3c10084de047fa8"; + libraryHaskellDepends = [ + aeson base containers country generic-arbitrary iso639 megaparsec + QuickCheck text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/freckle/bcp47#readme"; + description = "Language tags as specified by BCP 47"; + license = lib.licenses.mit; + }) {}; + "bcp47-orphans" = callPackage + ({ mkDerivation, base, bcp47, cassava, errors, esqueleto, hashable + , http-api-data, lib, path-pieces, persistent, text + }: + mkDerivation { + pname = "bcp47-orphans"; + version = "0.1.0.4"; + sha256 = "3c048815f8eab35b149dc148ebe4b75c270330425a34f655df40f2da1b007d22"; + libraryHaskellDepends = [ + base bcp47 cassava errors esqueleto hashable http-api-data + path-pieces persistent text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/freckle/bcp47#readme"; + description = "BCP47 orphan instances"; + license = lib.licenses.mit; }) {}; "bcrypt" = callPackage - ({ mkDerivation, base, bytestring, data-default, entropy, memory - , stdenv + ({ mkDerivation, base, bytestring, data-default, entropy, lib + , memory }: mkDerivation { pname = "bcrypt"; @@ -4667,16 +5222,56 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doHaddock = false; doCheck = false; description = "Haskell bindings to the bcrypt password hash"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "bech32" = callPackage + ({ mkDerivation, array, base, base58-bytestring, bytestring + , containers, extra, lib, memory, optparse-applicative, text + }: + mkDerivation { + pname = "bech32"; + version = "1.1.1"; + sha256 = "f6f504873cfdd1e33b664d3cfa596b62b4dfc135940dbffae5a1b811e78a6d45"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + array base bytestring containers extra text + ]; + executableHaskellDepends = [ + base base58-bytestring bytestring extra memory optparse-applicative + text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/input-output-hk/bech32"; + description = "Implementation of the Bech32 cryptocurrency address format (BIP 0173)"; + license = lib.licenses.asl20; + }) {}; + "bech32-th" = callPackage + ({ mkDerivation, base, bech32, lib, template-haskell, text }: + mkDerivation { + pname = "bech32-th"; + version = "1.0.2"; + sha256 = "d836c5c825b66cf799b6c423476d9ae942a2e5073eae63c2928747b08847f67a"; + revision = "1"; + editedCabalFile = "1b614lymjd3idcbzrkha7labfskv1m0kbljrnhwcz7sbymfcbdbk"; + libraryHaskellDepends = [ base bech32 template-haskell text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/input-output-hk/bech32"; + description = "Template Haskell extensions to the Bech32 library"; + license = lib.licenses.asl20; }) {}; "bench" = callPackage - ({ mkDerivation, base, criterion, optparse-applicative, process - , silently, stdenv, text, turtle + ({ mkDerivation, base, criterion, lib, optparse-applicative + , process, silently, text, turtle }: mkDerivation { pname = "bench"; version = "1.0.12"; sha256 = "a6376f4741588201ab6e5195efb1e9921bc0a899f77a5d9ac84a5db32f3ec9eb"; + revision = "2"; + editedCabalFile = "055482m81h7pijiszdkk2k65p208i3c3pxs955pv6h0gwrialcsh"; isLibrary = false; isExecutable = true; executableHaskellDepends = [ @@ -4686,42 +5281,26 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/Gabriel439/bench"; description = "Command-line benchmark tool"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "benchpress" = callPackage - ({ mkDerivation, base, bytestring, mtl, stdenv, time }: + ({ mkDerivation, base, bytestring, lib, mtl, time }: mkDerivation { pname = "benchpress"; - version = "0.2.2.12"; - sha256 = "d571e8d37f5ded433f184dcf8319757284abe6c0fce3106dd716812a5b0dab64"; + version = "0.2.2.17"; + sha256 = "79f4de94eb72dadcf7f8029227d2905e66e98313d09a10ed9997e64c3c947c9d"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base mtl time ]; - executableHaskellDepends = [ base bytestring ]; + executableHaskellDepends = [ base bytestring time ]; doHaddock = false; doCheck = false; homepage = "https://github.com/WillSewell/benchpress"; description = "Micro-benchmarking with detailed statistics"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "bencode" = callPackage - ({ mkDerivation, base, binary, bytestring, containers, parsec - , stdenv - }: - mkDerivation { - pname = "bencode"; - version = "0.6.0.0"; - sha256 = "3b8efdfecee9bc486d9bcdbb633b7128ca235360f102478a7e0f8c895281f68a"; - libraryHaskellDepends = [ - base binary bytestring containers parsec - ]; - doHaddock = false; - doCheck = false; - description = "Parser and printer for bencoded data"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "between" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "between"; version = "0.11.0.0"; @@ -4731,10 +5310,10 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/trskop/between"; description = "Function combinator \"between\" and derived combinators"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "bibtex" = callPackage - ({ mkDerivation, base, latex, parsec, stdenv, utility-ht }: + ({ mkDerivation, base, latex, lib, parsec, utility-ht }: mkDerivation { pname = "bibtex"; version = "0.1.0.6"; @@ -4746,43 +5325,44 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/BibTeX"; description = "Parse, format and processing BibTeX files"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "bifunctors" = callPackage - ({ mkDerivation, base, base-orphans, comonad, containers - , semigroups, stdenv, tagged, template-haskell, th-abstraction - , transformers + ({ mkDerivation, base, base-orphans, comonad, containers, lib + , tagged, template-haskell, th-abstraction, transformers }: mkDerivation { pname = "bifunctors"; - version = "5.5.3"; - sha256 = "d434528fd2ea765bace57c4ade0bc9fa32ba2c425f563b33a4b60f625ecfc9ca"; + version = "5.5.11"; + sha256 = "2b6b9672faab649995cf4c885f353b6638b6daee467a9ace40a7fc773831091c"; libraryHaskellDepends = [ - base base-orphans comonad containers semigroups tagged - template-haskell th-abstraction transformers + base base-orphans comonad containers tagged template-haskell + th-abstraction transformers ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/bifunctors/"; description = "Bifunctors"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "bimap" = callPackage - ({ mkDerivation, base, containers, exceptions, stdenv }: + ({ mkDerivation, base, containers, deepseq, exceptions, lib }: mkDerivation { pname = "bimap"; - version = "0.3.3"; - sha256 = "73829355c7bcbd3eedba22a382a04a3ab641702b00828790ec082ec2db3a8ad1"; - libraryHaskellDepends = [ base containers exceptions ]; + version = "0.4.0"; + sha256 = "d1a39686abbfed5864a8fb778d2244825b6eac977e130e7c1212e6d3a68f249d"; + revision = "1"; + editedCabalFile = "111wyqh17a6pkjhyaz8n1891m69hwr2gybqcpacw4xdmarxmi7f5"; + libraryHaskellDepends = [ base containers deepseq exceptions ]; doHaddock = false; doCheck = false; homepage = "https://github.com/joelwilliamson/bimap"; description = "Bidirectional mapping between two key types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "bimap-server" = callPackage ({ mkDerivation, aeson, base, bimap, binary, directory, http-types - , stdenv, unix, wai, warp + , lib, unix, wai, warp }: mkDerivation { pname = "bimap-server"; @@ -4794,23 +5374,48 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doHaddock = false; doCheck = false; description = "Two-column database server"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "binary-bits" = callPackage - ({ mkDerivation, base, binary, bytestring, stdenv }: + "bimaps" = callPackage + ({ mkDerivation, aeson, base, binary, cereal, cereal-vector + , containers, deepseq, hashable, lib, primitive, storable-tuple + , unordered-containers, vector, vector-binary-instances + , vector-th-unbox + }: mkDerivation { - pname = "binary-bits"; - version = "0.5"; - sha256 = "16534a018a4754d8d1eab051711c23fb741f41a0d141b289001c52824b5be794"; - libraryHaskellDepends = [ base binary bytestring ]; + pname = "bimaps"; + version = "0.1.0.2"; + sha256 = "9774dd645620074f0b95d8c29183f4bf328944f571b2dbe9c0f02d508c6d9520"; + libraryHaskellDepends = [ + aeson base binary cereal cereal-vector containers deepseq hashable + primitive storable-tuple unordered-containers vector + vector-binary-instances vector-th-unbox + ]; doHaddock = false; doCheck = false; - description = "Bit parsing/writing on top of binary"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/choener/bimaps"; + description = "bijections with multiple implementations"; + license = lib.licenses.bsd3; + }) {}; + "bin" = callPackage + ({ mkDerivation, base, dec, deepseq, fin, hashable, lib, QuickCheck + }: + mkDerivation { + pname = "bin"; + version = "0.1.1"; + sha256 = "da9789e8fc7909a78a71d66b337b84704a07305503c262867f4ddad9bec85c85"; + libraryHaskellDepends = [ + base dec deepseq fin hashable QuickCheck + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/phadej/vec"; + description = "Bin: binary natural numbers"; + license = lib.licenses.gpl2Plus; }) {}; "binary-conduit" = callPackage - ({ mkDerivation, base, binary, bytestring, conduit, exceptions - , stdenv, vector + ({ mkDerivation, base, binary, bytestring, conduit, exceptions, lib + , vector }: mkDerivation { pname = "binary-conduit"; @@ -4823,13 +5428,13 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "http://github.com/qnikst/binary-conduit/"; description = "data serialization/deserialization conduit library"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "binary-ext" = callPackage ({ mkDerivation, attoparsec, base, binary, bytestring, conduit - , conduit-combinators, data-binary-ieee754, errors, exceptions + , conduit-combinators, data-binary-ieee754, errors, exceptions, lib , monad-control, monad-loops, mono-traversable, mtl, scientific - , stdenv, text, transformers, transformers-base + , text, transformers, transformers-base }: mkDerivation { pname = "binary-ext"; @@ -4844,10 +5449,10 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/A1-Triard/binary-ext#readme"; description = "An alternate with strong-typed errors for `Data.Binary.Get` monad from `binary` package."; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; }) {}; "binary-ieee754" = callPackage - ({ mkDerivation, array, base, binary, stdenv }: + ({ mkDerivation, array, base, binary, lib }: mkDerivation { pname = "binary-ieee754"; version = "0.1.0.0"; @@ -4857,11 +5462,34 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/winterland1989/binary-ieee754"; description = "Backport ieee754 float double combinators to older binary"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "binary-instances" = callPackage + ({ mkDerivation, aeson, base, binary, binary-orphans + , case-insensitive, hashable, lib, scientific, tagged, text + , text-binary, time-compat, unordered-containers, vector + , vector-binary-instances + }: + mkDerivation { + pname = "binary-instances"; + version = "1.0.1"; + sha256 = "0006fec46a653db4fe7d914a6fd83eff907709f23952bf8ca31a67cce3971872"; + revision = "1"; + editedCabalFile = "1xw2rl5mk626i54c0azrw5as3avd2cvzxn8l6sg5ymc14c240iwp"; + libraryHaskellDepends = [ + aeson base binary binary-orphans case-insensitive hashable + scientific tagged text text-binary time-compat unordered-containers + vector vector-binary-instances + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskellari/binary-instances#readme"; + description = "Orphan instances for binary"; + license = lib.licenses.bsd3; }) {}; "binary-list" = callPackage - ({ mkDerivation, base, binary, bytestring, deepseq, phantom-state - , stdenv, transformers + ({ mkDerivation, base, binary, bytestring, deepseq, lib + , phantom-state, transformers }: mkDerivation { pname = "binary-list"; @@ -4873,59 +5501,43 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doHaddock = false; doCheck = false; description = "Lists of length a power of two"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "binary-orphans" = callPackage - ({ mkDerivation, aeson, base, binary, case-insensitive, hashable - , scientific, stdenv, tagged, text, text-binary, time - , unordered-containers, vector, vector-binary-instances - }: + ({ mkDerivation, base, binary, lib, transformers }: mkDerivation { pname = "binary-orphans"; - version = "0.1.8.0"; - sha256 = "f17557ccd98931df2bea038f25e7f835f38019ea7d53bd763f71fe64f931c0cc"; + version = "1.0.1"; + sha256 = "431ad40b8d812bada186c68935c0a69aa2904ca3bc57d957e1b0fb7d73b1753d"; revision = "5"; - editedCabalFile = "1dny1jvwwcyrbzhqvymmn6n7ib48bpy0nasbrcrdrpzjypkmg500"; - libraryHaskellDepends = [ - aeson base binary case-insensitive hashable scientific tagged text - text-binary time unordered-containers vector - vector-binary-instances - ]; + editedCabalFile = "1h2d37szfrcwn9rphnijn4q9l947b0wwqjs1aqmm62xkhbad7jf6"; + libraryHaskellDepends = [ base binary transformers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/phadej/binary-orphans#readme"; - description = "Orphan instances for binary"; - license = stdenv.lib.licenses.bsd3; + description = "Compatibility package for binary; provides instances"; + license = lib.licenses.bsd3; }) {}; "binary-parser" = callPackage - ({ mkDerivation, base, base-prelude, bytestring, mtl, stdenv, text - , transformers - }: + ({ mkDerivation, base, bytestring, lib, mtl, text, transformers }: mkDerivation { pname = "binary-parser"; - version = "0.5.5"; - sha256 = "1dab718e06a978118cd28d2412bceaa0b6ec8d67785bdb0982e259fb60fe43b3"; - revision = "3"; - editedCabalFile = "14n41yazmks2qw0v4krxcqw3ac0wdy2z53d0qz0rdjcd94fpghjf"; - libraryHaskellDepends = [ - base base-prelude bytestring mtl text transformers - ]; + version = "0.5.7"; + sha256 = "9fa1471cc7e58806178293a4613edce5c19ae223431404669f6acf42bcec880f"; + libraryHaskellDepends = [ base bytestring mtl text transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nikita-volkov/binary-parser"; description = "A highly-efficient but limited parser API specialised for bytestrings"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "binary-parsers" = callPackage - ({ mkDerivation, base, binary, bytestring, bytestring-lexing - , scientific, stdenv + ({ mkDerivation, base, binary, bytestring, bytestring-lexing, lib + , scientific }: mkDerivation { pname = "binary-parsers"; - version = "0.2.3.0"; - sha256 = "bc6195493b950efcbeb9ef54dfe47a6badf894dff934cf02a4b170331c1b217a"; - revision = "1"; - editedCabalFile = "09ag18yr1m26fl3w7ab1d5q5j201ygbw7qsbsy41bwd6iq87rq15"; + version = "0.2.4.0"; + sha256 = "d193d3d3dca259e7299fb2c44cdd95b0a3e1bf54363ce4a9f6cda63b654bb9ca"; libraryHaskellDepends = [ base binary bytestring bytestring-lexing scientific ]; @@ -4933,23 +5545,22 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/winterland1989/binary-parsers"; description = "Extends binary with parsec/attoparsec style parsing combinators"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "binary-search" = callPackage - ({ mkDerivation, base, containers, stdenv, transformers }: + ({ mkDerivation, base, containers, lib, transformers }: mkDerivation { pname = "binary-search"; - version = "1.0.0.3"; - sha256 = "b0e32df46aeddceac57bd6afa940f84f275f82fb251479e10fadd7c14414f6fa"; + version = "2.0.0"; + sha256 = "67bf99ab64354d1dc8d1dc1108fbf4ffe6f9c13d0e329ff2ca64a2e2164fb78d"; libraryHaskellDepends = [ base containers transformers ]; doHaddock = false; doCheck = false; description = "Binary and exponential searches"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "binary-shared" = callPackage - ({ mkDerivation, base, binary, bytestring, containers, mtl, stdenv - }: + ({ mkDerivation, base, binary, bytestring, containers, lib, mtl }: mkDerivation { pname = "binary-shared"; version = "0.8.3"; @@ -4962,29 +5573,26 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; license = "GPL"; }) {}; "binary-tagged" = callPackage - ({ mkDerivation, aeson, array, base, base16-bytestring, binary - , bytestring, containers, generics-sop, hashable, scientific, SHA - , stdenv, tagged, text, time, unordered-containers, vector + ({ mkDerivation, array, base, base16-bytestring, binary, bytestring + , containers, lib, structured, tagged }: mkDerivation { pname = "binary-tagged"; - version = "0.1.5.1"; - sha256 = "70cb8fff540937f1d9753a71e0343039ee1718a0f029d4df698164b04fd5d5a4"; - revision = "1"; - editedCabalFile = "1z612d3wbrlywcx96lc52svi9b2s6nskdnwnwm3d5mylcqaqckcx"; + version = "0.3"; + sha256 = "5a3f37504277cc039f9022e6a86a51a691119f673c0f31e95827f72e1be47faf"; + revision = "2"; + editedCabalFile = "0h397jzajqiw01nf7fkjmqzsmzd08d1z6f9ff2rvcj4s6wsqkik8"; libraryHaskellDepends = [ - aeson array base base16-bytestring binary bytestring containers - generics-sop hashable scientific SHA tagged text time - unordered-containers vector + array base base16-bytestring binary bytestring containers + structured tagged ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/phadej/binary-tagged#readme"; description = "Tagged binary serialisation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "bindings-DSL" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "bindings-DSL"; version = "1.0.25"; @@ -4994,17 +5602,16 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doCheck = false; homepage = "https://github.com/jwiegley/bindings-dsl/wiki"; description = "FFI domain specific language, on top of hsc2hs"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "bindings-GLFW" = callPackage - ({ mkDerivation, base, bindings-DSL, libGL, libX11, libXcursor + ({ mkDerivation, base, bindings-DSL, lib, libGL, libX11, libXcursor , libXext, libXfixes, libXi, libXinerama, libXrandr, libXxf86vm - , stdenv }: mkDerivation { pname = "bindings-GLFW"; - version = "3.2.1.1"; - sha256 = "6b24c66b20ebfd8ff2e4ac32e3b435889bba0a32477598ba69fc7adc9608160e"; + version = "3.3.2.0"; + sha256 = "7c3509eb1aad7065f8442b0ea3fd588d3c524e25bb36985b3a7319bf97c73b3b"; libraryHaskellDepends = [ base bindings-DSL ]; librarySystemDepends = [ libGL libX11 libXcursor libXext libXfixes libXi libXinerama @@ -5013,11 +5620,11 @@ inherit (pkgs.xorg) libXinerama; inherit (pkgs.xorg) libXrender;}; doHaddock = false; doCheck = false; description = "Low-level bindings to GLFW OpenGL library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) libGL; inherit (pkgs.xorg) libXext; inherit (pkgs.xorg) libXfixes;}; "bindings-libzip" = callPackage - ({ mkDerivation, base, bindings-DSL, libzip, stdenv }: + ({ mkDerivation, base, bindings-DSL, lib, libzip }: mkDerivation { pname = "bindings-libzip"; version = "1.0.1"; @@ -5028,10 +5635,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://bitbucket.org/astanin/hs-libzip/"; description = "Low level bindings to libzip"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) libzip;}; "bindings-uname" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "bindings-uname"; version = "0.1"; @@ -5040,17 +5647,17 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Low-level binding to POSIX uname(3)"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "bins" = callPackage ({ mkDerivation, base, containers, finite-typelits - , ghc-typelits-knownnat, ghc-typelits-natnormalise, math-functions - , profunctors, reflection, stdenv, tagged, vector-sized + , ghc-typelits-knownnat, ghc-typelits-natnormalise, lib + , math-functions, profunctors, reflection, tagged, vector-sized }: mkDerivation { pname = "bins"; - version = "0.1.1.1"; - sha256 = "28739d05b7946d6237426294a9ded16d99d674f307cf25ac2482bc52ef2da8ec"; + version = "0.1.2.0"; + sha256 = "8a83fe1b836f7455b060becafa19c625a3f35bc2576295d163a81dbe91bbff0e"; libraryHaskellDepends = [ base containers finite-typelits ghc-typelits-knownnat ghc-typelits-natnormalise math-functions profunctors reflection @@ -5060,25 +5667,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/mstksg/bins#readme"; description = "Aggregate continuous values into discrete bins"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "bit-stream" = callPackage - ({ mkDerivation, base, ghc-prim, stdenv, vector }: - mkDerivation { - pname = "bit-stream"; - version = "0.1.0.2"; - sha256 = "811f2e7d4a827440bc21557e48c5310fe91e1b17f337ec35208546e1c5639bf4"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ base ghc-prim vector ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/Bodigrim/bit-stream#readme"; - description = "Lazy, infinite, compact stream of Bool with O(1) indexing"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "bitarray" = callPackage - ({ mkDerivation, array, base, stdenv }: + ({ mkDerivation, array, base, lib }: mkDerivation { pname = "bitarray"; version = "0.0.1.1"; @@ -5090,165 +5682,155 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://code.haskell.org/~bkomuves/"; description = "Mutable and immutable bit arrays"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "bitcoin-block" = callPackage - ({ mkDerivation, base, binary, bitcoin-tx, bitcoin-types - , bytestring, cryptohash, hexstring, largeword, lens, stdenv - }: + "bits" = callPackage + ({ mkDerivation, base, bytes, lib, mtl, transformers }: mkDerivation { - pname = "bitcoin-block"; - version = "0.13.1"; - sha256 = "d7f57c0fe71045dab85d223dc15d64db3a15cc7fd8446bfe4ebd98cd9d417d5a"; - enableSeparateDataOutput = true; - libraryHaskellDepends = [ - base binary bitcoin-tx bitcoin-types bytestring cryptohash - hexstring largeword lens - ]; + pname = "bits"; + version = "0.5.3"; + sha256 = "007bab52090b95a87a501406f4949904174ab431912d7b327c6fdb328ca86c2b"; + libraryHaskellDepends = [ base bytes mtl transformers ]; doHaddock = false; doCheck = false; - homepage = "http://www.leonmergen.com/opensource.html"; - description = "Utility functions for manipulating bitcoin blocks"; - license = stdenv.lib.licenses.mit; + homepage = "http://github.com/ekmett/bits"; + description = "Various bit twiddling and bitwise serialization primitives"; + license = lib.licenses.bsd3; }) {}; - "bitcoin-script" = callPackage - ({ mkDerivation, base, base16-bytestring, binary, bytestring - , stdenv, text - }: + "bits-extra" = callPackage + ({ mkDerivation, base, ghc-prim, lib, vector }: mkDerivation { - pname = "bitcoin-script"; - version = "0.11.1"; - sha256 = "398c1d86e918731b5b2026351bb3b0b90b20606517e7c21e42f05d6c6e197b4c"; - enableSeparateDataOutput = true; - libraryHaskellDepends = [ - base base16-bytestring binary bytestring text - ]; + pname = "bits-extra"; + version = "0.0.2.0"; + sha256 = "2e8839d77e60a5684e57024d8baa3046d183f9b96c233647eaecdb381100a4b0"; + revision = "2"; + editedCabalFile = "01qlnzbc3kgbyacqg9c7ldab2s91h9s4kalld0wz9q2k1d4063lv"; + libraryHaskellDepends = [ base ghc-prim vector ]; doHaddock = false; doCheck = false; - homepage = "http://www.leonmergen.com/opensource.html"; - description = "Compilation, manipulation and decompilation of Bitcoin scripts"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/haskell-works/bits-extra#readme"; + description = "Useful bitwise operations"; + license = lib.licenses.bsd3; }) {}; - "bitcoin-tx" = callPackage - ({ mkDerivation, base, binary, bitcoin-script, bitcoin-types - , bytestring, cryptohash, hexstring, lens, stdenv + "bitset-word8" = callPackage + ({ mkDerivation, base, containers, lib, template-haskell + , th-lift-instances }: mkDerivation { - pname = "bitcoin-tx"; - version = "0.13.1"; - sha256 = "3bb88265353066c394e96a56b2dc555fa13d37ca7f820978b793196c6829cc00"; - enableSeparateDataOutput = true; + pname = "bitset-word8"; + version = "0.1.1.2"; + sha256 = "f246d88f84a5ddc352fd47468834ec5513aa23f8a5963b74d202f32f2b9d5d19"; libraryHaskellDepends = [ - base binary bitcoin-script bitcoin-types bytestring cryptohash - hexstring lens + base containers template-haskell th-lift-instances ]; doHaddock = false; doCheck = false; - homepage = "http://www.leonmergen.com/opensource.html"; - description = "Utility functions for manipulating bitcoin transactions"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/nshimaza/bitset-word8#readme"; + description = "Space efficient set of Word8 and some pre-canned sets useful for parsing HTTP"; + license = lib.licenses.mit; }) {}; - "bitcoin-types" = callPackage - ({ mkDerivation, base, base58string, binary, bytestring, hexstring - , stdenv, text + "bitvec" = callPackage + ({ mkDerivation, base, bytestring, deepseq, ghc-prim, integer-gmp + , lib, primitive, vector }: mkDerivation { - pname = "bitcoin-types"; - version = "0.9.2"; - sha256 = "b72f9448508b64706d5f443748dc9b8abde8e749959187ce3d8356cde0d6c40b"; - enableSeparateDataOutput = true; + pname = "bitvec"; + version = "1.1.1.0"; + sha256 = "db8f3d0a95cba508719a3a6ec2fd099e2d2813d00a17923a9546bc147a6fa218"; libraryHaskellDepends = [ - base base58string binary bytestring hexstring text + base bytestring deepseq ghc-prim integer-gmp primitive vector ]; doHaddock = false; doCheck = false; - homepage = "http://www.leonmergen.com/opensource.html"; - description = "Provides consistent low-level types used commonly among Bitcoin implementations"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/Bodigrim/bitvec"; + description = "Space-efficient bit vectors"; + license = lib.licenses.bsd3; }) {}; - "bits" = callPackage - ({ mkDerivation, base, bytes, Cabal, cabal-doctest, mtl, stdenv - , transformers + "bitwise-enum" = callPackage + ({ mkDerivation, aeson, array, base, deepseq, lib, mono-traversable + , vector }: mkDerivation { - pname = "bits"; - version = "0.5.1"; - sha256 = "657e557bb913b53fb3b3fc7eda820cf3c85a5b89692d242275d3e8e8d9479c93"; - revision = "5"; - editedCabalFile = "012qycmsfz5l6y82d3zgjmp1k3pgvhlpjdk6rwlpc1wlfbpdqiaw"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; - libraryHaskellDepends = [ base bytes mtl transformers ]; + pname = "bitwise-enum"; + version = "1.0.1.0"; + sha256 = "3ff86390a241f2c9512469b6e640823b6addf0750d574bf4598af7aa19caad6e"; + libraryHaskellDepends = [ + aeson array base deepseq mono-traversable vector + ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/ekmett/bits"; - description = "Various bit twiddling and bitwise serialization primitives"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/jnbooth/bitwise-enum"; + description = "Bitwise operations on bounded enumerations"; + license = lib.licenses.bsd3; }) {}; - "bits-extra" = callPackage - ({ mkDerivation, base, ghc-prim, stdenv, vector }: + "blake2" = callPackage + ({ mkDerivation, base, bytestring, lib }: mkDerivation { - pname = "bits-extra"; - version = "0.0.1.3"; - sha256 = "692b08b3e9a490f5b2776b8f20277320fad247d9c4ea158225fee0f27f91afed"; - libraryHaskellDepends = [ base ghc-prim vector ]; + pname = "blake2"; + version = "0.3.0"; + sha256 = "3b5ab376b87f481f2245f62734071a0e4a80b8ba9cd0cc67a407dd36f23c2379"; + libraryHaskellDepends = [ base bytestring ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/haskell-works/bits-extra#readme"; - description = "Useful bitwise operations"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/centromere/blake2"; + description = "A library providing BLAKE2"; + license = lib.licenses.publicDomain; }) {}; - "bitset-word8" = callPackage - ({ mkDerivation, base, containers, stdenv, template-haskell - , th-lift-instances + "blanks" = callPackage + ({ mkDerivation, adjunctions, base, containers, deepseq + , distributive, lib, mtl }: mkDerivation { - pname = "bitset-word8"; - version = "0.1.1.1"; - sha256 = "ffc0f8508049717192021dabcfe77d65f604cbe107da6b8b76d45b891dbe52de"; + pname = "blanks"; + version = "0.5.0"; + sha256 = "0eaffedda239ef8f3d41313abb830f335d5fd524bb24e611867ffe62266768a8"; libraryHaskellDepends = [ - base containers template-haskell th-lift-instances + adjunctions base containers deepseq distributive mtl ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/nshimaza/bitset-word8#readme"; - description = "Space efficient set of Word8 and some pre-canned sets useful for parsing HTTP"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/ejconlon/blanks#readme"; + description = "Fill-in-the-blanks - A library factoring out substitution from ASTs"; + license = lib.licenses.bsd3; }) {}; - "bitx-bitcoin" = callPackage - ({ mkDerivation, aeson, base, bytestring, deepseq, exceptions - , http-client, http-client-tls, http-types, microlens, microlens-th - , network, QuickCheck, scientific, split, stdenv, text, time + "blas-carray" = callPackage + ({ mkDerivation, base, blas-ffi, carray, lib, netlib-carray + , netlib-ffi, storable-complex, transformers }: mkDerivation { - pname = "bitx-bitcoin"; - version = "0.12.0.0"; - sha256 = "31f2398bbb0deff80361fdabb108c1552ae097b15a44c6ca6674977ae735c871"; + pname = "blas-carray"; + version = "0.1.0.1"; + sha256 = "f4bd1f0d73707ea92992ad18fdea6998ebca2681d76cfde577df67f61f8717ab"; libraryHaskellDepends = [ - aeson base bytestring deepseq exceptions http-client - http-client-tls http-types microlens microlens-th network - QuickCheck scientific split text time + base blas-ffi carray netlib-carray netlib-ffi storable-complex + transformers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/tebello-thejane/bitx.hs"; - description = "A Haskell library for working with the BitX bitcoin exchange"; - license = stdenv.lib.licenses.bsd3; + homepage = "http://hub.darcs.net/thielema/blas-carray/"; + description = "Auto-generated interface to Fortran BLAS via CArrays"; + license = lib.licenses.bsd3; }) {}; - "blake2" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + "blas-comfort-array" = callPackage + ({ mkDerivation, base, blas-ffi, comfort-array, lib + , netlib-comfort-array, netlib-ffi, storable-complex, transformers + }: mkDerivation { - pname = "blake2"; - version = "0.2.0"; - sha256 = "07d910e3f5c6e98f5a6b9d53dbe5f52506c3859b513bc7493b52552a28382cfc"; - libraryHaskellDepends = [ base bytestring ]; + pname = "blas-comfort-array"; + version = "0.0.0.2"; + sha256 = "a1cd40064f00c8d5c0dccb0fccaf8a61bb946f7cbbaf8e1ae008ac7b0b483cd9"; + libraryHaskellDepends = [ + base blas-ffi comfort-array netlib-comfort-array netlib-ffi + storable-complex transformers + ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/centromere/blake2"; - description = "A library providing BLAKE2"; - license = stdenv.lib.licenses.publicDomain; + homepage = "http://hub.darcs.net/thielema/blas-comfort-array/"; + description = "Auto-generated interface to Fortran BLAS via comfort-array"; + license = lib.licenses.bsd3; }) {}; "blas-ffi" = callPackage - ({ mkDerivation, base, blas, netlib-ffi, stdenv }: + ({ mkDerivation, base, blas, lib, netlib-ffi }: mkDerivation { pname = "blas-ffi"; version = "0.1"; @@ -5261,24 +5843,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://hub.darcs.net/thielema/blas-ffi/"; description = "Auto-generated interface to Fortran BLAS"; - license = stdenv.lib.licenses.bsd3; - }) {inherit (pkgs) blas;}; - "blas-hs" = callPackage - ({ mkDerivation, base, blas, stdenv, storable-complex }: - mkDerivation { - pname = "blas-hs"; - version = "0.1.1.0"; - sha256 = "80e06b0927982b391d239f8656ed437cd29665969d1a078ea4e42a2bf196b086"; - libraryHaskellDepends = [ base storable-complex ]; - librarySystemDepends = [ blas ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/Rufflewind/blas-hs"; - description = "Low-level Haskell bindings to Blas"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.bsd3; }) {inherit (pkgs) blas;}; "blaze-bootstrap" = callPackage - ({ mkDerivation, base, blaze-html, stdenv, text }: + ({ mkDerivation, base, blaze-html, lib, text }: mkDerivation { pname = "blaze-bootstrap"; version = "0.1.0.1"; @@ -5288,46 +5856,31 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/agrafix/blaze-bootstrap"; description = "Blaze helper functions for bootstrap pages"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "blaze-builder" = callPackage - ({ mkDerivation, base, bytestring, deepseq, stdenv, text }: + ({ mkDerivation, base, bytestring, deepseq, lib, text }: mkDerivation { pname = "blaze-builder"; - version = "0.4.1.0"; - sha256 = "91fc8b966f3e9dc9461e1675c7566b881740f99abc906495491a3501630bc814"; + version = "0.4.2.1"; + sha256 = "6e6889bc9c3ff92062a17f3825dcc1b28510d261334d4d4e177232d904ea0b06"; libraryHaskellDepends = [ base bytestring deepseq text ]; doHaddock = false; doCheck = false; homepage = "http://github.com/lpsmith/blaze-builder"; description = "Efficient buffered output"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "blaze-colonnade" = callPackage - ({ mkDerivation, base, blaze-html, blaze-markup, colonnade, stdenv - , text - }: - mkDerivation { - pname = "blaze-colonnade"; - version = "1.2.2"; - sha256 = "1f2f7116ffea5ad2a04337b9bdc1277de0b12a71fb4b830b216c37911d8ea14c"; - libraryHaskellDepends = [ - base blaze-html blaze-markup colonnade text - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/andrewthad/colonnade#readme"; - description = "Helper functions for using blaze-html with colonnade"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "blaze-html" = callPackage - ({ mkDerivation, base, blaze-builder, blaze-markup, bytestring - , stdenv, text + ({ mkDerivation, base, blaze-builder, blaze-markup, bytestring, lib + , text }: mkDerivation { pname = "blaze-html"; - version = "0.9.1.1"; - sha256 = "ea0e944298dbbd692b41af4f15dbd1a1574aec7b8f91f38391d25106b143bb1b"; + version = "0.9.1.2"; + sha256 = "60503f42546c6c1b954014d188ea137e43d74dcffd2bf6157c113fd91a0c394c"; + revision = "1"; + editedCabalFile = "0wvlfb3rd9cm3p894p5rl9kggrsr5da3n8x9ydrbagx91yvkxns9"; libraryHaskellDepends = [ base blaze-builder blaze-markup bytestring text ]; @@ -5335,25 +5888,23 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://jaspervdj.be/blaze"; description = "A blazingly fast HTML combinator library for Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "blaze-markup" = callPackage - ({ mkDerivation, base, blaze-builder, bytestring, stdenv, text }: + ({ mkDerivation, base, blaze-builder, bytestring, lib, text }: mkDerivation { pname = "blaze-markup"; - version = "0.8.2.2"; - sha256 = "c6f0cf8fd707ba8c0b700e0c5ad6a1212c8b57d46a9cbdfb904d8bf585ad82e1"; - revision = "1"; - editedCabalFile = "0ivspcxz0b2r7kcas5hlw0fh92883r8ghwz9lck7nyqn6wn5i8zx"; + version = "0.8.2.8"; + sha256 = "43fc3f6872dc8d1be8d0fe091bd4775139b42179987f33d6490a7c5f1e07a349"; libraryHaskellDepends = [ base blaze-builder bytestring text ]; doHaddock = false; doCheck = false; homepage = "http://jaspervdj.be/blaze"; description = "A blazingly fast markup combinator library for Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "blaze-svg" = callPackage - ({ mkDerivation, base, blaze-markup, mtl, stdenv }: + ({ mkDerivation, base, blaze-markup, lib, mtl }: mkDerivation { pname = "blaze-svg"; version = "0.3.6.1"; @@ -5363,11 +5914,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/deepakjois/blaze-svg"; description = "SVG combinator library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "blaze-textual" = callPackage ({ mkDerivation, base, blaze-builder, bytestring, ghc-prim - , integer-gmp, old-locale, stdenv, text, time, vector + , integer-gmp, lib, old-locale, text, time, vector }: mkDerivation { pname = "blaze-textual"; @@ -5381,10 +5932,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/bos/blaze-textual"; description = "Fast rendering of common datatypes"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "bmp" = callPackage - ({ mkDerivation, base, binary, bytestring, stdenv }: + ({ mkDerivation, base, binary, bytestring, lib }: mkDerivation { pname = "bmp"; version = "1.2.6.3"; @@ -5394,28 +5945,38 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/benl23x5/bmp"; description = "Read and write uncompressed BMP image files"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "bno055-haskell" = callPackage - ({ mkDerivation, base, bytestring, cereal, h2c, mtl, resourcet - , stdenv + "board-games" = callPackage + ({ mkDerivation, array, base, cgi, containers, enummapset, html + , httpd-shed, lib, network-uri, non-empty, QuickCheck, random + , transformers, utility-ht }: mkDerivation { - pname = "bno055-haskell"; - version = "0.1.0"; - sha256 = "7adc29f94755047b4214115c23b63041e9d3970d2648f53dcd38b84725059ad8"; + pname = "board-games"; + version = "0.3"; + sha256 = "a77bcfe67d4c83ab0b15f1fdbed553d786416a83d2ba9bdb023b4840fd8a9cfa"; + revision = "1"; + editedCabalFile = "0rb5bqjg6r8p2v2wfdhivsbgbn55acdjsj6hcy6bv5w50qmg1l6c"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - base bytestring cereal h2c mtl resourcet + array base cgi containers enummapset html non-empty QuickCheck + random transformers utility-ht + ]; + executableHaskellDepends = [ + array base cgi containers html httpd-shed network-uri non-empty + random transformers utility-ht ]; doHaddock = false; doCheck = false; - homepage = "https://bitbucket.org/fmapE/bno055-haskell"; - description = "Library for communication with the Bosch BNO055 orientation sensor"; - license = stdenv.lib.licenses.mit; + homepage = "http://code.haskell.org/~thielema/games/"; + description = "Three games for inclusion in a web server"; + license = "GPL"; }) {}; "boltzmann-samplers" = callPackage ({ mkDerivation, ad, base, containers, hashable, hmatrix, ieee754 - , MonadRandom, mtl, QuickCheck, stdenv, transformers + , lib, MonadRandom, mtl, QuickCheck, transformers , unordered-containers, vector }: mkDerivation { @@ -5430,11 +5991,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/Lysxia/boltzmann-samplers#readme"; description = "Uniform random generators"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "boolean-like" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, containers - , semigroups, stdenv, text, vector + ({ mkDerivation, attoparsec, base, bytestring, containers, lib + , semigroups, text, vector }: mkDerivation { pname = "boolean-like"; @@ -5447,24 +6008,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/Shou/boolean-like"; description = "Logical combinatory operations dealing with datatypes representing booleans by their constructors"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "boolean-normal-forms" = callPackage - ({ mkDerivation, base, cond, containers, deepseq, stdenv }: - mkDerivation { - pname = "boolean-normal-forms"; - version = "0.0.1"; - sha256 = "8b90942bcbda0c761e683931bd813613f3819f804f02fed115f89dbdb292208a"; - revision = "1"; - editedCabalFile = "1p31kqxp77xdhkszppmnzqgxp883vasrh5910qfif50lch39myfm"; - libraryHaskellDepends = [ base cond containers deepseq ]; - doHaddock = false; - doCheck = false; - description = "Boolean normal form: NNF, DNF & CNF"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.bsd3; }) {}; "boolsimplifier" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "boolsimplifier"; version = "0.1.8"; @@ -5475,10 +6022,23 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Simplification tools for simple propositional formulas"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "boots" = callPackage + ({ mkDerivation, base, exceptions, lib, mtl }: + mkDerivation { + pname = "boots"; + version = "0.2.0.1"; + sha256 = "1c5d8bdaba7800e0c85c7d75fc7fe65f51129008aff4fae0c88adb721339b011"; + libraryHaskellDepends = [ base exceptions mtl ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/leptonyu/boots#readme"; + description = "IoC Monad in Haskell"; + license = lib.licenses.mit; }) {}; "bordacount" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "bordacount"; version = "0.1.0.0"; @@ -5488,67 +6048,69 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/hverr/bordacount#readme"; description = "Implementation of the Borda count election method"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "boring" = callPackage - ({ mkDerivation, adjunctions, base, base-compat, constraints, fin - , generics-sop, stdenv, streams, tagged, transformers - , transformers-compat, vec - }: + ({ mkDerivation, base, lib, tagged, transformers }: mkDerivation { pname = "boring"; - version = "0.1"; - sha256 = "73d60829c3a789f3d377d56ce7844aaaea6b517bcea43e06579ab785181b4664"; - revision = "2"; - editedCabalFile = "1jxaby4cagbhii194x9x0j75ms1v5bm14sx7d19zz3844mh9qyci"; - libraryHaskellDepends = [ - adjunctions base base-compat constraints fin generics-sop streams - tagged transformers transformers-compat vec - ]; + version = "0.2"; + sha256 = "0bac533b66e754d4fc65ab8d7557eea6f7b35d16998e5e74579b25a372aa4c34"; + libraryHaskellDepends = [ base tagged transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/phadej/boring"; description = "Boring and Absurd types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "both" = callPackage - ({ mkDerivation, base, semigroups, stdenv, zero }: + ({ mkDerivation, base, lib, semigroups, zero }: mkDerivation { pname = "both"; - version = "0.1.1.0"; - sha256 = "6f4ee8b7745fb3054282240fe941dd74cf2481f1a07b170d211c2b8791340e8e"; + version = "0.1.1.1"; + sha256 = "b69ff74cdaa375f32dfc7a1d841a6249d577f6b537a73aeb7baf5d1740fab84d"; libraryHaskellDepends = [ base semigroups zero ]; doHaddock = false; doCheck = false; homepage = "https://github.com/barrucadu/both"; description = "Like Maybe, but with a different Monoid instance"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "bound" = callPackage - ({ mkDerivation, base, bifunctors, binary, bytes, Cabal - , cabal-doctest, cereal, comonad, deepseq, hashable, mmorph - , profunctors, stdenv, template-haskell, transformers - , transformers-compat + ({ mkDerivation, base, bifunctors, binary, bytes, cereal, comonad + , deepseq, hashable, lib, mmorph, profunctors, template-haskell + , th-abstraction, transformers, transformers-compat }: mkDerivation { pname = "bound"; - version = "2.0.1"; - sha256 = "294a206f33b6583e56bd3aad620e4a7bd0a22b4bf4c6fe5988b2fe55159fbb76"; - revision = "6"; - editedCabalFile = "18fqzxy3f8r09jwcsfzjlrpvnlz711jq5gcjp4dal1pvsbbw6i09"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "2.0.3"; + sha256 = "cf1fb168cedaba4768603dc97b4d5196b9d7c53b9c8729e00fa82b9dd2671766"; libraryHaskellDepends = [ base bifunctors binary bytes cereal comonad deepseq hashable mmorph - profunctors template-haskell transformers transformers-compat + profunctors template-haskell th-abstraction transformers + transformers-compat ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/bound/"; description = "Making de Bruijn Succ Less"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "bounded-queue" = callPackage + ({ mkDerivation, base, containers, deepseq, lib }: + mkDerivation { + pname = "bounded-queue"; + version = "1.0.0"; + sha256 = "ad7056ad562c19841bf5e8d911de3ce90df6d49ff83bf45d341bf0e97e9b54a2"; + libraryHaskellDepends = [ base containers deepseq ]; + doHaddock = false; + doCheck = false; + homepage = "https://gitlab.com/fosskers/bounded-queue"; + description = "A strict, immutable, thread-safe, single-ended, bounded queue"; + license = lib.licenses.bsd3; }) {}; "boundingboxes" = callPackage - ({ mkDerivation, base, lens, stdenv }: + ({ mkDerivation, base, lens, lib }: mkDerivation { pname = "boundingboxes"; version = "0.2.3"; @@ -5558,11 +6120,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/fumieval/boundingboxes"; description = "A generic boundingbox for an arbitrary vector"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "bower-json" = callPackage ({ mkDerivation, aeson, aeson-better-errors, base, bytestring - , deepseq, ghc-prim, mtl, scientific, stdenv, text, transformers + , deepseq, ghc-prim, lib, mtl, scientific, text, transformers , unordered-containers, vector }: mkDerivation { @@ -5577,10 +6139,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/hdgarrood/bower-json"; description = "Read bower.json from Haskell"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "boxes" = callPackage - ({ mkDerivation, base, split, stdenv }: + ({ mkDerivation, base, lib, split }: mkDerivation { pname = "boxes"; version = "0.1.5"; @@ -5589,54 +6151,89 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "2D text pretty-printing library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "brick" = callPackage + ({ mkDerivation, base, bytestring, config-ini, containers + , contravariant, data-clist, deepseq, directory, dlist, exceptions + , filepath, lib, microlens, microlens-mtl, microlens-th, random + , stm, template-haskell, text, text-zipper, transformers, unix + , vector, vty, word-wrap + }: + mkDerivation { + pname = "brick"; + version = "0.62"; + sha256 = "66c01767de1942cd4f11ce451b36e0e3bb17a1e0fc422883ee6363de7daae4b8"; + configureFlags = [ "-fdemos" ]; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base bytestring config-ini containers contravariant data-clist + deepseq directory dlist exceptions filepath microlens microlens-mtl + microlens-th stm template-haskell text text-zipper transformers + unix vector vty word-wrap + ]; + executableHaskellDepends = [ + base microlens microlens-th random text text-zipper vector vty + word-wrap + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jtdaugherty/brick/"; + description = "A declarative terminal user interface library"; + license = lib.licenses.bsd3; + }) {}; + "broadcast-chan" = callPackage + ({ mkDerivation, base, lib, transformers, unliftio-core }: + mkDerivation { + pname = "broadcast-chan"; + version = "0.2.1.1"; + sha256 = "2f47fa5a0b9a9b00913fb3a83b743c2d879f69d09f18c8d9197b3af8c43e2507"; + revision = "2"; + editedCabalFile = "0zpbfdgxs3b7wx2qgvrs5y01z8lzvww2b7bmyrg5cj6p5xznllk1"; + libraryHaskellDepends = [ base transformers unliftio-core ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/merijn/broadcast-chan"; + description = "Closable, fair, single-wakeup channel type that avoids 0 reader space leaks"; + license = lib.licenses.bsd3; }) {}; "bsb-http-chunked" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "bsb-http-chunked"; version = "0.0.0.4"; sha256 = "148309e23eb8b261c1de374712372d62d8c8dc8ee504c392809c7ec33c0a0e7c"; + revision = "3"; + editedCabalFile = "15hg352id2f4x0dnvv47bdiz6gv5hp5a2mki9yzmhc7ajpk31mdd"; libraryHaskellDepends = [ base bytestring ]; doHaddock = false; doCheck = false; homepage = "http://github.com/sjakobi/bsb-http-chunked"; description = "Chunked HTTP transfer encoding for bytestring builders"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "bson" = callPackage - ({ mkDerivation, base, binary, bytestring, cryptohash - , data-binary-ieee754, mtl, network, stdenv, text, time + ({ mkDerivation, base, binary, bytestring, cryptohash-md5 + , data-binary-ieee754, lib, mtl, network-bsd, text, time }: mkDerivation { pname = "bson"; - version = "0.3.2.7"; - sha256 = "27329dcd593fd7503e7cf6705c863ed5c76b2fc816342e194c79d5a1d4c87f2b"; + version = "0.4.0.1"; + sha256 = "6bc436f1671c19fbe3b56a52cf786a0f78f8a73a4b072af0aa006ce40286bdf6"; + configureFlags = [ "-f-_old-network" ]; libraryHaskellDepends = [ - base binary bytestring cryptohash data-binary-ieee754 mtl network - text time + base binary bytestring cryptohash-md5 data-binary-ieee754 mtl + network-bsd text time ]; doHaddock = false; doCheck = false; homepage = "http://github.com/mongodb-haskell/bson"; description = "BSON documents are JSON-like objects with a standard binary encoding"; - license = stdenv.lib.licenses.asl20; - }) {}; - "bson-lens" = callPackage - ({ mkDerivation, base, bson, lens, stdenv, text }: - mkDerivation { - pname = "bson-lens"; - version = "0.1.1"; - sha256 = "d73bb417def2d8cb1efebfc22482a859e119bcc4005dd10106c82dff5ceeb160"; - libraryHaskellDepends = [ base bson lens text ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/jb55/bson-lens"; - description = "BSON lenses"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.asl20; }) {}; "btrfs" = callPackage - ({ mkDerivation, base, bytestring, stdenv, time, unix }: + ({ mkDerivation, base, bytestring, lib, time, unix }: mkDerivation { pname = "btrfs"; version = "0.2.0.0"; @@ -5648,10 +6245,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/redneb/hs-btrfs"; description = "Bindings to the btrfs API"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "buffer-builder" = callPackage - ({ mkDerivation, base, bytestring, mtl, stdenv, text + ({ mkDerivation, base, bytestring, lib, mtl, text , unordered-containers, vector }: mkDerivation { @@ -5665,10 +6262,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/chadaustin/buffer-builder"; description = "Library for efficiently building up buffers, one piece at a time"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "buffer-pipe" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "buffer-pipe"; version = "0.0"; @@ -5679,18 +6276,18 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Read from stdin and write to stdout in large blocks"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "bugsnag-haskell" = callPackage ({ mkDerivation, aeson, base, bytestring, case-insensitive , containers, Glob, http-client, http-client-tls, http-conduit - , http-types, iproute, network, parsec, stdenv, template-haskell - , text, th-lift-instances, time, ua-parser, wai + , http-types, iproute, lib, network, parsec, template-haskell, text + , th-lift-instances, time, ua-parser, wai }: mkDerivation { pname = "bugsnag-haskell"; - version = "0.0.3.0"; - sha256 = "98258f64568d1898a70e5c3d8faaacfd1c06c3fa79f30e1c9abe3dba87c63cbc"; + version = "0.0.4.1"; + sha256 = "4eed5384ded56bbbf1937bd8a1f0f05aa9cdec6d9a4f92d56236410157305957"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -5702,46 +6299,111 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/pbrisbin/bugsnag-haskell#readme"; description = "Bugsnag error reporter for Haskell"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "bulletproofs" = callPackage - ({ mkDerivation, arithmoi, base, containers, cryptonite, memory - , MonadRandom, protolude, random-shuffle, stdenv, text + "bugsnag-hs" = callPackage + ({ mkDerivation, aeson, base, bytestring, http-client, lib, text + , time, unordered-containers }: mkDerivation { - pname = "bulletproofs"; - version = "0.4.0"; - sha256 = "6c6ea840f4d22e07bc0325dcbc6f41004b627e1868ddd13939fdd6105e41842b"; + pname = "bugsnag-hs"; + version = "0.2.0.4"; + sha256 = "694cb2770a92903dcf0f5ca72ef8ae278c35c119db7409467be9245e3748a3bc"; + enableSeparateDataOutput = true; libraryHaskellDepends = [ - arithmoi base containers cryptonite memory MonadRandom protolude - random-shuffle text + aeson base bytestring http-client text time unordered-containers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/adjoint-io/bulletproofs#readme"; - license = stdenv.lib.licenses.asl20; + homepage = "https://github.com/jwoudenberg/bugsnag-hs#readme"; + description = "A Bugsnag client for Haskell"; + license = lib.licenses.bsd3; }) {}; - "butter" = callPackage - ({ mkDerivation, aeson, base, bytestring, containers - , forkable-monad, free, HUnit, network-simple, stdenv, stm + "bugzilla-redhat" = callPackage + ({ mkDerivation, aeson, base, blaze-builder, bytestring, connection + , containers, http-conduit, http-types, iso8601-time, lib + , resourcet, text, time, transformers, unordered-containers, vector + }: + mkDerivation { + pname = "bugzilla-redhat"; + version = "0.3.2"; + sha256 = "b5aa9e859363b4116ebebda1b1e6adbaa835035dbff59d64379b4abf70155bb8"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson base blaze-builder bytestring connection containers + http-conduit http-types iso8601-time resourcet text time + transformers unordered-containers vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/juhp/hsbugzilla"; + description = "A Haskell interface to the Bugzilla native REST API"; + license = lib.licenses.bsd3; + }) {}; + "burrito" = callPackage + ({ mkDerivation, base, bytestring, containers, lib, parsec , template-haskell, text, transformers }: mkDerivation { - pname = "butter"; - version = "0.1.0.6"; - sha256 = "8640b2681a57c0bc545684c821e80a97d57fe14bc6036e9030dc4cc63c2e4164"; + pname = "burrito"; + version = "1.2.0.2"; + sha256 = "c56ac56a587bfd1a038623a33bfb078226ab181d0d709a10876617e8a5b2d834"; + libraryHaskellDepends = [ + base bytestring containers parsec template-haskell text + transformers + ]; + doHaddock = false; + doCheck = false; + description = "Parse and render URI templates"; + license = lib.licenses.isc; + }) {}; + "butcher" = callPackage + ({ mkDerivation, base, bifunctors, containers, deque, extra, free + , lib, microlens, microlens-th, mtl, multistate, pretty + , transformers, unsafe, void + }: + mkDerivation { + pname = "butcher"; + version = "1.3.3.2"; + sha256 = "1d0f8e8e498b012c4a859671eebf34a6e965e8ed99b3c90d3aad1d8898c40f1b"; + libraryHaskellDepends = [ + base bifunctors containers deque extra free microlens microlens-th + mtl multistate pretty transformers unsafe void + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/lspitzner/butcher/"; + description = "Chops a command or program invocation into digestable pieces"; + license = lib.licenses.bsd3; + }) {}; + "buttplug-hs-core" = callPackage + ({ mkDerivation, aeson, aeson-casing, async, base, bytestring + , connection, containers, lib, network, text, unordered-containers + , websockets, wuss + }: + mkDerivation { + pname = "buttplug-hs-core"; + version = "0.1.0.0"; + sha256 = "7ec880a79161ee71309a14d45e3dc100ca19cd39625fe7b7b4985c836188d12b"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - aeson base bytestring containers forkable-monad free HUnit - network-simple stm template-haskell text transformers + aeson aeson-casing base bytestring connection containers network + text unordered-containers websockets wuss + ]; + executableHaskellDepends = [ + aeson aeson-casing async base bytestring connection containers + network text unordered-containers websockets wuss ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/System-Indystress/Butter#readme"; - description = "Monad Transformer for Asyncronous Message Passing"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/sullyj3/buttplug-hs-core#readme"; + description = "Client library for buttplug.io"; + license = lib.licenses.bsd3; }) {}; "bv" = callPackage - ({ mkDerivation, base, ghc-prim, integer-gmp, stdenv }: + ({ mkDerivation, base, ghc-prim, integer-gmp, lib }: mkDerivation { pname = "bv"; version = "0.5"; @@ -5753,28 +6415,55 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/iagoabal/haskell-bv"; description = "Bit-vector arithmetic library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "bv-little" = callPackage - ({ mkDerivation, base, deepseq, hashable, integer-gmp - , mono-traversable, primitive, QuickCheck, stdenv + ({ mkDerivation, base, deepseq, hashable, integer-gmp, keys, lib + , mono-traversable, mono-traversable-keys, primitive, QuickCheck + , text-show }: mkDerivation { pname = "bv-little"; - version = "0.1.2"; - sha256 = "8c8d394050d154e100e29df7daf75235eb870aeb3946d8a68f58472e31c14c77"; + version = "1.1.1"; + sha256 = "d936b6eabc60706a2a0668ce88b7f0787feddbd82315b669a19eb1f9288e990c"; libraryHaskellDepends = [ - base deepseq hashable integer-gmp mono-traversable primitive - QuickCheck + base deepseq hashable integer-gmp keys mono-traversable + mono-traversable-keys primitive QuickCheck text-show ]; doHaddock = false; doCheck = false; homepage = "https://github.com/recursion-ninja/bv-little"; description = "Efficient little-endian bit vector library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "byte-count-reader" = callPackage + ({ mkDerivation, base, extra, lib, parsec, parsec-numbers, text }: + mkDerivation { + pname = "byte-count-reader"; + version = "0.10.1.3"; + sha256 = "00ea9c8ec8ab76e103e8c0263e148ede4e141ecf7b31dbfdcaad73392b7a02fc"; + libraryHaskellDepends = [ base extra parsec parsec-numbers text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/danielrolls/byte-count-reader#readme"; + description = "Read strings describing a number of bytes like 2Kb and 0.5 MiB"; + license = lib.licenses.gpl3Only; + }) {}; + "byte-order" = callPackage + ({ mkDerivation, base, lib, primitive, primitive-unaligned }: + mkDerivation { + pname = "byte-order"; + version = "0.1.2.0"; + sha256 = "bc103be34d25e70071a6bc1a65a7b42b9f078d2601e6ee590f66cf8a2b26d8da"; + libraryHaskellDepends = [ base primitive primitive-unaligned ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/andrewthad/byte-order"; + description = "Portable big-endian and little-endian conversions"; + license = lib.licenses.bsd3; }) {}; "byteable" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "byteable"; version = "0.1.1"; @@ -5785,10 +6474,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/vincenthz/hs-byteable"; description = "Type class for sequence of bytes"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "bytedump" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "bytedump"; version = "1.0"; @@ -5801,10 +6490,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/vincenthz/hs-bytedump"; description = "Flexible byte dump helpers for human readers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "byteorder" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "byteorder"; version = "1.0.4"; @@ -5814,31 +6503,30 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://community.haskell.org/~aslatter/code/byteorder"; description = "Exposes the native endianness or byte ordering of the system"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "bytes" = callPackage - ({ mkDerivation, base, binary, bytestring, Cabal, cabal-doctest - , cereal, containers, hashable, mtl, scientific, stdenv, text, time + ({ mkDerivation, base, binary, binary-orphans, bytestring, cereal + , containers, hashable, lib, mtl, scientific, text, time , transformers, transformers-compat, unordered-containers, void }: mkDerivation { pname = "bytes"; - version = "0.15.5"; - sha256 = "039935e6b367eb8657aa3eb109e719b257a06524b0d9ff5246e8029bb7a07118"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "0.17.1"; + sha256 = "3ae9b2f34c87419a81e8dbb01f329a7a99123f87649cda53751ca5b737d2b7e2"; libraryHaskellDepends = [ - base binary bytestring cereal containers hashable mtl scientific - text time transformers transformers-compat unordered-containers - void + base binary binary-orphans bytestring cereal containers hashable + mtl scientific text time transformers transformers-compat + unordered-containers void ]; doHaddock = false; doCheck = false; homepage = "https://github.com/ekmett/bytes"; description = "Sharing code for serialization between binary and cereal"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "byteset" = callPackage - ({ mkDerivation, base, binary, stdenv }: + ({ mkDerivation, base, binary, lib }: mkDerivation { pname = "byteset"; version = "0.1.1.0"; @@ -5849,10 +6537,10 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Set of bytes"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "bytestring-builder" = callPackage - ({ mkDerivation, base, bytestring, deepseq, stdenv }: + ({ mkDerivation, base, bytestring, deepseq, lib }: mkDerivation { pname = "bytestring-builder"; version = "0.10.8.2.0"; @@ -5861,11 +6549,11 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "The new bytestring builder, packaged outside of GHC"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "bytestring-conversion" = callPackage ({ mkDerivation, attoparsec, base, bytestring, case-insensitive - , double-conversion, stdenv, text + , double-conversion, lib, text }: mkDerivation { pname = "bytestring-conversion"; @@ -5880,77 +6568,113 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/twittner/bytestring-conversion/"; description = "Type-classes to convert values to and from ByteString"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "bytestring-lexing" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "bytestring-lexing"; version = "0.5.0.2"; sha256 = "01f9add3f25067a89c5ae9ab1f2fd8ab75ec9f386987ee0d83f73ec855b43f73"; + revision = "1"; + editedCabalFile = "0icnbv83h542vkmn51ykzc4w1g7nl4w6d6lj79909hnwr2g10616"; libraryHaskellDepends = [ base bytestring ]; doHaddock = false; doCheck = false; homepage = "http://code.haskell.org/~wren/"; description = "Parse and produce literals efficiently from strict or lazy bytestrings"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; + }) {}; + "bytestring-mmap" = callPackage + ({ mkDerivation, base, bytestring, lib, unix }: + mkDerivation { + pname = "bytestring-mmap"; + version = "0.2.2"; + sha256 = "7bbcaeeccec5cf448ba59c9ed4de95bcc47b11ae2b9bcddb6201decb88eb69af"; + libraryHaskellDepends = [ base bytestring unix ]; + doHaddock = false; + doCheck = false; + homepage = "http://code.haskell.org/~dons/code/bytestring-mmap/"; + description = "mmap support for strict ByteStrings"; + license = lib.licenses.bsd3; }) {}; "bytestring-strict-builder" = callPackage - ({ mkDerivation, base, base-prelude, bytestring, semigroups, stdenv - }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "bytestring-strict-builder"; - version = "0.4.5.1"; - sha256 = "1879edb56e530169f5c4a738fff46ac56faeb30f9ac3d59f1361183111a5c69e"; - revision = "1"; - editedCabalFile = "1snn8qb17maa76zji75i4yfz9x8ci16xp6zwg6kgwb33lf06imnd"; - libraryHaskellDepends = [ - base base-prelude bytestring semigroups - ]; + version = "0.4.5.4"; + sha256 = "84a1dcc426d77372d5f5a639615c2a0974aaa3b9c171702845f199b434ee50fa"; + libraryHaskellDepends = [ base bytestring ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nikita-volkov/bytestring-strict-builder"; description = "An efficient strict bytestring builder"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "bytestring-to-vector" = callPackage + ({ mkDerivation, base, bytestring, lib, vector }: + mkDerivation { + pname = "bytestring-to-vector"; + version = "0.3.0.1"; + sha256 = "ccfb5bdccd88a5be488acb291a5863d9026e109d2178e58d87948b43b519284a"; + libraryHaskellDepends = [ base bytestring vector ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/sheyll/bytestring-to-vector"; + description = "Convert between ByteString and Vector.Storable without copying"; + license = lib.licenses.bsd3; }) {}; "bytestring-tree-builder" = callPackage - ({ mkDerivation, base, base-prelude, bytestring, semigroups, stdenv - , text - }: + ({ mkDerivation, base, bytestring, lib, text }: mkDerivation { pname = "bytestring-tree-builder"; - version = "0.2.7.2"; - sha256 = "a12df2ef970eab34c7bb968ba1a157fb01e478cd9abada097fc3e4ec61b5020e"; - libraryHaskellDepends = [ - base base-prelude bytestring semigroups text - ]; + version = "0.2.7.9"; + sha256 = "cbdbfba5aa05a212ff26b7363f990b364d2e12633a3e7ca9c5182c138e28b552"; + libraryHaskellDepends = [ base bytestring text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nikita-volkov/bytestring-tree-builder"; description = "A very efficient ByteString builder implementation based on the binary tree"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "bz2" = callPackage + ({ mkDerivation, base, bytestring, c2hs, lib }: + mkDerivation { + pname = "bz2"; + version = "1.0.1.0"; + sha256 = "18bacc3f22ba4973d7f8f086a8ad53f2305a80a928890390b5e25de9da7353cf"; + configureFlags = [ "-f-with-bzlib" ]; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ base bytestring ]; + libraryToolDepends = [ c2hs ]; + doHaddock = false; + doCheck = false; + description = "Bindings to libbz2"; + license = lib.licenses.bsd3; }) {}; "bzlib" = callPackage - ({ mkDerivation, base, bytestring, bzip2, stdenv }: + ({ mkDerivation, base, bytestring, bzip2, lib }: mkDerivation { pname = "bzlib"; - version = "0.5.0.5"; - sha256 = "9ee7d0ac7461b330820af928c13c6668bf4fe3601f171c42432a85c33718017e"; + version = "0.5.1.0"; + sha256 = "ded9b3e000417a6c217b4bb05260488f2188050d138caaa6280ebeee794fa9d8"; + revision = "1"; + editedCabalFile = "0r9b9y5qlz9k8wdzb23jif9wgvxi7r652i9apwzdaq7g1l08i6ky"; libraryHaskellDepends = [ base bytestring ]; librarySystemDepends = [ bzip2 ]; doHaddock = false; doCheck = false; description = "Compression and decompression in the bzip2 format"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) bzip2;}; "bzlib-conduit" = callPackage ({ mkDerivation, base, bindings-DSL, bytestring, bzip2, conduit - , data-default-class, mtl, resourcet, stdenv + , data-default-class, lib, mtl, resourcet }: mkDerivation { pname = "bzlib-conduit"; - version = "0.3.0.1"; - sha256 = "43d811549f7fb0710e4895ad54f78418271579f7e27d75e3c3470b74b285a239"; + version = "0.3.0.2"; + sha256 = "eb2c732b3d4ab5f7b367c51eef845e597ade19da52c03ee11954d35b6cfc4128"; enableSeparateDataOutput = true; libraryHaskellDepends = [ base bindings-DSL bytestring conduit data-default-class mtl @@ -5961,16 +6685,57 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/snoyberg/bzlib-conduit#readme"; description = "Streaming compression/decompression via conduits"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) bzip2;}; + "c-enum" = callPackage + ({ mkDerivation, base, lib, template-haskell }: + mkDerivation { + pname = "c-enum"; + version = "0.1.0.1"; + sha256 = "a06751d537eab043162756c2c2dc9e0e18a5e5be3319017a4c7a2a5e3f0ee0d5"; + libraryHaskellDepends = [ base template-haskell ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/YoshikuniJujo/c-enum#readme"; + description = "To make a type corresponding to an enum of C language"; + license = lib.licenses.bsd3; + }) {}; + "c-struct" = callPackage + ({ mkDerivation, array, base, lib, primitive, template-haskell }: + mkDerivation { + pname = "c-struct"; + version = "0.1.0.1"; + sha256 = "fc0724120fc845b51ea1a874d5d037d41847ec869819a996415a43f801586224"; + libraryHaskellDepends = [ array base primitive template-haskell ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/YoshikuniJujo/c-struct#readme"; + description = "To make a wrapper for struct of C language"; + license = lib.licenses.bsd3; + }) {}; + "c14n" = callPackage + ({ mkDerivation, base, bytestring, lib, libxml2 }: + mkDerivation { + pname = "c14n"; + version = "0.1.0.1"; + sha256 = "16544d106a48dbbf0b73ea9b2446a7ace603313da481f0c1177799dfb519af48"; + libraryHaskellDepends = [ base bytestring ]; + librarySystemDepends = [ libxml2 ]; + libraryPkgconfigDepends = [ libxml2 ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/mbg/c14n#readme"; + description = "Bindings to the c14n implementation in libxml"; + license = lib.licenses.mit; + }) {inherit (pkgs) libxml2;}; "c2hs" = callPackage ({ mkDerivation, array, base, bytestring, containers, directory - , dlist, filepath, language-c, pretty, process, stdenv + , dlist, filepath, language-c, lib, pretty, process }: mkDerivation { pname = "c2hs"; - version = "0.28.6"; - sha256 = "91dd121ac565009f2fc215c50f3365ed66705071a698a545e869041b5d7ff4da"; + version = "0.28.8"; + sha256 = "390632cffc561c32483af474aac50168a68f0fa382096552e37749923617884c"; isLibrary = false; isExecutable = true; enableSeparateDataOutput = true; @@ -5982,91 +6747,188 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/haskell/c2hs"; description = "C->Haskell FFI tool that gives some cross-language type safety"; - license = stdenv.lib.licenses.gpl2; + license = lib.licenses.gpl2Only; + }) {}; + "ca-province-codes" = callPackage + ({ mkDerivation, aeson, base, lib, text }: + mkDerivation { + pname = "ca-province-codes"; + version = "1.0.0.0"; + sha256 = "03e3427723546165237d5e27d1e24803ca6b7a5fd88a4e2a752bed812cae15d2"; + libraryHaskellDepends = [ aeson base text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/prikhi/ca-province-codes#readme"; + description = "ISO 3166-2:CA Province Codes and Names"; + license = lib.licenses.bsd3; + }) {}; + "cabal-appimage" = callPackage + ({ mkDerivation, base, Cabal, filepath, lib }: + mkDerivation { + pname = "cabal-appimage"; + version = "0.3.0.2"; + sha256 = "8da6b760be36e0369ce80f3aac021ee8bf099a464957fd3d63f8b84f3c5ad243"; + libraryHaskellDepends = [ base Cabal filepath ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/gbrsales/cabal-appimage"; + description = "Cabal support for creating AppImage applications"; + license = lib.licenses.agpl3Only; + }) {}; + "cabal-debian" = callPackage + ({ mkDerivation, ansi-wl-pprint, base, bifunctors, Cabal + , containers, data-default, debian, deepseq, Diff, directory + , exceptions, filepath, hsemail, HUnit, lens, lib, mtl, network-uri + , newtype-generics, optparse-applicative, parsec, pretty, process + , pureMD5, regex-tdfa, syb, text, unix, unliftio, utf8-string + }: + mkDerivation { + pname = "cabal-debian"; + version = "5.1"; + sha256 = "deeecce128a0bc36d8c88a100eb643ed898cb7bbb4115d014c959f1a8c167092"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + ansi-wl-pprint base bifunctors Cabal containers data-default debian + deepseq Diff directory exceptions filepath hsemail HUnit lens mtl + network-uri newtype-generics optparse-applicative parsec pretty + process pureMD5 regex-tdfa syb text unix unliftio utf8-string + ]; + executableHaskellDepends = [ base Cabal debian lens mtl pretty ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/clinty/cabal-debian"; + description = "Create a Debianization for a Cabal package"; + license = lib.licenses.bsd3; }) {}; "cabal-doctest" = callPackage - ({ mkDerivation, base, Cabal, directory, filepath, stdenv }: + ({ mkDerivation, base, Cabal, directory, filepath, lib }: mkDerivation { pname = "cabal-doctest"; - version = "1.0.6"; - sha256 = "decaaa5a73eaabaf3c4f8c644bd7f6e3f428b6244e935c0cf105f75f9b24ed2d"; + version = "1.0.8"; + sha256 = "2026a6a87d410202ce091412ca6bc33c5aca787025326b4a3d13425a23392e0e"; revision = "2"; - editedCabalFile = "1kbiwqm4fxrsdpcqijdq98h8wzmxydcvxd03f1z8dliqzyqsbd60"; + editedCabalFile = "05v1awad3d1wvc763xcgvxm4n6n7bs7byc6s14kdbw35zcaddlcb"; libraryHaskellDepends = [ base Cabal directory filepath ]; doHaddock = false; doCheck = false; homepage = "https://github.com/phadej/cabal-doctest"; description = "A Setup.hs helper for doctests running"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "cabal-install" = callPackage - ({ mkDerivation, array, async, base, base16-bytestring, binary - , bytestring, Cabal, containers, cryptohash-sha256, deepseq - , directory, echo, edit-distance, filepath, hackage-security - , hashable, HTTP, mtl, network, network-uri, parsec, pretty - , process, random, stdenv, stm, tar, text, time, unix, zip-archive - , zlib + license = lib.licenses.bsd3; + }) {}; + "cabal-file" = callPackage + ({ mkDerivation, base, bytestring, Cabal, directory, extra + , filepath, hackage-security, lib, optparse-applicative + , simple-cabal, simple-cmd, simple-cmd-args, time }: mkDerivation { - pname = "cabal-install"; - version = "2.4.1.0"; - sha256 = "69bcb2b54a064982412e1587c3c5c1b4fada3344b41b568aab25730034cb21ad"; - revision = "1"; - editedCabalFile = "0bm11hd3s07s1vsxdbkn5bgm5fz5bh1xdg91yz1fzr9d3b3ypa8p"; - configureFlags = [ "-f-native-dns" ]; + pname = "cabal-file"; + version = "0.1.1"; + sha256 = "cbae99e27635aa977dfcd0e7c858b9ab6529be97118822b7cd712f0b78804a17"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base bytestring Cabal directory extra filepath hackage-security + optparse-applicative simple-cabal simple-cmd time + ]; + executableHaskellDepends = [ + base bytestring Cabal directory extra filepath optparse-applicative + simple-cabal simple-cmd simple-cmd-args + ]; + doHaddock = false; + doCheck = false; + description = "Cabal file access"; + license = lib.licenses.bsd3; + }) {}; + "cabal-flatpak" = callPackage + ({ mkDerivation, aeson, aeson-pretty, base, bytestring, cabal-plan + , containers, cryptohash-sha256, http-client, http-client-tls + , http-types, lib, optparse-applicative, pathtype, shell-utility + , tar, text, utility-ht, zlib + }: + mkDerivation { + pname = "cabal-flatpak"; + version = "0.1.0.2"; + sha256 = "a478c4f875d530f31bdf363c32ae00eb0f3035f8dd6717089afde98c219dfec0"; + revision = "2"; + editedCabalFile = "0mf387hkxshcbss739c66j0hc1143r9lns3p3aw1l76as9lbdlwj"; isLibrary = false; isExecutable = true; - setupHaskellDepends = [ base Cabal filepath process ]; executableHaskellDepends = [ - array async base base16-bytestring binary bytestring Cabal - containers cryptohash-sha256 deepseq directory echo edit-distance - filepath hackage-security hashable HTTP mtl network network-uri - parsec pretty process random stm tar text time unix zip-archive + aeson aeson-pretty base bytestring cabal-plan containers + cryptohash-sha256 http-client http-client-tls http-types + optparse-applicative pathtype shell-utility tar text utility-ht zlib ]; doHaddock = false; doCheck = false; - postInstall = '' - mkdir $out/etc - mv bash-completion $out/etc/bash_completion.d - ''; - homepage = "http://www.haskell.org/cabal/"; - description = "The command-line interface for Cabal and Hackage"; - license = stdenv.lib.licenses.bsd3; + homepage = "http://hub.darcs.net/thielema/cabal-flatpak/"; + description = "Generate a FlatPak manifest from a Cabal package description"; + license = lib.licenses.bsd3; + }) {}; + "cabal-plan" = callPackage + ({ mkDerivation, aeson, ansi-terminal, async, base, base-compat + , base16-bytestring, bytestring, containers, directory, filepath + , lib, mtl, optics-core, optparse-applicative, parsec, process + , semialign, singleton-bool, text, these, topograph, transformers + , vector + }: + mkDerivation { + pname = "cabal-plan"; + version = "0.7.2.0"; + sha256 = "233a3d1460732fe3486169023758e431d37c5c9156fb28d829decaf7b9170f85"; + configureFlags = [ "-fexe" ]; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson base base16-bytestring bytestring containers directory + filepath text + ]; + executableHaskellDepends = [ + ansi-terminal async base base-compat bytestring containers + directory mtl optics-core optparse-applicative parsec process + semialign singleton-bool text these topograph transformers vector + ]; + doHaddock = false; + doCheck = false; + description = "Library and utility for processing cabal's plan.json file"; + license = lib.licenses.gpl2Plus; }) {}; "cabal-rpm" = callPackage - ({ mkDerivation, base, bytestring, Cabal, directory, filepath - , http-client, http-client-tls, http-conduit, process, simple-cmd - , stdenv, time, unix + ({ mkDerivation, base, bytestring, Cabal, directory, extra + , filepath, http-client, http-client-tls, http-conduit, lib + , optparse-applicative, process, simple-cabal, simple-cmd + , simple-cmd-args, time, unix }: mkDerivation { pname = "cabal-rpm"; - version = "0.12.6"; - sha256 = "da26117406caca76e85729b69c8ef573499b5fb1a816951aeb861fb4cf16c0cc"; + version = "2.0.9"; + sha256 = "9859c32a04c9ab70e611c410d738b4ecd006e45c6949d70bae5973126703cae4"; configureFlags = [ "-f-old-locale" ]; isLibrary = false; isExecutable = true; executableHaskellDepends = [ - base bytestring Cabal directory filepath http-client - http-client-tls http-conduit process simple-cmd time unix + base bytestring Cabal directory extra filepath http-client + http-client-tls http-conduit optparse-applicative process + simple-cabal simple-cmd simple-cmd-args time unix ]; doHaddock = false; doCheck = false; homepage = "https://github.com/juhp/cabal-rpm"; description = "RPM packaging tool for Haskell Cabal-based packages"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; }) {}; "cabal2nix" = callPackage ({ mkDerivation, aeson, ansi-wl-pprint, base, bytestring, Cabal , containers, deepseq, directory, distribution-nixpkgs, filepath - , hackage-db, hopenssl, hpack, language-nix, lens, monad-par + , hackage-db, hopenssl, hpack, language-nix, lens, lib, monad-par , monad-par-extras, mtl, optparse-applicative, pretty, process - , split, stdenv, text, time, transformers, yaml + , split, text, time, transformers, yaml }: mkDerivation { pname = "cabal2nix"; - version = "2.12"; - sha256 = "7b1cf2f4cdfa4a5c723993644e4827a1442f2420d88a2aa967b3314eba2aa87e"; + version = "2.17.0"; + sha256 = "959aa9a2ea54fa7b60b031cc2d3e923e47134a3f30d0439353ffdf07e7532179"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -6088,16 +6950,18 @@ inherit (pkgs.xorg) libXfixes;}; ''; homepage = "https://github.com/nixos/cabal2nix#readme"; description = "Convert Cabal files into Nix build instructions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cabal2spec" = callPackage - ({ mkDerivation, base, Cabal, filepath, optparse-applicative - , stdenv, time + ({ mkDerivation, base, Cabal, filepath, lib, optparse-applicative + , time }: mkDerivation { pname = "cabal2spec"; - version = "2.2.2"; - sha256 = "bc6b13682eec02d9a22d5696cd8a2bbf47f2eb60f678af6f444e63aa29f967e5"; + version = "2.6.2"; + sha256 = "3bb7e734b3ce90066a13fc27d483278a293769dd54351bbf3990d5325d003974"; + revision = "1"; + editedCabalFile = "196j1fga9cqlc0nbxbgl0c3g0ic8sf618whps95zzp58lac9dqak"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base Cabal filepath time ]; @@ -6108,16 +6972,16 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/peti/cabal2spec"; description = "Convert Cabal files into rpm spec files"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; }) {}; "cache" = callPackage - ({ mkDerivation, base, clock, hashable, stdenv, stm, transformers + ({ mkDerivation, base, clock, hashable, lib, stm, transformers , unordered-containers }: mkDerivation { pname = "cache"; - version = "0.1.1.1"; - sha256 = "1029991d52add00d7ea68cc03e7d87301cf23f644a0ffa8dbbaed91c9eb05f11"; + version = "0.1.3.0"; + sha256 = "42e9d9f040fab2fd5fc1095a901d6348de73342b1d14254bdaf6ca3d4f11e534"; libraryHaskellDepends = [ base clock hashable stm transformers unordered-containers ]; @@ -6125,39 +6989,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/hverr/haskell-cache#readme"; description = "An in-memory key/value store with expiration support"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "cachix-api" = callPackage - ({ mkDerivation, aeson, amazonka, base, base16-bytestring - , bytestring, conduit, cookie, cryptonite, http-api-data - , http-media, lens, memory, servant, servant-auth - , servant-auth-server, servant-auth-swagger, servant-streaming - , servant-swagger, servant-swagger-ui-core, stdenv, string-conv - , swagger2, text, transformers - }: - mkDerivation { - pname = "cachix-api"; - version = "0.1.0.3"; - sha256 = "aefd2d623cb8b0da0ac6861df37f2f5673659ebd341943e4da9c538befa84502"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - aeson amazonka base base16-bytestring bytestring conduit cookie - cryptonite http-api-data http-media lens memory servant - servant-auth servant-auth-server servant-auth-swagger - servant-streaming servant-swagger servant-swagger-ui-core - string-conv swagger2 text transformers - ]; - executableHaskellDepends = [ aeson base ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/cachix/cachix#readme"; - description = "Servant HTTP API specification for https://cachix.org"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.bsd3; }) {}; "cacophony" = callPackage ({ mkDerivation, base, bytestring, cryptonite, exceptions, free - , lens, memory, monad-coroutine, mtl, safe-exceptions, stdenv + , lens, lib, memory, monad-coroutine, mtl, safe-exceptions , transformers }: mkDerivation { @@ -6174,11 +7010,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/centromere/cacophony#readme"; description = "A library implementing the Noise protocol"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "calendar-recycling" = callPackage - ({ mkDerivation, base, containers, html, old-time, stdenv - , utility-ht + ({ mkDerivation, base, containers, html, lib, old-time, utility-ht }: mkDerivation { pname = "calendar-recycling"; @@ -6193,24 +7028,78 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://hub.darcs.net/thielema/calendar-recycling"; description = "List years with the same calendars"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "call-stack" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "call-stack"; - version = "0.1.0"; - sha256 = "f25f5e0992a39371079cc25c2a14b5abb872fa7d868a32753aac3a258b83b1e2"; + version = "0.3.0"; + sha256 = "b80e8de2b87f01922b23b328655ad2f843f42495f3e1033ae907aade603c716a"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/sol/call-stack#readme"; description = "Use GHC call-stacks in a backward compatible way"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "can-i-haz" = callPackage + ({ mkDerivation, base, lib, mtl }: + mkDerivation { + pname = "can-i-haz"; + version = "0.3.1.0"; + sha256 = "e857532b2d9a634cef07442b483c833696301d64f14cc49ed7a16dae6ea19c5f"; + libraryHaskellDepends = [ base mtl ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/0xd34df00d/can-i-haz#readme"; + description = "Generic implementation of the Has and CoHas patterns"; + license = lib.licenses.bsd3; + }) {}; + "capability" = callPackage + ({ mkDerivation, base, constraints, dlist, exceptions, generic-lens + , lens, lib, monad-control, monad-unlift, mtl, mutable-containers + , primitive, reflection, safe-exceptions, streaming, transformers + , unliftio, unliftio-core + }: + mkDerivation { + pname = "capability"; + version = "0.4.0.0"; + sha256 = "007b755143ca71e0b371a51db95c46ef4732ef68d8057271093320bbdddfb609"; + revision = "1"; + editedCabalFile = "0dqqry8qjx9gigz7x542zchrvjbmmhpafzn4fxf1dw0yd6hqavfq"; + libraryHaskellDepends = [ + base constraints dlist exceptions generic-lens lens monad-control + monad-unlift mtl mutable-containers primitive reflection + safe-exceptions streaming transformers unliftio unliftio-core + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/tweag/capability"; + description = "Extensional capabilities and deriving combinators"; + license = lib.licenses.bsd3; + }) {}; + "cardano-coin-selection" = callPackage + ({ mkDerivation, base, bytestring, containers, cryptonite, deepseq + , lib, quiet, text, transformers + }: + mkDerivation { + pname = "cardano-coin-selection"; + version = "1.0.1"; + sha256 = "4a6230041f9e274e97da0a5a3516fc3c9f1d5668b0141e24de046ff04a9b76db"; + libraryHaskellDepends = [ + base bytestring containers cryptonite deepseq quiet text + transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/input-output-hk/cardano-coin-selection#readme"; + description = "Algorithms for coin selection and fee balancing"; + license = lib.licenses.asl20; }) {}; "carray" = callPackage - ({ mkDerivation, array, base, binary, bytestring, ix-shapable - , QuickCheck, stdenv, syb + ({ mkDerivation, array, base, binary, bytestring, ix-shapable, lib + , QuickCheck, syb }: mkDerivation { pname = "carray"; @@ -6222,90 +7111,130 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "A C-compatible array library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "case-insensitive" = callPackage - ({ mkDerivation, base, bytestring, deepseq, hashable, stdenv, text + "casa-client" = callPackage + ({ mkDerivation, aeson, attoparsec, base, base16-bytestring + , bytestring, casa-types, conduit, conduit-extra, cryptonite + , exceptions, http-conduit, http-types, lib, memory, network-uri + , resourcet, template-haskell, text, th-lift, unliftio-core + , unordered-containers }: mkDerivation { - pname = "case-insensitive"; - version = "1.2.0.11"; - sha256 = "a7ce6d17e50caaa0f19ad8e67361499022860554c521b1e57993759da3eb37e3"; - libraryHaskellDepends = [ base bytestring deepseq hashable text ]; + pname = "casa-client"; + version = "0.0.1"; + sha256 = "5cee76485ad99ea998273c706596543e2b91ee3477a891cc8df2e6b5ce8414d1"; + libraryHaskellDepends = [ + aeson attoparsec base base16-bytestring bytestring casa-types + conduit conduit-extra cryptonite exceptions http-conduit http-types + memory network-uri resourcet template-haskell text th-lift + unliftio-core unordered-containers + ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/basvandijk/case-insensitive"; - description = "Case insensitive string comparison"; - license = stdenv.lib.licenses.bsd3; + description = "Client for Casa"; + license = lib.licenses.bsd3; }) {}; - "cased" = callPackage - ({ mkDerivation, base, stdenv, text }: + "casa-types" = callPackage + ({ mkDerivation, aeson, attoparsec, base, base16-bytestring + , bytestring, hashable, lib, path-pieces, persistent, text + }: mkDerivation { - pname = "cased"; - version = "0.1.0.0"; - sha256 = "8394e6705ed83152875e1de1c51c54c26b04a2359919d8958d66997b2b60ad23"; + pname = "casa-types"; + version = "0.0.2"; + sha256 = "6707dda387ce7a0ef71e21ddba251d161d047fb05a8c202bb6ef8264e0dd78b0"; + libraryHaskellDepends = [ + aeson attoparsec base base16-bytestring bytestring hashable + path-pieces persistent text + ]; + doHaddock = false; + doCheck = false; + description = "Types for Casa"; + license = lib.licenses.bsd3; + }) {}; + "case-insensitive" = callPackage + ({ mkDerivation, base, bytestring, deepseq, hashable, lib, text }: + mkDerivation { + pname = "case-insensitive"; + version = "1.2.1.0"; + sha256 = "296dc17e0c5f3dfb3d82ced83e4c9c44c338ecde749b278b6eae512f1d04e406"; + libraryHaskellDepends = [ base bytestring deepseq hashable text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/basvandijk/case-insensitive"; + description = "Case insensitive string comparison"; + license = lib.licenses.bsd3; + }) {}; + "cased" = callPackage + ({ mkDerivation, base, lib, text }: + mkDerivation { + pname = "cased"; + version = "0.1.0.0"; + sha256 = "8394e6705ed83152875e1de1c51c54c26b04a2359919d8958d66997b2b60ad23"; libraryHaskellDepends = [ base text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/jb55/cased"; description = "Track string casing in its type"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "cases" = callPackage - ({ mkDerivation, attoparsec, base-prelude, loch-th, stdenv, text }: + ({ mkDerivation, attoparsec, base, lib, text }: mkDerivation { pname = "cases"; - version = "0.1.3.2"; - sha256 = "9ecf632f7751aac2ed7ec93407f9499237316f2eb50f331bb4969abf3359a8a9"; - libraryHaskellDepends = [ attoparsec base-prelude loch-th text ]; + version = "0.1.4.1"; + sha256 = "1fd8db66dc82616b2f9fdeb6ff5c92e25586a7f2750c9999fa6b72273f267499"; + libraryHaskellDepends = [ attoparsec base text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nikita-volkov/cases"; description = "A converter for spinal, snake and camel cases"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "casing" = callPackage - ({ mkDerivation, base, split, stdenv }: + ({ mkDerivation, base, lib, split }: mkDerivation { pname = "casing"; - version = "0.1.4.0"; - sha256 = "8e8a3631ef5823ae53dfeb7497ad4856c6758e3e380ff164f6a261f41685f6d7"; + version = "0.1.4.1"; + sha256 = "106271c00246b551f2ef6a2e511437c9f0e1f3bb920a283f6f9eaa0940b4f8ca"; + revision = "1"; + editedCabalFile = "1n7w4w2icfppyvlmyzzmfivbx175ckqabs4my5qvvdvwlc89xrqb"; libraryHaskellDepends = [ base split ]; doHaddock = false; doCheck = false; description = "Convert between various source code casing conventions"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "cassava" = callPackage ({ mkDerivation, array, attoparsec, base, bytestring, containers - , deepseq, hashable, Only, scientific, stdenv, text, text-short - , unordered-containers, vector + , deepseq, hashable, lib, Only, scientific, text, text-short + , transformers, unordered-containers, vector }: mkDerivation { pname = "cassava"; - version = "0.5.1.0"; - sha256 = "762c8aaea2cdad61f52bad1b9f1f3b32764b4b6da03371aba6e5017f69614277"; - revision = "1"; - editedCabalFile = "1brz20js95synh0yw942ihy4y9y6nk4xnsqcjqi9580y24zcigkl"; + version = "0.5.2.0"; + sha256 = "b30d2ad5894519e364130c0510f167a4ffaf0e08a1e24c9a64238c855bfe0106"; + revision = "4"; + editedCabalFile = "19rkq41r5vj8drnj850b1wqnc54mxpw0x5z54brq0nvyww5f8ai8"; configureFlags = [ "-f-bytestring--lt-0_10_4" ]; libraryHaskellDepends = [ array attoparsec base bytestring containers deepseq hashable Only - scientific text text-short unordered-containers vector + scientific text text-short transformers unordered-containers vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/hvr/cassava"; description = "A CSV parsing and encoding library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cassava-conduit" = callPackage ({ mkDerivation, array, base, bifunctors, bytestring, cassava - , conduit, containers, mtl, stdenv, text + , conduit, containers, lib, mtl, text }: mkDerivation { pname = "cassava-conduit"; - version = "0.5.1"; - sha256 = "b55b72e9d52a40473f609c0c406db41bd92178a493f191295a7d8f23d89677f8"; + version = "0.6.0"; + sha256 = "406d1b6beb75b87a95a0f452f90d01970a392b88c9eba02f0c321fdf27588a84"; libraryHaskellDepends = [ array base bifunctors bytestring cassava conduit containers mtl text @@ -6314,16 +7243,16 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/domdere/cassava-conduit"; description = "Conduit interface for cassava package"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cassava-megaparsec" = callPackage - ({ mkDerivation, base, bytestring, cassava, megaparsec, stdenv + ({ mkDerivation, base, bytestring, cassava, lib, megaparsec , unordered-containers, vector }: mkDerivation { pname = "cassava-megaparsec"; - version = "2.0.0"; - sha256 = "cee6286a13a9884c3d725f3e7c57579b649fe7b850a5c898b9fdf637dddb904b"; + version = "2.0.2"; + sha256 = "4735aea6fce09caf4b42a319b72c6a507c72d14a88a14be753cde5a78421a10f"; libraryHaskellDepends = [ base bytestring cassava megaparsec unordered-containers vector ]; @@ -6331,28 +7260,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/stackbuilders/cassava-megaparsec"; description = "Megaparsec parser of CSV files that plays nicely with Cassava"; - license = stdenv.lib.licenses.mit; - }) {}; - "cassava-records" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, cassava, foldl - , stdenv, template-haskell, text, unordered-containers, vector - }: - mkDerivation { - pname = "cassava-records"; - version = "0.1.0.4"; - sha256 = "11f832c11125bd7a73b57941284d9aeb7f1e7572004da7e37311b34d3366af8d"; - libraryHaskellDepends = [ - attoparsec base bytestring cassava foldl template-haskell text - unordered-containers vector - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/gdevanla/cassava-records#readme"; - description = "Auto-generation of records data type"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; "cast" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "cast"; version = "0.1.0.2"; @@ -6362,29 +7273,29 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/haskell-patterns/cast#readme"; description = "Abstact cast pattern"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "category" = callPackage - ({ mkDerivation, alg, base, stdenv, transformers }: + ({ mkDerivation, alg, base, dual, lib, transformers }: mkDerivation { pname = "category"; - version = "0.2.2.0"; - sha256 = "2323558f9fd9b741815663ff69e090cadde4c2d5f7133b5edd8cbfdd658801a8"; - libraryHaskellDepends = [ alg base transformers ]; + version = "0.2.5.0"; + sha256 = "870b624395000ccfadb2ec5b739e6dc7d54c03ab2beaaac8ee2bfcb0063eca47"; + libraryHaskellDepends = [ alg base dual transformers ]; doHaddock = false; doCheck = false; description = "Categorical types and classes"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cayley-client" = callPackage ({ mkDerivation, aeson, attoparsec, base, binary, bytestring - , exceptions, http-client, http-conduit, lens, lens-aeson, mtl - , stdenv, text, transformers, unordered-containers, vector + , exceptions, http-client, http-conduit, lens, lens-aeson, lib, mtl + , text, transformers, unordered-containers, vector }: mkDerivation { pname = "cayley-client"; - version = "0.4.8"; - sha256 = "b1b1328fb855211a78b9c7da74eecc7ee81c9f92101debb9ca87238d66c01926"; + version = "0.4.15"; + sha256 = "2b7e6a5260a90d541c4c867dfdd6d31de803982f148f0dbc0defd3461e4279a2"; libraryHaskellDepends = [ aeson attoparsec base binary bytestring exceptions http-client http-conduit lens lens-aeson mtl text transformers @@ -6394,33 +7305,35 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/MichelBoucey/cayley-client"; description = "A Haskell client for the Cayley graph database"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cborg" = callPackage ({ mkDerivation, array, base, bytestring, containers, deepseq - , ghc-prim, half, integer-gmp, primitive, stdenv, text + , ghc-prim, half, integer-gmp, lib, primitive, text }: mkDerivation { pname = "cborg"; - version = "0.2.1.0"; - sha256 = "9198735f7645ae492345505448f790433f5fe407b19e1c6b2ec2a4c76bd97483"; + version = "0.2.5.0"; + sha256 = "ae17533937a03d5735a0be1f8d8db5e8647daaac85d414122bd4aebb5022aa21"; libraryHaskellDepends = [ array base bytestring containers deepseq ghc-prim half integer-gmp primitive text ]; doHaddock = false; doCheck = false; - description = "Concise Binary Object Representation"; - license = stdenv.lib.licenses.bsd3; + description = "Concise Binary Object Representation (CBOR)"; + license = lib.licenses.bsd3; }) {}; "cborg-json" = callPackage - ({ mkDerivation, aeson, aeson-pretty, base, cborg, scientific - , stdenv, text, unordered-containers, vector + ({ mkDerivation, aeson, aeson-pretty, base, cborg, lib, scientific + , text, unordered-containers, vector }: mkDerivation { pname = "cborg-json"; - version = "0.2.1.0"; - sha256 = "3fb6b54e6ddd322880689fb461f7911aca45b9758482c9f9949619c7d7b52006"; + version = "0.2.2.0"; + sha256 = "ab68a2457cb71a76699d7a8df07a880ea70c51d2c1a891b12669ca9ccfa7517b"; + revision = "3"; + editedCabalFile = "1sn2f9nfjcbr0n62n4kklbdi3pzpwrcy7ilg7m3v41nwrk53ifwy"; libraryHaskellDepends = [ aeson aeson-pretty base cborg scientific text unordered-containers vector @@ -6429,16 +7342,30 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/well-typed/cborg"; description = "A library for encoding JSON as CBOR"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "cdar-mBound" = callPackage + ({ mkDerivation, base, containers, deepseq, integer-gmp, lib }: + mkDerivation { + pname = "cdar-mBound"; + version = "0.1.0.4"; + sha256 = "d631ff7aa569dfab8e89601ca2109eed49a3bf16012b3400a87ec8edf689f9dc"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base containers deepseq integer-gmp ]; + executableHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + description = "Exact real arithmetic using Centred Dyadic Approximations"; + license = lib.licenses.bsd3; }) {}; "cereal" = callPackage - ({ mkDerivation, array, base, bytestring, containers, ghc-prim - , stdenv + ({ mkDerivation, array, base, bytestring, containers, ghc-prim, lib }: mkDerivation { pname = "cereal"; - version = "0.5.8.0"; - sha256 = "37d3668aba37babc83321aa1538841da041476b5423722e6f5210c4e5e014282"; + version = "0.5.8.1"; + sha256 = "2d9e88ac934b9ebc058097c72011ff59f3f146176310e1c957a0e4cf63681bd7"; libraryHaskellDepends = [ array base bytestring containers ghc-prim ]; @@ -6446,11 +7373,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/GaloisInc/cereal"; description = "A binary serialization library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cereal-conduit" = callPackage - ({ mkDerivation, base, bytestring, cereal, conduit, resourcet - , stdenv, transformers + ({ mkDerivation, base, bytestring, cereal, conduit, lib, resourcet + , transformers }: mkDerivation { pname = "cereal-conduit"; @@ -6465,10 +7392,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/snoyberg/conduit"; description = "Turn Data.Serialize Gets and Puts into Sources, Sinks, and Conduits"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cereal-text" = callPackage - ({ mkDerivation, base, cereal, stdenv, text }: + ({ mkDerivation, base, cereal, lib, text }: mkDerivation { pname = "cereal-text"; version = "0.1.0.2"; @@ -6478,22 +7405,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/ulikoehler/cereal-text"; description = "Data.Text instances for the cereal serialization library"; - license = stdenv.lib.licenses.asl20; - }) {}; - "cereal-time" = callPackage - ({ mkDerivation, base, cereal, stdenv, time }: - mkDerivation { - pname = "cereal-time"; - version = "0.1.0.0"; - sha256 = "bec6d5103ec45bee242825da4cf695f574f101bb1d48778bf7823175dfa43cb2"; - libraryHaskellDepends = [ base cereal time ]; - doHaddock = false; - doCheck = false; - description = "Serialize instances for types from `time` package"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.asl20; }) {}; "cereal-vector" = callPackage - ({ mkDerivation, base, bytestring, cereal, stdenv, vector }: + ({ mkDerivation, base, bytestring, cereal, lib, vector }: mkDerivation { pname = "cereal-vector"; version = "0.2.0.1"; @@ -6503,10 +7418,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/acfoltzer/cereal-vector"; description = "Serialize instances for Data.Vector types."; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cfenv" = callPackage - ({ mkDerivation, aeson, base, bytestring, containers, stdenv }: + ({ mkDerivation, aeson, base, bytestring, containers, lib }: mkDerivation { pname = "cfenv"; version = "0.1.0.0"; @@ -6516,30 +7431,30 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/tomphp/haskell-cfenv#readme"; description = "A library getting the environment when running on Cloud Foundry"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cgi" = callPackage - ({ mkDerivation, base, bytestring, containers, exceptions, mtl - , multipart, network, network-uri, parsec, stdenv, time, xhtml + ({ mkDerivation, base, bytestring, containers, exceptions, lib, mtl + , multipart, network-uri, parsec, time, xhtml }: mkDerivation { pname = "cgi"; - version = "3001.3.0.3"; - sha256 = "eb8144d7d0b74643c43b73c63e4d9fa88a110c4be719b9436917ca7d0d32b4e6"; - revision = "2"; - editedCabalFile = "082i8x8j8ry2nf7m99injh18sr9llbw66ck5ylqlyvh6bhwspa6b"; + version = "3001.5.0.0"; + sha256 = "0ad57acff9b981e44a3b049a2d3b26d924cfa035e4274e1dd1562b3c77ba9b27"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - base bytestring containers exceptions mtl multipart network - network-uri parsec time xhtml + base bytestring containers exceptions mtl multipart network-uri + parsec time xhtml ]; doHaddock = false; doCheck = false; homepage = "https://github.com/cheecheeo/haskell-cgi"; description = "A library for writing CGI programs"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "chan" = callPackage - ({ mkDerivation, async, base, stdenv, stm }: + ({ mkDerivation, async, base, lib, stm }: mkDerivation { pname = "chan"; version = "0.0.4.1"; @@ -6549,29 +7464,44 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/athanclark/chan#readme"; description = "Some extra kit for Chans"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "character-cases" = callPackage + ({ mkDerivation, base, containers, lib, megaparsec, prettyprinter + , template-haskell + }: + mkDerivation { + pname = "character-cases"; + version = "0.1.0.6"; + sha256 = "1e5a9220b1e19bc0425b7f9ea436c886a0be9d3ad697b2a64ea240246330045b"; + libraryHaskellDepends = [ + base containers megaparsec prettyprinter template-haskell + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/aiya000/hs-character-cases#readme"; + description = "Exposes subspecies types of Char. And naming cases."; + license = lib.licenses.mit; }) {}; "charset" = callPackage - ({ mkDerivation, array, base, bytestring, containers, semigroups - , stdenv, unordered-containers + ({ mkDerivation, array, base, bytestring, containers, lib + , unordered-containers }: mkDerivation { pname = "charset"; - version = "0.3.7.1"; - sha256 = "3d415d2883bd7bf0cc9f038e8323f19c71e07dd12a3c712f449ccb8b4daac0be"; - revision = "1"; - editedCabalFile = "1z6nxw2g9vgsjq0g159sk8mwj68lwzxzi5iv5ynha0h85jcqxszy"; + version = "0.3.8"; + sha256 = "7aaaa3e79b527dd46ee43b274f25d7ba18b4d3e698db404b5c923e6da3f086e7"; libraryHaskellDepends = [ - array base bytestring containers semigroups unordered-containers + array base bytestring containers unordered-containers ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/charset"; description = "Fast unicode character sets based on complemented PATRICIA tries"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "charsetdetect-ae" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "charsetdetect-ae"; version = "1.1.0.4"; @@ -6585,7 +7515,7 @@ inherit (pkgs.xorg) libXfixes;}; }) {}; "chaselev-deque" = callPackage ({ mkDerivation, abstract-deque, array, atomic-primops, base - , ghc-prim, stdenv, transformers, vector + , ghc-prim, lib, transformers, vector }: mkDerivation { pname = "chaselev-deque"; @@ -6599,19 +7529,19 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/rrnewton/haskell-lockfree/wiki"; description = "Chase & Lev work-stealing lock-free double-ended queues (deques)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cheapskate" = callPackage ({ mkDerivation, base, blaze-html, bytestring, containers - , data-default, deepseq, mtl, stdenv, syb, text, uniplate + , data-default, deepseq, lib, mtl, syb, text, uniplate , xss-sanitize }: mkDerivation { pname = "cheapskate"; - version = "0.1.1.1"; - sha256 = "d50d4f6978343f4990aeb6debf11e33054d8dc5ec4390196f12b8b68176ade62"; + version = "0.1.1.2"; + sha256 = "ed374897c39391fcf760552e6468def39fe36c3185708ca83056660ca3a2c69e"; revision = "1"; - editedCabalFile = "0mf6qdpgh56n0ynyy272vhkk2bjrdhppks2vrw79gk0kzn29fggh"; + editedCabalFile = "15hdlp062gv8x7giwcfbj1kfmhpj1bg7y2w4wr2yl436haxkrbmq"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -6623,11 +7553,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/jgm/cheapskate"; description = "Experimental markdown processor"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cheapskate-highlight" = callPackage ({ mkDerivation, base, blaze-html, cheapskate, highlighting-kate - , stdenv, text + , lib, text }: mkDerivation { pname = "cheapskate-highlight"; @@ -6642,10 +7572,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/aelve/cheapskate-highlight"; description = "Code highlighting for cheapskate"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cheapskate-lucid" = callPackage - ({ mkDerivation, base, blaze-html, cheapskate, lucid, stdenv }: + ({ mkDerivation, base, blaze-html, cheapskate, lib, lucid }: mkDerivation { pname = "cheapskate-lucid"; version = "0.1.0.0"; @@ -6657,31 +7587,16 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/aelve/cheapskate-lucid"; description = "Use cheapskate with Lucid"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "check-email" = callPackage - ({ mkDerivation, base, bytestring, email-validate, resolv, stdenv - }: - mkDerivation { - pname = "check-email"; - version = "1.0.2"; - sha256 = "1c2615fadba09a5d7aa5c68648d12218a595efb759842fb4f524cf380afa9327"; - libraryHaskellDepends = [ base bytestring email-validate ]; - librarySystemDepends = [ resolv ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/qoelet/check-email#readme"; - description = "Confirm whether an email is valid and probably existant"; - license = stdenv.lib.licenses.bsd3; - }) {inherit (pkgs) resolv;}; "checkers" = callPackage - ({ mkDerivation, array, base, QuickCheck, random, semigroupoids - , stdenv + ({ mkDerivation, array, base, lib, QuickCheck, random + , semigroupoids }: mkDerivation { pname = "checkers"; - version = "0.4.11"; - sha256 = "d0602d3561b9c3d9365387543e363e40b11851ace42698feb519c6567d842d38"; + version = "0.5.6"; + sha256 = "5fe92a2ccb0142144b4925bca837cf5bedf950c8244fbb4cbc67c092c46f02ad"; libraryHaskellDepends = [ array base QuickCheck random semigroupoids ]; @@ -6689,10 +7604,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/conal/checkers"; description = "Check properties on standard classes and data structures"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "checksum" = callPackage - ({ mkDerivation, base, explicit-exception, stdenv, utility-ht }: + ({ mkDerivation, base, explicit-exception, lib, utility-ht }: mkDerivation { pname = "checksum"; version = "0.0"; @@ -6702,10 +7617,46 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://hub.darcs.net/thielema/checksum"; description = "Compute and verify checksums of ISBN, IBAN, etc"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "chimera" = callPackage + ({ mkDerivation, adjunctions, base, distributive, lib, mtl, vector + }: + mkDerivation { + pname = "chimera"; + version = "0.3.1.0"; + sha256 = "2945f0a12b1a56b73249fd67e23b1e4e9e34cb1495f250af32536405454fb325"; + libraryHaskellDepends = [ + adjunctions base distributive mtl vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/Bodigrim/chimera#readme"; + description = "Lazy infinite streams with O(1) indexing"; + license = lib.licenses.bsd3; + }) {}; + "chiphunk" = callPackage + ({ mkDerivation, base, c2hs, hashable, lib, safe-exceptions + , StateVar, vector-space + }: + mkDerivation { + pname = "chiphunk"; + version = "0.1.4.0"; + sha256 = "bd150cdb405df446a3dfcd62c75201682c2ae46f35db897f83a933f6b563d724"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base hashable safe-exceptions StateVar vector-space + ]; + libraryToolDepends = [ c2hs ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/CthulhuDen/chiphunk#readme"; + description = "Haskell bindings for Chipmunk2D physics engine"; + license = lib.licenses.bsd3; }) {}; "choice" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "choice"; version = "0.2.2"; @@ -6715,24 +7666,65 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/mboes/choice#readme"; description = "A solution to boolean blindness"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "chronologique" = callPackage - ({ mkDerivation, aeson, base, hourglass, stdenv, text, time, vector - }: + ({ mkDerivation, aeson, base, hourglass, lib, text, time, vector }: mkDerivation { pname = "chronologique"; - version = "0.3.1.1"; - sha256 = "c538bc2e7b1cb9c1f4ae4177a5545c08d3ff66c29c80ef8faddd92daaa499e16"; + version = "0.3.1.3"; + sha256 = "903b53527a38cfbe180afa81d33d6e8e0b9c24fec06132e3dbd04a2b632b672d"; libraryHaskellDepends = [ aeson base hourglass text time vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/afcowie/chronologique/"; + homepage = "https://github.com/aesiniath/chronologique/"; description = "Time to manipulate time"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; + }) {}; + "chronos" = callPackage + ({ mkDerivation, aeson, attoparsec, base, bytestring, hashable, lib + , primitive, semigroups, text, torsor, vector + }: + mkDerivation { + pname = "chronos"; + version = "1.1.1"; + sha256 = "d223900866e77af08438eec80d1680773965e8176c72e1ea6004255fa485dd82"; + revision = "1"; + editedCabalFile = "0yspjcgnzl8kvfw6lgndkd2m4cp1s5gvga0kfm5fbrf0g8kwhns8"; + libraryHaskellDepends = [ + aeson attoparsec base bytestring hashable primitive semigroups text + torsor vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/andrewthad/chronos"; + description = "A performant time library"; + license = lib.licenses.bsd3; + }) {}; + "chronos-bench" = callPackage + ({ mkDerivation, ansi-terminal, base, bytestring, chronos + , containers, deepseq, lib, optparse-applicative, process + , terminal-size + }: + mkDerivation { + pname = "chronos-bench"; + version = "0.2.0.2"; + sha256 = "1b1880b02973dad0bad3a6fa18d6f85f7e0b2fadc602de83dd91e4fbbe255bc0"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + ansi-terminal base bytestring chronos containers deepseq + optparse-applicative process terminal-size + ]; + executableHaskellDepends = [ base optparse-applicative ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/knupfer/chronos"; + description = "Benchmarking tool with focus on comparing results"; + license = lib.licenses.bsd3; }) {}; "chunked-data" = callPackage - ({ mkDerivation, base, bytestring, containers, semigroups, stdenv + ({ mkDerivation, base, bytestring, containers, lib, semigroups , text, transformers, vector }: mkDerivation { @@ -6746,11 +7738,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/snoyberg/mono-traversable#readme"; description = "Typeclasses for dealing with various chunked data representations"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "cipher-aes" = callPackage ({ mkDerivation, base, byteable, bytestring, crypto-cipher-types - , securemem, stdenv + , lib, securemem }: mkDerivation { pname = "cipher-aes"; @@ -6763,48 +7755,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/vincenthz/hs-cipher-aes"; description = "Fast AES cipher implementation with advanced mode of operations"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "cipher-aes128" = callPackage - ({ mkDerivation, base, bytestring, Cabal, cereal, crypto-api - , process, stdenv, tagged - }: - mkDerivation { - pname = "cipher-aes128"; - version = "0.7.0.4"; - sha256 = "cd8d8987c1a1839f3c66e655277981083be85489d34b6b47f95d7e82d2d10285"; - isLibrary = true; - isExecutable = true; - setupHaskellDepends = [ base Cabal process ]; - libraryHaskellDepends = [ - base bytestring cereal crypto-api tagged - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/TomMD/cipher-aes128"; - description = "AES and common modes using AES-NI when available"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "cipher-blowfish" = callPackage - ({ mkDerivation, base, byteable, bytestring, crypto-cipher-types - , securemem, stdenv, vector - }: - mkDerivation { - pname = "cipher-blowfish"; - version = "0.0.3"; - sha256 = "8f41170a851dba6d0b6f07298af3213baca09ab2a8aaf2adb733631feb3b6641"; - libraryHaskellDepends = [ - base byteable bytestring crypto-cipher-types securemem vector - ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/vincenthz/hs-crypto-cipher"; - description = "Blowfish cipher"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cipher-camellia" = callPackage ({ mkDerivation, base, byteable, bytestring, crypto-cipher-types - , securemem, stdenv, vector + , lib, securemem, vector }: mkDerivation { pname = "cipher-camellia"; @@ -6817,11 +7772,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/vincenthz/hs-crypto-cipher"; description = "Camellia block cipher primitives"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cipher-des" = callPackage ({ mkDerivation, base, byteable, bytestring, crypto-cipher-types - , securemem, stdenv + , lib, securemem }: mkDerivation { pname = "cipher-des"; @@ -6834,11 +7789,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/vincenthz/hs-crypto-cipher"; description = "DES and 3DES primitives"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cipher-rc4" = callPackage ({ mkDerivation, base, byteable, bytestring, crypto-cipher-types - , stdenv + , lib }: mkDerivation { pname = "cipher-rc4"; @@ -6851,54 +7806,162 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/vincenthz/hs-cipher-rc4"; description = "Fast RC4 cipher implementation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "circle-packing" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "circle-packing"; version = "0.1.0.6"; sha256 = "64ee44a90da3e5fe20d5b78bfe6eba93102a6b52c65f8a7b99af7799798ee81b"; - revision = "2"; - editedCabalFile = "1ag213lv6yfzxdc4ghbywy165qblnqx5b3j9d23kc6fcyf19nfyk"; + revision = "4"; + editedCabalFile = "1jp1b6l5v1llmggy316s4bb78wjvgq8iya0i2zz4k5v6l5dl8ln2"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; description = "Simple heuristic for packing discs of varying radii in a circle"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "cisco-spark-api" = callPackage - ({ mkDerivation, aeson, attoparsec, base, bitset-word8, bytestring - , conduit, data-default, http-conduit, network-uri - , optparse-applicative, stdenv, text, utf8-string + "circular" = callPackage + ({ mkDerivation, aeson, base, lib, primitive, vector }: + mkDerivation { + pname = "circular"; + version = "0.4.0.0"; + sha256 = "c1ce741c5a1445a00a095f53c95f431ed79511e2540b63511f93015753f88294"; + libraryHaskellDepends = [ aeson base primitive vector ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/dschrempf/circular#readme"; + description = "Circular fixed-sized mutable vectors"; + license = lib.licenses.bsd3; + }) {}; + "citeproc" = callPackage + ({ mkDerivation, aeson, attoparsec, base, bytestring + , case-insensitive, containers, data-default, file-embed, filepath + , lib, pandoc-types, safe, scientific, text, transformers + , unicode-collation, uniplate, vector, xml-conduit }: mkDerivation { - pname = "cisco-spark-api"; - version = "0.1.0.4"; - sha256 = "6f550e999cb3b3bf1d4d041363c0bead0eec02f078dc51301873cc450143a244"; + pname = "citeproc"; + version = "0.4.0.1"; + sha256 = "9b061757b225b6e9e80d90e3df17858e602ed8204c3b74fb727ec993175b0f8e"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - aeson attoparsec base bitset-word8 bytestring conduit data-default - http-conduit network-uri text + aeson attoparsec base bytestring case-insensitive containers + data-default file-embed filepath pandoc-types safe scientific text + transformers unicode-collation uniplate vector xml-conduit ]; - executableHaskellDepends = [ - aeson base bytestring conduit data-default http-conduit - optparse-applicative text utf8-string + doHaddock = false; + doCheck = false; + description = "Generates citations and bibliography from CSL styles"; + license = lib.licenses.bsd2; + }) {}; + "clash-ghc" = callPackage + ({ mkDerivation, array, base, bifunctors, bytestring, Cabal + , clash-lib, clash-prelude, concurrent-supply, containers, deepseq + , directory, exceptions, extra, filepath, ghc, ghc-boot, ghc-prim + , ghc-typelits-extra, ghc-typelits-knownnat + , ghc-typelits-natnormalise, ghci, hashable, haskeline, integer-gmp + , lens, lib, mtl, primitive, process, reflection, split + , template-haskell, text, time, transformers, uniplate, unix + , unordered-containers, utf8-string, vector + }: + mkDerivation { + pname = "clash-ghc"; + version = "1.4.2"; + sha256 = "5acf6adc2c2e8c303d7b0714110c3c6e5e9111513cdb9e515eefebce2a425213"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + array base bifunctors bytestring Cabal clash-lib clash-prelude + concurrent-supply containers deepseq directory exceptions extra + filepath ghc ghc-boot ghc-prim ghc-typelits-extra + ghc-typelits-knownnat ghc-typelits-natnormalise ghci hashable + haskeline integer-gmp lens mtl primitive process reflection split + template-haskell text time transformers uniplate unix + unordered-containers utf8-string vector ]; + executableHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/nshimaza/webex-teams-api#readme"; - description = "DEPRECATED in favor of webex-teams-api"; - license = stdenv.lib.licenses.mit; + homepage = "https://clash-lang.org/"; + description = "Clash: a functional hardware description language - GHC frontend"; + license = lib.licenses.bsd2; + }) {}; + "clash-lib" = callPackage + ({ mkDerivation, aeson, aeson-pretty, ansi-terminal, array + , attoparsec, base, base16-bytestring, binary, bytestring + , clash-prelude, concurrent-supply, containers, cryptohash-sha256 + , data-binary-ieee754, data-default, deepseq, directory, dlist + , errors, exceptions, extra, filepath, ghc, ghc-boot-th, hashable + , haskell-src-meta, hint, integer-gmp, interpolate, lens, lib, mtl + , ordered-containers, parsers, pretty-show, prettyprinter + , primitive, process, reducers, template-haskell, temporary + , terminal-size, text, text-show, time, transformers, trifecta + , unordered-containers, utf8-string, vector + , vector-binary-instances + }: + mkDerivation { + pname = "clash-lib"; + version = "1.4.2"; + sha256 = "1504aec8bb96e5513d1a5225ef6cb951a03722197622959f7b10aa0bbeab3abe"; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + aeson aeson-pretty ansi-terminal array attoparsec base + base16-bytestring binary bytestring clash-prelude concurrent-supply + containers cryptohash-sha256 data-binary-ieee754 data-default + deepseq directory dlist errors exceptions extra filepath ghc + ghc-boot-th hashable haskell-src-meta hint integer-gmp interpolate + lens mtl ordered-containers parsers pretty-show prettyprinter + primitive process reducers template-haskell temporary terminal-size + text text-show time transformers trifecta unordered-containers + utf8-string vector vector-binary-instances + ]; + doHaddock = false; + doCheck = false; + homepage = "https://clash-lang.org/"; + description = "Clash: a functional hardware description language - As a library"; + license = lib.licenses.bsd2; + }) {}; + "clash-prelude" = callPackage + ({ mkDerivation, array, arrows, base, bifunctors, binary + , bytestring, Cabal, cabal-doctest, constraints, containers + , data-binary-ieee754, data-default-class, deepseq, ghc-prim + , ghc-typelits-extra, ghc-typelits-knownnat + , ghc-typelits-natnormalise, half, hashable, integer-gmp + , interpolate, lens, lib, QuickCheck, recursion-schemes, reflection + , singletons, template-haskell, text, text-show, th-abstraction + , th-lift, th-orphans, time, transformers, type-errors, uniplate + , vector + }: + mkDerivation { + pname = "clash-prelude"; + version = "1.4.2"; + sha256 = "25b5a859f65abfde9bd3131cc3b36bdbefc60ca67ced7f92993ab5d69a841a12"; + setupHaskellDepends = [ base Cabal cabal-doctest ]; + libraryHaskellDepends = [ + array arrows base bifunctors binary bytestring constraints + containers data-binary-ieee754 data-default-class deepseq ghc-prim + ghc-typelits-extra ghc-typelits-knownnat ghc-typelits-natnormalise + half hashable integer-gmp interpolate lens QuickCheck + recursion-schemes reflection singletons template-haskell text + text-show th-abstraction th-lift th-orphans time transformers + type-errors uniplate vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://clash-lang.org/"; + description = "Clash: a functional hardware description language - Prelude library"; + license = lib.licenses.bsd2; }) {}; "classy-prelude" = callPackage ({ mkDerivation, async, base, basic-prelude, bifunctors, bytestring - , chunked-data, containers, deepseq, dlist, ghc-prim, hashable + , chunked-data, containers, deepseq, dlist, ghc-prim, hashable, lib , mono-traversable, mono-traversable-instances, mtl - , mutable-containers, primitive, say, semigroups, stdenv, stm - , stm-chans, text, time, transformers, unliftio - , unordered-containers, vector, vector-instances + , mutable-containers, primitive, say, semigroups, stm, stm-chans + , text, time, transformers, unliftio, unordered-containers, vector + , vector-instances }: mkDerivation { pname = "classy-prelude"; @@ -6915,11 +7978,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/snoyberg/mono-traversable#readme"; description = "A typeclass-based Prelude"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "classy-prelude-conduit" = callPackage - ({ mkDerivation, base, bytestring, classy-prelude, conduit - , monad-control, resourcet, stdenv, transformers, void + ({ mkDerivation, base, bytestring, classy-prelude, conduit, lib + , monad-control, resourcet, transformers, void }: mkDerivation { pname = "classy-prelude-conduit"; @@ -6933,57 +7996,25 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/snoyberg/mono-traversable#readme"; description = "classy-prelude together with conduit functions"; - license = stdenv.lib.licenses.mit; - }) {}; - "classy-prelude-yesod" = callPackage - ({ mkDerivation, aeson, base, classy-prelude - , classy-prelude-conduit, data-default, http-conduit, http-types - , persistent, stdenv, yesod, yesod-newsfeed, yesod-static - }: - mkDerivation { - pname = "classy-prelude-yesod"; - version = "1.5.0"; - sha256 = "9ffbc4447ec2df8131ca32c259da19f379109d6e44569a7ee16714ab67029f83"; - libraryHaskellDepends = [ - aeson base classy-prelude classy-prelude-conduit data-default - http-conduit http-types persistent yesod yesod-newsfeed - yesod-static - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/snoyberg/mono-traversable#readme"; - description = "Provide a classy prelude including common Yesod functionality"; - license = stdenv.lib.licenses.mit; - }) {}; - "classyplate" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: - mkDerivation { - pname = "classyplate"; - version = "0.3.2.0"; - sha256 = "712eefbe6b6fd92d6e5e7982d82a27e45b7992a83c2b09fc8696b1e30752527a"; - libraryHaskellDepends = [ base template-haskell ]; - doHaddock = false; - doCheck = false; - description = "Fuseable type-class based generics"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; "clay" = callPackage - ({ mkDerivation, base, mtl, stdenv, text }: + ({ mkDerivation, base, lib, mtl, text }: mkDerivation { pname = "clay"; - version = "0.13.1"; - sha256 = "844e9101cc1835eb12bac50e289d00f19c24eeee12bcdebae1b633edffa328a3"; + version = "0.13.3"; + sha256 = "5db3c4c4a40f377b808a1569c5f8aeeea3ecdd2191f4fbbcd0f22b23fdd254a4"; libraryHaskellDepends = [ base mtl text ]; doHaddock = false; doCheck = false; homepage = "http://fvisser.nl/clay"; description = "CSS preprocessor as embedded Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "clientsession" = callPackage ({ mkDerivation, base, base64-bytestring, bytestring, cereal , cipher-aes, cprng-aes, crypto-api, crypto-random, directory - , entropy, setenv, skein, stdenv, tagged + , entropy, lib, setenv, skein, tagged }: mkDerivation { pname = "clientsession"; @@ -7000,113 +8031,123 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/yesodweb/clientsession/tree/master"; description = "Securely store session data in a client-side cookie"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "climb" = callPackage + ({ mkDerivation, base, bytestring, containers, exceptions, lib + , linenoise, mtl, text, unliftio-core + }: + mkDerivation { + pname = "climb"; + version = "0.3.3"; + sha256 = "447c32f13bd39b3c3f6492822c6bf2b4b46d7a1c2c09da980ca252b938d3d234"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base bytestring containers exceptions linenoise mtl text + unliftio-core + ]; + executableHaskellDepends = [ + base bytestring containers exceptions linenoise mtl text + unliftio-core + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ejconlon/climb#readme"; + description = "Building blocks for a GHCi-like REPL with colon-commands"; + license = lib.licenses.bsd3; }) {}; "clock" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "clock"; - version = "0.7.2"; - sha256 = "886601978898d3a91412fef895e864576a7125d661e1f8abc49a2a08840e691f"; + version = "0.8.2"; + sha256 = "0b5db110c703e68b251d5883253a934b012110b45393fc65df1b095eb9a4e461"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/corsis/clock"; description = "High-resolution clock functions: monotonic, realtime, cputime"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "clock-extras" = callPackage - ({ mkDerivation, base, clock, stdenv }: - mkDerivation { - pname = "clock-extras"; - version = "0.1.0.2"; - sha256 = "a9ed097aa9d48b53c6a555bc5f67e347249b08e2252dd4fc998fb4ab42edda59"; - libraryHaskellDepends = [ base clock ]; - doHaddock = false; - doCheck = false; - description = "A couple functions that probably should be in the 'clock' package"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "clr-host" = callPackage - ({ mkDerivation, base, bytestring, Cabal, clr-marshal, directory - , file-embed, filepath, glib, mono, stdenv, text, transformers + "closed" = callPackage + ({ mkDerivation, aeson, base, cassava, deepseq, hashable, lib + , persistent, QuickCheck, text }: mkDerivation { - pname = "clr-host"; - version = "0.2.1.0"; - sha256 = "fe2abf0386c96df6e51cbae4f45e074b54452fc01f9308b098198ade4ffc5ea4"; - setupHaskellDepends = [ - base Cabal directory filepath transformers - ]; + pname = "closed"; + version = "0.2.0.1"; + sha256 = "564334f7c6d0fcc06daade2ddafc15210bcdf9717b875da7ba2a1fbb655be4b4"; libraryHaskellDepends = [ - base bytestring clr-marshal file-embed text + aeson base cassava deepseq hashable persistent QuickCheck text ]; - librarySystemDepends = [ glib mono ]; - doHaddock = false; - doCheck = false; - homepage = "https://gitlab.com/tim-m89/clr-haskell/tree/master/libs/clr-host"; - description = "Hosting the Common Language Runtime"; - license = stdenv.lib.licenses.bsd3; - }) {inherit (pkgs) glib; inherit (pkgs) mono;}; - "clr-marshal" = callPackage - ({ mkDerivation, base, stdenv, text }: - mkDerivation { - pname = "clr-marshal"; - version = "0.2.0.0"; - sha256 = "4113651f3d10de21813b2a44b78ca19f9ab62b6c6d9df0c25a88940fabebdcd6"; - libraryHaskellDepends = [ base text ]; doHaddock = false; doCheck = false; - homepage = "https://gitlab.com/tim-m89/clr-haskell/tree/master/libs/clr-marshal"; - description = "Marshaling for the clr"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/frontrowed/closed#readme"; + description = "Integers bounded by a closed interval"; + license = lib.licenses.mit; }) {}; "clumpiness" = callPackage - ({ mkDerivation, base, containers, stdenv, tree-fun }: + ({ mkDerivation, base, containers, lib, tree-fun }: mkDerivation { pname = "clumpiness"; - version = "0.17.0.0"; - sha256 = "fd4b303d206eaf242c779bb65c42256e42220c8497a6bcf3bc59589b9396c495"; + version = "0.17.0.2"; + sha256 = "eca2c21c6d3d9d3e6f26f7ca36db99680120c8f959fdbfef8c970aac131936c0"; libraryHaskellDepends = [ base containers tree-fun ]; doHaddock = false; doCheck = false; description = "Calculate the clumpiness of leaf properties in a tree"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; }) {}; "cmark" = callPackage - ({ mkDerivation, base, bytestring, stdenv, text }: + ({ mkDerivation, base, bytestring, lib, text }: mkDerivation { pname = "cmark"; - version = "0.5.6"; - sha256 = "855c4b7aca6d4e9eb076beb6cc6f74e7578fae7aa3625fd3fca5e3b4901a32b0"; + version = "0.6"; + sha256 = "0dec55cd4e02ac6ff557044a9aa2523479afc88370d3838430b3e386bef981dc"; libraryHaskellDepends = [ base bytestring text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/jgm/cmark-hs"; description = "Fast, accurate CommonMark (Markdown) parser and renderer"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cmark-gfm" = callPackage - ({ mkDerivation, base, bytestring, stdenv, text }: + ({ mkDerivation, base, bytestring, lib, text }: mkDerivation { pname = "cmark-gfm"; - version = "0.1.6"; - sha256 = "c8f916c8fbc9b3c564dcd6946cd530a292a055b60c784dde303803199a6c6968"; + version = "0.2.2"; + sha256 = "ee701aff393373f51c2653d7d23482aa7a000451cb2e38f307165616c36b7fea"; libraryHaskellDepends = [ base bytestring text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/kivikakk/cmark-gfm-hs"; description = "Fast, accurate GitHub Flavored Markdown parser and renderer"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "cmark-lucid" = callPackage + ({ mkDerivation, base, cmark, lib, lucid }: + mkDerivation { + pname = "cmark-lucid"; + version = "0.1.0.0"; + sha256 = "d2927b9fed0e32fe7afc539e7b427e0a95f8c9297bb6bc531101b476ba8a3c03"; + revision = "1"; + editedCabalFile = "1mizbv18bl8qrgz27wlz7sb6cfhblmp7p7gh7dqq8g0r4djrvqg5"; + libraryHaskellDepends = [ base cmark lucid ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/aelve/cmark-lucid"; + description = "Use cmark with Lucid"; + license = lib.licenses.bsd3; }) {}; "cmdargs" = callPackage - ({ mkDerivation, base, filepath, process, stdenv, template-haskell + ({ mkDerivation, base, filepath, lib, process, template-haskell , transformers }: mkDerivation { pname = "cmdargs"; - version = "0.10.20"; - sha256 = "0e269dc48c3d4c0447c96ffd772a6fe69dfa1260c323f4cd7bf171cbf2ab7331"; + version = "0.10.21"; + sha256 = "f7d8ea5c4e6af368d9b5d2eb994fc29235406fbe91916a6dc63bd883025eca75"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -7116,79 +8157,51 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/ndmitchell/cmdargs#readme"; description = "Command line argument processing"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "co-log" = callPackage - ({ mkDerivation, ansi-terminal, base, bytestring, co-log-core - , containers, contravariant, directory, filepath, markdown-unlit - , mtl, stdenv, stm, text, time, transformers, typerep-map - }: + "co-log-concurrent" = callPackage + ({ mkDerivation, base, co-log-core, lib, stm }: mkDerivation { - pname = "co-log"; - version = "0.2.0"; - sha256 = "592e2a5cb7fbe5ae48e7d5682337ac197ef3e41f3577a185b3a9989ab31ea8f5"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - ansi-terminal base bytestring co-log-core containers contravariant - directory filepath mtl stm text time transformers typerep-map - ]; - executableHaskellDepends = [ base text typerep-map ]; - executableToolDepends = [ markdown-unlit ]; + pname = "co-log-concurrent"; + version = "0.5.0.0"; + sha256 = "cad691afb8c35ee6a2bf229b1b89d2e1e0dd164c6d82c1167482b533e954e41f"; + libraryHaskellDepends = [ base co-log-core stm ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/kowainik/co-log"; - description = "Composable Contravariant Comonadic Logging Library"; - license = stdenv.lib.licenses.mpl20; + homepage = "https://github.com/qnikst/co-log-concurrent/"; + description = "Asynchronous backend for co-log library"; + license = lib.licenses.mpl20; }) {}; "co-log-core" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "co-log-core"; - version = "0.1.1"; - sha256 = "bc0071c6f09dd45b8eee9a990696490dfa96e60425c2c5d4c5b591da999f1303"; + version = "0.2.1.1"; + sha256 = "337abebabafac114893d33b3e2ee7d7494777810522e4af7fed5b160d3908813"; + revision = "1"; + editedCabalFile = "1mib449rp5g02f62nl4phfgjm4f8dj5v6qwxyx0cccglkiccn28j"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/kowainik/co-log"; description = "Composable Contravariant Comonadic Logging Library"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "code-page" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "code-page"; - version = "0.2"; - sha256 = "bfe32a8c4be9cf0d5a088267bf3fdf4adda8ba3f109e85675c93e70d575e1844"; + version = "0.2.1"; + sha256 = "b2f90e19c61ed8a6ff7295f7f123d4a9913c790d4cf2c6029bc299293fdb2aaa"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/RyanGlScott/code-page"; description = "Windows code page library for Haskell"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "codec" = callPackage - ({ mkDerivation, aeson, base, binary, binary-bits, bytestring, mtl - , profunctors, stdenv, template-haskell, text, transformers - , unordered-containers, vector - }: - mkDerivation { - pname = "codec"; - version = "0.2.1"; - sha256 = "ffc261b58108c3d90c0b0b68461857d1148208d1a9645916e63241aaa3c25b28"; - libraryHaskellDepends = [ - aeson base binary binary-bits bytestring mtl profunctors - template-haskell text transformers unordered-containers vector - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/chpatrick/codec"; - description = "Simple bidirectional serialization"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "codec-beam" = callPackage - ({ mkDerivation, base, bytestring, containers, stdenv, text, zlib - }: + ({ mkDerivation, base, bytestring, containers, lib, text, zlib }: mkDerivation { pname = "codec-beam"; version = "0.2.0"; @@ -7198,89 +8211,36 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/hkgumbs/codec-beam#readme"; description = "Erlang VM byte code assembler"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "codec-rpm" = callPackage - ({ mkDerivation, attoparsec, attoparsec-binary, base, bytestring - , conduit, conduit-extra, cpio-conduit, exceptions, lzma-conduit - , mtl, parsec, pretty, resourcet, stdenv, text - }: - mkDerivation { - pname = "codec-rpm"; - version = "0.2.2"; - sha256 = "a34b88378dc79b08b56c39515763b6d940166595c24dc45e61cc8d2bb4ed4b97"; - libraryHaskellDepends = [ - attoparsec attoparsec-binary base bytestring conduit conduit-extra - cpio-conduit exceptions lzma-conduit mtl parsec pretty resourcet - text - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/weldr/codec-rpm"; - description = "A library for manipulating RPM files"; - license = stdenv.lib.licenses.lgpl21; - }) {}; - "codo-notation" = callPackage - ({ mkDerivation, base, comonad, haskell-src-meta, parsec, stdenv - , template-haskell, uniplate - }: - mkDerivation { - pname = "codo-notation"; - version = "0.5.2"; - sha256 = "78eb57004541ed29eb4c54196b91ac2dd1028a3315f51cd4dc00debfc0938eaf"; - libraryHaskellDepends = [ - base comonad haskell-src-meta parsec template-haskell uniplate - ]; - doHaddock = false; - doCheck = false; - description = "A notation for comonads, analogous to the do-notation for monads"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "coercible-utils" = callPackage - ({ mkDerivation, base, stdenv }: - mkDerivation { - pname = "coercible-utils"; - version = "0.0.0"; - sha256 = "2a624986cdc010c7fc3e90f8c94f722995af9fe6e88b9d52a94ebaa319b08c98"; - libraryHaskellDepends = [ base ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/sjakobi/coercible-utils"; - description = "Utility functions for Coercible types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "colonnade" = callPackage - ({ mkDerivation, base, bytestring, contravariant, profunctors - , stdenv, text, vector - }: + "collect-errors" = callPackage + ({ mkDerivation, base, containers, deepseq, lib, QuickCheck }: mkDerivation { - pname = "colonnade"; - version = "1.2.0.1"; - sha256 = "32ebd86360c9a363d62a2490b7120de5651a6674a79c4f9d85e13d2cc8cb3e8b"; - libraryHaskellDepends = [ - base bytestring contravariant profunctors text vector - ]; + pname = "collect-errors"; + version = "0.1.5.0"; + sha256 = "69b2417851ef0a19a4f8d00f88e4a9f3c124420029e94677cc87cccbab6592c2"; + libraryHaskellDepends = [ base containers deepseq QuickCheck ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/andrewthad/colonnade#readme"; - description = "Generic types and functions for columnar encoding and decoding"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/michalkonecny/collect-errors#readme"; + description = "Error monad with a Float instance"; + license = lib.licenses.bsd3; }) {}; "colorful-monoids" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "colorful-monoids"; - version = "0.2.1.2"; - sha256 = "0b42ff47e011f011f73e444d7121b7bc54324077cb2a1011ee01766483706578"; + version = "0.2.1.3"; + sha256 = "381b2f106c3c814bcc1b2d812c1fe3a125cae8f2a58a00db3f54b126fb165679"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/minad/colorful-monoids#readme"; description = "Styled console text output using ANSI escape sequences"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "colorize-haskell" = callPackage - ({ mkDerivation, ansi-terminal, base, haskell-lexer, stdenv }: + ({ mkDerivation, ansi-terminal, base, haskell-lexer, lib }: mkDerivation { pname = "colorize-haskell"; version = "1.0.1"; @@ -7293,24 +8253,24 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/yav/colorize-haskell"; description = "Highligt Haskell source"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "colour" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "colour"; - version = "2.3.4"; - sha256 = "0f439f00b322ce3d551f28a4dd1520aa2c91d699de4cdc6d485b9b04be0dc5eb"; + version = "2.3.6"; + sha256 = "2cd35dcd6944a5abc9f108a5eb5ee564b6b1fa98a9ec79cefcc20b588991f871"; enableSeparateDataOutput = true; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Colour"; description = "A model for human colour/color perception"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "combinatorial" = callPackage - ({ mkDerivation, array, base, containers, stdenv, transformers + ({ mkDerivation, array, base, containers, lib, transformers , utility-ht }: mkDerivation { @@ -7324,10 +8284,30 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://hub.darcs.net/thielema/combinatorial/"; description = "Count, enumerate, rank and unrank combinatorial objects"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "comfort-array" = callPackage + ({ mkDerivation, base, containers, deepseq, guarded-allocation, lib + , non-empty, prelude-compat, primitive, QuickCheck, semigroups + , storable-record, tagged, transformers, utility-ht + }: + mkDerivation { + pname = "comfort-array"; + version = "0.4.1"; + sha256 = "25a627f9c076edc14188db258bb9cbff17dc73227aee646d2ae2ebc1bcc1da86"; + libraryHaskellDepends = [ + base containers deepseq guarded-allocation non-empty prelude-compat + primitive QuickCheck semigroups storable-record tagged transformers + utility-ht + ]; + doHaddock = false; + doCheck = false; + homepage = "https://hub.darcs.net/thielema/comfort-array/"; + description = "Arrays where the index type is a function of the shape type"; + license = lib.licenses.bsd3; }) {}; "comfort-graph" = callPackage - ({ mkDerivation, base, containers, QuickCheck, semigroups, stdenv + ({ mkDerivation, base, containers, lib, QuickCheck, semigroups , transformers, utility-ht }: mkDerivation { @@ -7341,10 +8321,63 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://hub.darcs.net/thielema/comfort-graph"; description = "Graph structure with type parameters for nodes and edges"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "commonmark" = callPackage + ({ mkDerivation, base, bytestring, containers, lib, parsec, text + , transformers, unicode-transforms + }: + mkDerivation { + pname = "commonmark"; + version = "0.2.1"; + sha256 = "ab6047825fd282f667c0f3a454ffe37d7358cf13a4133976080862f5c33e6aed"; + libraryHaskellDepends = [ + base bytestring containers parsec text transformers + unicode-transforms + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jgm/commonmark-hs"; + description = "Pure Haskell commonmark parser"; + license = lib.licenses.bsd3; + }) {}; + "commonmark-extensions" = callPackage + ({ mkDerivation, base, commonmark, containers, emojis, filepath + , lib, network-uri, parsec, text, transformers + }: + mkDerivation { + pname = "commonmark-extensions"; + version = "0.2.1.2"; + sha256 = "a4cf7c83ac3b157f99c572c0d158e1913b5e589e564823dec5152983c091c0cf"; + libraryHaskellDepends = [ + base commonmark containers emojis filepath network-uri parsec text + transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jgm/commonmark-hs"; + description = "Pure Haskell commonmark parser"; + license = lib.licenses.bsd3; + }) {}; + "commonmark-pandoc" = callPackage + ({ mkDerivation, base, commonmark, commonmark-extensions, lib + , pandoc-types, text + }: + mkDerivation { + pname = "commonmark-pandoc"; + version = "0.2.1.1"; + sha256 = "9795d9bc40eb3d389ca8a58ae63f1f6e4db653bdddf302df595ceb9ac8572e97"; + libraryHaskellDepends = [ + base commonmark commonmark-extensions pandoc-types text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jgm/commonmark-hs"; + description = "Bridge between commonmark and pandoc AST"; + license = lib.licenses.bsd3; }) {}; "commutative" = callPackage - ({ mkDerivation, base, random, semigroups, stdenv, vector }: + ({ mkDerivation, base, lib, random, semigroups, vector }: mkDerivation { pname = "commutative"; version = "0.0.2"; @@ -7354,30 +8387,47 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/athanclark/commutative#readme"; description = "Commutative binary operations"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "comonad" = callPackage - ({ mkDerivation, base, Cabal, cabal-doctest, containers - , contravariant, distributive, semigroups, stdenv, tagged - , transformers, transformers-compat + ({ mkDerivation, base, containers, distributive + , indexed-traversable, lib, tagged, transformers + , transformers-compat }: mkDerivation { pname = "comonad"; - version = "5.0.4"; - sha256 = "78a89d7f9f0975b40b3294adcb70885649572b687ac5f5dc98e452471838e825"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "5.0.8"; + sha256 = "ef6cdf2cc292cc43ee6aa96c581b235fdea8ab44a0bffb24dc79ae2b2ef33d13"; libraryHaskellDepends = [ - base containers contravariant distributive semigroups tagged + base containers distributive indexed-traversable tagged transformers transformers-compat ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/comonad/"; description = "Comonads"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "comonad-extras" = callPackage + ({ mkDerivation, array, base, comonad, containers, distributive + , lib, semigroupoids, transformers + }: + mkDerivation { + pname = "comonad-extras"; + version = "4.0.1"; + sha256 = "64ac950358fe4f97c85366f4e5d3caa5d37a8e0d7acade45cdf7c7a8f1eb5def"; + libraryHaskellDepends = [ + array base comonad containers distributive semigroupoids + transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/ekmett/comonad-extras/"; + description = "Exotic comonad transformers"; + license = lib.licenses.bsd3; }) {}; "compactmap" = callPackage - ({ mkDerivation, base, stdenv, vector }: + ({ mkDerivation, base, lib, vector }: mkDerivation { pname = "compactmap"; version = "0.1.4.2.1"; @@ -7386,19 +8436,34 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "A read-only memory-efficient key-value store"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "compdata" = callPackage + ({ mkDerivation, base, containers, deepseq, lib, mtl, QuickCheck + , template-haskell, th-expand-syns, transformers, tree-view + }: + mkDerivation { + pname = "compdata"; + version = "0.12.1"; + sha256 = "05b8647de09834ae71e6ff6bea08d66aac39d3078290d36e9e506f89df1a4a4f"; + libraryHaskellDepends = [ + base containers deepseq mtl QuickCheck template-haskell + th-expand-syns transformers tree-view + ]; + doHaddock = false; + doCheck = false; + description = "Compositional Data Types"; + license = lib.licenses.bsd3; }) {}; "compensated" = callPackage - ({ mkDerivation, base, bifunctors, binary, bytes, Cabal - , cabal-doctest, cereal, comonad, deepseq, distributive, hashable - , lens, log-domain, safecopy, semigroupoids, semigroups, stdenv - , vector + ({ mkDerivation, base, bifunctors, binary, bytes, cereal, comonad + , deepseq, distributive, hashable, lens, lib, log-domain, safecopy + , semigroupoids, semigroups, vector }: mkDerivation { pname = "compensated"; - version = "0.7.2"; - sha256 = "c7f9bf47a586720deda33b82ddc633d3507c8bc199eb5555c80931f6c323cae2"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "0.8.3"; + sha256 = "2a8d1a381ccaf4f0535e274880f7636fa5eff59cb2c125276a0115ce2e892f76"; libraryHaskellDepends = [ base bifunctors binary bytes cereal comonad deepseq distributive hashable lens log-domain safecopy semigroupoids semigroups vector @@ -7407,10 +8472,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/analytics/compensated/"; description = "Compensated floating-point arithmetic"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "compiler-warnings" = callPackage - ({ mkDerivation, base, binary, parsec, stdenv, text }: + ({ mkDerivation, base, binary, lib, parsec, text }: mkDerivation { pname = "compiler-warnings"; version = "0.1.0"; @@ -7420,10 +8485,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/yi-editor/compiler-warnings#readme"; description = "Parser for common compiler warning formats"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; }) {}; "composable-associations" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "composable-associations"; version = "0.1.0.0"; @@ -7433,16 +8498,16 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/SamProtas/composable-associations#readme"; description = "Types and helpers for composing types into a single larger key-value type"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "composable-associations-aeson" = callPackage - ({ mkDerivation, aeson, base, composable-associations, stdenv, text + ({ mkDerivation, aeson, base, composable-associations, lib, text , unordered-containers }: mkDerivation { pname = "composable-associations-aeson"; - version = "0.1.0.0"; - sha256 = "dbd754ed6d624469f16c4cd2ad51c441eeb8c62d6af66673f76034c7517c2a4f"; + version = "0.1.0.1"; + sha256 = "3c238ea8615f2838ed82b4fca42c2a80e13c2c5f9de5a625da21ea34798ef23a"; libraryHaskellDepends = [ aeson base composable-associations text unordered-containers ]; @@ -7450,21 +8515,21 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/SamProtas/composable-associations#readme"; description = "Aeson ToJSON/FromJSON implementation for the types of composable-associations"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "composition" = callPackage - ({ mkDerivation, stdenv }: + ({ mkDerivation, lib }: mkDerivation { pname = "composition"; - version = "1.0.2.1"; - sha256 = "7123300f5eca5a7cec4eb731dc0e9c2c44aabe26b37e6579582a7267d9f7ad6a"; + version = "1.0.2.2"; + sha256 = "b50bf7a96f1fb56b1598f98e448c37963e8f457e424afbb0fd562eacea44d42e"; doHaddock = false; doCheck = false; description = "Combinators for unorthodox function composition"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "composition-extra" = callPackage - ({ mkDerivation, base, composition, contravariant, stdenv }: + ({ mkDerivation, base, composition, contravariant, lib }: mkDerivation { pname = "composition-extra"; version = "2.0.0"; @@ -7473,10 +8538,10 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Combinators for unorthodox structure composition"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "concise" = callPackage - ({ mkDerivation, base, bytestring, lens, stdenv, text }: + ({ mkDerivation, base, bytestring, lens, lib, text }: mkDerivation { pname = "concise"; version = "0.1.0.1"; @@ -7486,16 +8551,16 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/frasertweedale/hs-concise"; description = "Utilities for Control.Lens.Cons"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "concurrency" = callPackage - ({ mkDerivation, array, atomic-primops, base, exceptions - , monad-control, mtl, stdenv, stm, transformers + ({ mkDerivation, array, atomic-primops, base, exceptions, lib + , monad-control, mtl, stm, transformers }: mkDerivation { pname = "concurrency"; - version = "1.6.2.0"; - sha256 = "c8e43e6d19f075e7a66a7191350eba0d177b5339ba6db6d3bcfde2d73a0f9000"; + version = "1.11.0.1"; + sha256 = "5089059dccd092a28e70c2a4b309b3ccd35ec04a970c8a4b173cd33e2f2f4537"; libraryHaskellDepends = [ array atomic-primops base exceptions monad-control mtl stm transformers @@ -7504,10 +8569,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/barrucadu/dejafu"; description = "Typeclasses, functions, and data types for concurrency and STM"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "concurrent-extra" = callPackage - ({ mkDerivation, base, stdenv, stm, unbounded-delays }: + ({ mkDerivation, base, lib, stm, unbounded-delays }: mkDerivation { pname = "concurrent-extra"; version = "0.7.0.12"; @@ -7517,16 +8582,16 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/basvandijk/concurrent-extra"; description = "Extra concurrency primitives"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "concurrent-output" = callPackage ({ mkDerivation, ansi-terminal, async, base, directory, exceptions - , process, stdenv, stm, terminal-size, text, transformers, unix + , lib, process, stm, terminal-size, text, transformers, unix }: mkDerivation { pname = "concurrent-output"; - version = "1.10.9"; - sha256 = "8cc49408e957c65359182fbfcda80717b931915d101e4be55ccb26c44b098e57"; + version = "1.10.12"; + sha256 = "87f8a1cf54e6eaf146750fa6bf11aa2620da496073cb6c3dc8f697169eba3c20"; libraryHaskellDepends = [ ansi-terminal async base directory exceptions process stm terminal-size text transformers unix @@ -7534,10 +8599,10 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Ungarble output from several threads or commands"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; }) {}; "concurrent-split" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "concurrent-split"; version = "0.0.1.1"; @@ -7546,23 +8611,25 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "MVars and Channels with distinguished input and output side"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "concurrent-supply" = callPackage - ({ mkDerivation, base, ghc-prim, hashable, stdenv }: + ({ mkDerivation, base, ghc-prim, hashable, lib }: mkDerivation { pname = "concurrent-supply"; version = "0.1.8"; sha256 = "ccf827dcd221298ae93fad6021c63a06707456de0671706b44f1f2fed867f21f"; + revision = "1"; + editedCabalFile = "1yzrr68k81w3jmrarx3y6z7ymzaaxwab509pp6kkd2fjia3g8wwk"; libraryHaskellDepends = [ base ghc-prim hashable ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/concurrent-supply/"; description = "A fast concurrent unique identifier supply with a pure API"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cond" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "cond"; version = "0.4.1.1"; @@ -7572,17 +8639,35 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/kallisti-dev/cond"; description = "Basic conditional and boolean operators with monadic variants"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "conduino" = callPackage + ({ mkDerivation, base, bytestring, containers, exceptions, free + , lib, list-transformer, mtl, transformers + }: + mkDerivation { + pname = "conduino"; + version = "0.2.2.0"; + sha256 = "62728e07b29613499bf3368216f1a7fcdd193f176d7e0e88433ba96dc391b049"; + libraryHaskellDepends = [ + base bytestring containers exceptions free list-transformer mtl + transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/mstksg/conduino#readme"; + description = "Lightweight composable continuation-based stream processors"; + license = lib.licenses.bsd3; }) {}; "conduit" = callPackage ({ mkDerivation, base, bytestring, directory, exceptions, filepath - , mono-traversable, mtl, primitive, resourcet, stdenv, text + , lib, mono-traversable, mtl, primitive, resourcet, text , transformers, unix, unliftio-core, vector }: mkDerivation { pname = "conduit"; - version = "1.3.1"; - sha256 = "ae129b66ada785c43a693d3b260f0e7b2f01d79fbf04ae43f7341405455320d6"; + version = "1.3.4.1"; + sha256 = "85743b8d5f2d5779ccb7459b5a919c5786707af23fe7a065d281ee8e6dc226f1"; libraryHaskellDepends = [ base bytestring directory exceptions filepath mono-traversable mtl primitive resourcet text transformers unix unliftio-core vector @@ -7591,19 +8676,19 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/snoyberg/conduit"; description = "Streaming data processing library"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "conduit-algorithms" = callPackage ({ mkDerivation, async, base, bytestring, bzlib-conduit, conduit , conduit-combinators, conduit-extra, conduit-zstd, containers - , deepseq, exceptions, lzma-conduit, monad-control, mtl, pqueue - , resourcet, stdenv, stm, stm-conduit, streaming-commons + , deepseq, exceptions, lib, lzma-conduit, monad-control, mtl + , pqueue, resourcet, stm, stm-conduit, streaming-commons , transformers, unliftio-core, vector }: mkDerivation { pname = "conduit-algorithms"; - version = "0.0.9.0"; - sha256 = "11dd94dd4264f6985f35a6c102c3716178757be21da0dce9a4e7d83aa64a4db4"; + version = "0.0.11.0"; + sha256 = "31edb5d0a4a1bc03c31b0cafe27255ce4f30bd402798454faf71cf09c6e73230"; libraryHaskellDepends = [ async base bytestring bzlib-conduit conduit conduit-combinators conduit-extra conduit-zstd containers deepseq exceptions @@ -7614,10 +8699,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/luispedro/conduit-algorithms#readme"; description = "Conduit-based algorithms"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "conduit-combinators" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "conduit-combinators"; version = "1.3.0"; @@ -7627,10 +8712,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/snoyberg/mono-traversable#readme"; description = "DEPRECATED Functionality merged into the conduit package itself"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "conduit-concurrent-map" = callPackage - ({ mkDerivation, base, conduit, containers, mtl, resourcet, stdenv + ({ mkDerivation, base, conduit, containers, lib, mtl, resourcet , unliftio, unliftio-core, vector }: mkDerivation { @@ -7644,35 +8729,18 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/nh2/conduit-concurrent-map"; description = "Concurrent, order-preserving mapping Conduit"; - license = stdenv.lib.licenses.mit; - }) {}; - "conduit-connection" = callPackage - ({ mkDerivation, base, bytestring, conduit, connection, resourcet - , stdenv, transformers - }: - mkDerivation { - pname = "conduit-connection"; - version = "0.1.0.4"; - sha256 = "5e784117f3698dc653b286fbb53d530068d0cdadbe130ec02abf42e3f2c821fc"; - libraryHaskellDepends = [ - base bytestring conduit connection resourcet transformers - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/sdroege/conduit-connection"; - description = "Conduit source and sink for Network.Connection."; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; "conduit-extra" = callPackage ({ mkDerivation, async, attoparsec, base, bytestring, conduit - , directory, filepath, network, primitive, process, resourcet - , stdenv, stm, streaming-commons, text, transformers, typed-process + , directory, filepath, lib, network, primitive, process, resourcet + , stm, streaming-commons, text, transformers, typed-process , unliftio-core }: mkDerivation { pname = "conduit-extra"; - version = "1.3.0"; - sha256 = "2c41c925fc53d9ba2e640c7cdca72c492b28c0d45f1a82e94baef8dfa65922ae"; + version = "1.3.5"; + sha256 = "8a648dee203c01e647fa386bfe7a5b293ce552f8b5cab9c0dd5cb71c7cd012d9"; libraryHaskellDepends = [ async attoparsec base bytestring conduit directory filepath network primitive process resourcet stm streaming-commons text transformers @@ -7682,24 +8750,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/snoyberg/conduit"; description = "Batteries included conduit: adapters for common libraries"; - license = stdenv.lib.licenses.mit; - }) {}; - "conduit-iconv" = callPackage - ({ mkDerivation, base, bytestring, conduit, stdenv }: - mkDerivation { - pname = "conduit-iconv"; - version = "0.1.1.3"; - sha256 = "1c71304782e4599a2987321028b50356c4982b45d9096d954e0b7c0b7ad3acb6"; - libraryHaskellDepends = [ base bytestring conduit ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/sdroege/conduit-iconv"; - description = "Conduit for character encoding conversion"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; "conduit-parse" = callPackage - ({ mkDerivation, base, conduit, dlist, mtl, parsers, safe - , safe-exceptions, stdenv, text, transformers + ({ mkDerivation, base, conduit, dlist, lib, mtl, parsers, safe + , safe-exceptions, text, transformers }: mkDerivation { pname = "conduit-parse"; @@ -7715,105 +8770,107 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/k0ral/conduit-parse"; description = "Parsing framework based on conduit"; - license = stdenv.lib.licenses.publicDomain; - }) {}; - "conduit-throttle" = callPackage - ({ mkDerivation, async, base, conduit, conduit-combinators - , conduit-extra, monad-control, resourcet, stdenv, stm, stm-chans - , throttle-io-stream, unliftio, unliftio-core - }: - mkDerivation { - pname = "conduit-throttle"; - version = "0.3.1.0"; - sha256 = "8dd6d616f5ddce25668bb34069bfdcdfe2a866c8d708b725a9b2e450a95aa329"; - libraryHaskellDepends = [ - async base conduit conduit-combinators conduit-extra monad-control - resourcet stm stm-chans throttle-io-stream unliftio unliftio-core - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/mtesseract/conduit-throttle#readme"; - description = "Throttle Conduit Producers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.publicDomain; }) {}; "conduit-zstd" = callPackage - ({ mkDerivation, base, bytestring, conduit, stdenv, zstd }: + ({ mkDerivation, base, bytestring, conduit, lib, zstd }: mkDerivation { pname = "conduit-zstd"; - version = "0.0.1.1"; - sha256 = "8681f59d08399f92478329b0cdd555ae5a1b7d12ef8acee423fcc10192e00712"; + version = "0.0.2.0"; + sha256 = "d407d9668c6d8dbd1772f3116699600162af1decf7ba8ad8187ceaa13fc91138"; libraryHaskellDepends = [ base bytestring conduit zstd ]; doHaddock = false; doCheck = false; homepage = "https://github.com/luispedro/conduit-zstd#readme"; description = "Conduit-based ZStd Compression"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "confcrypt" = callPackage - ({ mkDerivation, amazonka, amazonka-kms, base, base64-bytestring - , bytestring, conduit, containers, crypto-pubkey-openssh - , crypto-pubkey-types, cryptonite, deepseq, lens, megaparsec, mtl - , optparse-applicative, parser-combinators, stdenv, text - , transformers + "conferer" = callPackage + ({ mkDerivation, base, bytestring, containers, directory, filepath + , lib, text }: mkDerivation { - pname = "confcrypt"; - version = "0.1.0.4"; - sha256 = "6b358692cf5ab9bd92094df93aa774dcfa846577a5eb291dbe02206eafec45b0"; - isLibrary = true; - isExecutable = true; + pname = "conferer"; + version = "1.1.0.0"; + sha256 = "09c0ac36d8be0a24983f51a90624d80dc6c5886ec625d1f65f3530953bce6dc2"; + revision = "1"; + editedCabalFile = "0xr6910zn9j07gwc9f9dmlgxiagirmpzjzb9vlaqc0qvpawgq201"; libraryHaskellDepends = [ - amazonka amazonka-kms base base64-bytestring bytestring conduit - containers crypto-pubkey-openssh crypto-pubkey-types cryptonite - deepseq lens megaparsec mtl optparse-applicative parser-combinators - text transformers - ]; - executableHaskellDepends = [ - amazonka amazonka-kms base base64-bytestring bytestring conduit - containers crypto-pubkey-openssh crypto-pubkey-types cryptonite - deepseq lens megaparsec mtl optparse-applicative parser-combinators - text transformers + base bytestring containers directory filepath text ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/https://github.com/collegevine/confcrypt#readme"; - license = stdenv.lib.licenses.mit; + homepage = "https://conferer.ludat.io"; + description = "Configuration management library"; + license = lib.licenses.mpl20; }) {}; - "configuration-tools" = callPackage - ({ mkDerivation, aeson, ansi-wl-pprint, attoparsec, base - , base-unicode-symbols, base64-bytestring, bytestring, Cabal - , case-insensitive, connection, data-default, deepseq, directory - , dlist, enclosed-exceptions, filepath, http-client - , http-client-tls, http-types, monad-control, mtl, network-uri - , optparse-applicative, process, profunctors, semigroups, stdenv - , text, tls, transformers, unordered-containers, x509, x509-system - , x509-validation, yaml + "conferer-aeson" = callPackage + ({ mkDerivation, aeson, base, bytestring, conferer, directory, lib + , text, unordered-containers, vector }: mkDerivation { - pname = "configuration-tools"; - version = "0.4.0"; - sha256 = "fdb68289ee0a681269e3e4c4d89159b2717f962b7a89515bfa303f06dbda5d2f"; - setupHaskellDepends = [ - base bytestring Cabal directory filepath process + pname = "conferer-aeson"; + version = "1.1.0.1"; + sha256 = "47977475b732659e65ebf39bc796b718a41c95bc50e69068f3483165d7139fea"; + libraryHaskellDepends = [ + aeson base bytestring conferer directory text unordered-containers + vector ]; + doHaddock = false; + doCheck = false; + homepage = "https://conferer.ludat.io"; + description = "conferer's source for reading json files"; + license = lib.licenses.mpl20; + }) {}; + "conferer-hspec" = callPackage + ({ mkDerivation, base, conferer, hspec-core, lib, text }: + mkDerivation { + pname = "conferer-hspec"; + version = "1.1.0.0"; + sha256 = "65e0de0e17cc68c1294ee5361e64f8f8669f5aad5fcc6c28ed59b0e19a113b61"; + libraryHaskellDepends = [ base conferer hspec-core text ]; + doHaddock = false; + doCheck = false; + homepage = "https://conferer.ludat.io"; + description = "conferer's FromConfig instances for hspec Config"; + license = lib.licenses.mpl20; + }) {}; + "conferer-warp" = callPackage + ({ mkDerivation, base, conferer, http-types, lib, text, wai, warp + }: + mkDerivation { + pname = "conferer-warp"; + version = "1.1.0.0"; + sha256 = "b29ab3e6b8ac43547f2462cc1dd601912daa2dcf4060c33fef27cb2404ee6f7d"; + libraryHaskellDepends = [ base conferer http-types text wai warp ]; + doHaddock = false; + doCheck = false; + homepage = "https://conferer.ludat.io"; + description = "conferer's FromConfig instances for warp settings"; + license = lib.licenses.mpl20; + }) {}; + "config-ini" = callPackage + ({ mkDerivation, base, containers, lib, megaparsec, text + , transformers, unordered-containers + }: + mkDerivation { + pname = "config-ini"; + version = "0.2.4.0"; + sha256 = "6e5194e8acb7d189f0904852138990d03b64f86b9fde8f591ee1341d5627d535"; + revision = "2"; + editedCabalFile = "0iwraaa0y1b3xdsg760j1wpylkqshky0k2djcg0k4s97lrwqpbcz"; libraryHaskellDepends = [ - aeson ansi-wl-pprint attoparsec base base-unicode-symbols - base64-bytestring bytestring Cabal case-insensitive connection - data-default deepseq directory dlist enclosed-exceptions filepath - http-client http-client-tls http-types monad-control mtl - network-uri optparse-applicative process profunctors semigroups - text tls transformers unordered-containers x509 x509-system - x509-validation yaml + base containers megaparsec text transformers unordered-containers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/alephcloud/hs-configuration-tools"; - description = "Tools for specifying and parsing configurations"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/aisamanra/config-ini"; + description = "A library for simple INI-based configuration files"; + license = lib.licenses.bsd3; }) {}; "configurator" = callPackage ({ mkDerivation, attoparsec, base, bytestring, directory, hashable - , stdenv, text, unix-compat, unordered-containers + , lib, text, unix-compat, unordered-containers }: mkDerivation { pname = "configurator"; @@ -7828,11 +8885,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/bos/configurator"; description = "Configuration management"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "configurator-export" = callPackage - ({ mkDerivation, base, base-compat, configurator, pretty - , semigroups, stdenv, text, unordered-containers + ({ mkDerivation, base, base-compat, configurator, lib, pretty + , semigroups, text, unordered-containers }: mkDerivation { pname = "configurator-export"; @@ -7846,30 +8903,49 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/mstksg/configurator-export"; description = "Pretty printer and exporter for configurations from the \"configurator\" library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "configurator-pg" = callPackage + ({ mkDerivation, base, containers, lib, megaparsec, protolude + , scientific, text + }: + mkDerivation { + pname = "configurator-pg"; + version = "0.2.5"; + sha256 = "5563751bbaeb4be5aaf0333bd8b274886198a1f52ae78235841b7dd77f7aadf2"; + libraryHaskellDepends = [ + base containers megaparsec protolude scientific text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/robx/configurator-pg"; + description = "Reduced parser for configurator-ng config files"; + license = lib.licenses.bsd3; }) {}; "connection" = callPackage - ({ mkDerivation, base, byteable, bytestring, containers - , data-default-class, network, socks, stdenv, tls, x509, x509-store + ({ mkDerivation, base, basement, bytestring, containers + , data-default-class, lib, network, socks, tls, x509, x509-store , x509-system, x509-validation }: mkDerivation { pname = "connection"; - version = "0.2.8"; - sha256 = "70b1f44e8786320c18b26fc5d4ec115fc8ac016ba1f852fa8137f55d785a93eb"; + version = "0.3.1"; + sha256 = "5d759589c532c34d87bfc4f6fcb732bf55b55a93559d3b94229e8347a15375d9"; + revision = "1"; + editedCabalFile = "08f1n38zryd0jklyv3yillilp040zxfxha6jphrmf28haq2irnk5"; libraryHaskellDepends = [ - base byteable bytestring containers data-default-class network + base basement bytestring containers data-default-class network socks tls x509 x509-store x509-system x509-validation ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/vincenthz/hs-connection"; + homepage = "https://github.com/vincenthz/hs-connection"; description = "Simple and easy network connections API"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "connection-pool" = callPackage - ({ mkDerivation, base, between, data-default-class, monad-control - , network, resource-pool, stdenv, streaming-commons, time + ({ mkDerivation, base, between, data-default-class, lib + , monad-control, network, resource-pool, streaming-commons, time , transformers-base }: mkDerivation { @@ -7884,10 +8960,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/trskop/connection-pool"; description = "Connection pool built on top of resource-pool and streaming-commons"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "console-style" = callPackage - ({ mkDerivation, base, mtl, stdenv, transformers }: + ({ mkDerivation, base, lib, mtl, transformers }: mkDerivation { pname = "console-style"; version = "0.0.2.1"; @@ -7897,73 +8973,123 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/minad/console-style#readme"; description = "Styled console text output using ANSI escape sequences"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "constraint" = callPackage - ({ mkDerivation, base, category, stdenv, unconstrained }: + ({ mkDerivation, base, category, lib, unconstrained }: mkDerivation { pname = "constraint"; - version = "0.1.3.0"; - sha256 = "de53772aad12dc4a4542d6372a21b46a924019ac0622e8993db77498de4ee07a"; + version = "0.1.4.0"; + sha256 = "2467002144d7fa5e107c04bd5c64088334879d71e98d20365029fb777f63b631"; + revision = "1"; + editedCabalFile = "0ivca43m1lqi75462z4hacvzs27whqzjnby7y7jjji8kqaw8wlda"; libraryHaskellDepends = [ base category unconstrained ]; doHaddock = false; doCheck = false; description = "Reified constraints"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "constraint-tuples" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "constraint-tuples"; + version = "0.1.2"; + sha256 = "6262fe19dbacdaf3e0e2343d6db692f921560eca57a28706abc3857330f0c999"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/RyanGlScott/constraint-tuples"; + description = "Partially applicable constraint tuples"; + license = lib.licenses.bsd3; }) {}; "constraints" = callPackage - ({ mkDerivation, base, binary, deepseq, ghc-prim, hashable, mtl - , semigroups, stdenv, transformers, transformers-compat + ({ mkDerivation, base, binary, deepseq, ghc-prim, hashable, lib + , mtl, transformers, transformers-compat, type-equality }: mkDerivation { pname = "constraints"; - version = "0.10.1"; - sha256 = "5880ec261e053841b307c7c8c59614f46c2efbd5189f0f2a3c817589cedec3f7"; + version = "0.13"; + sha256 = "9259af54682f2673931978d96074c147406b1e18bd9111903fcaefe9252a6590"; libraryHaskellDepends = [ - base binary deepseq ghc-prim hashable mtl semigroups transformers - transformers-compat + base binary deepseq ghc-prim hashable mtl transformers + transformers-compat type-equality ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/constraints/"; description = "Constraint manipulation"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; + }) {}; + "constraints-extras" = callPackage + ({ mkDerivation, aeson, base, constraints, lib, template-haskell }: + mkDerivation { + pname = "constraints-extras"; + version = "0.3.1.0"; + sha256 = "7a5666a0905a0eb949a620ab899ec990c009e5d84841539012adceebbbea2143"; + revision = "1"; + editedCabalFile = "1hcaj1yk4f64v388zq2pd34ljkm68zds3vd8a3yhqr0xgr1wy3y7"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base constraints template-haskell ]; + executableHaskellDepends = [ aeson base constraints ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/obsidiansystems/constraints-extras"; + description = "Utility package for constraints"; + license = lib.licenses.bsd3; + }) {}; + "construct" = callPackage + ({ mkDerivation, attoparsec, base, bytestring, Cabal, cabal-doctest + , cereal, incremental-parser, input-parsers, lib, monoid-subclasses + , parsers, rank2classes, text + }: + mkDerivation { + pname = "construct"; + version = "0.3.0.2"; + sha256 = "f2882037833de03a2036c05897c731c926b2a8ea1edfe6df78bfead4d323cfe2"; + enableSeparateDataOutput = true; + setupHaskellDepends = [ base Cabal cabal-doctest ]; + libraryHaskellDepends = [ + attoparsec base bytestring cereal incremental-parser input-parsers + monoid-subclasses parsers rank2classes text + ]; + doHaddock = false; + doCheck = false; + description = "Haskell version of the Construct library for easy specification of file formats"; + license = lib.licenses.bsd3; }) {}; "contravariant" = callPackage - ({ mkDerivation, base, StateVar, stdenv, transformers }: + ({ mkDerivation, base, lib, StateVar, transformers }: mkDerivation { pname = "contravariant"; - version = "1.5"; - sha256 = "6ef067b692ad69ffff294b953aa85f3ded459d4ae133c37896222a09280fc3c2"; + version = "1.5.3"; + sha256 = "44536f0e331fde471271937323dc90409e95d47f57e42657fdaf242a0fd65dc1"; libraryHaskellDepends = [ base StateVar transformers ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/contravariant/"; description = "Contravariant functors"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "contravariant-extras" = callPackage - ({ mkDerivation, base, base-prelude, contravariant, semigroups - , stdenv, template-haskell, tuple-th + ({ mkDerivation, base, contravariant, lib, template-haskell + , template-haskell-compat-v0208 }: mkDerivation { pname = "contravariant-extras"; - version = "0.3.4"; - sha256 = "36a9239d5a84bc6a418a3aa1a0df145d76ece24d00b76deb817b92441913e63d"; - revision = "1"; - editedCabalFile = "1h2955ahga6i4fn7k8v66l03v77p6fhsac6ck8gpabkc08ij60wp"; + version = "0.3.5.2"; + sha256 = "e9cb90b7ede2d491c8bb2a9d44ab151c8a5d89d35a74703d38488a94c0fb7c46"; libraryHaskellDepends = [ - base base-prelude contravariant semigroups template-haskell - tuple-th + base contravariant template-haskell template-haskell-compat-v0208 ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nikita-volkov/contravariant-extras"; description = "Extras for the \"contravariant\" package"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "control-bool" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "control-bool"; version = "0.2.1"; @@ -7973,10 +9099,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/fumieval/control-bool"; description = "Useful combinators for boolean expressions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "control-dsl" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "control-dsl"; version = "0.2.1.3"; @@ -7988,10 +9114,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/Atry/Control.Dsl#readme"; description = "An alternative to monads in do-notation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "control-monad-free" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "control-monad-free"; version = "0.6.2"; @@ -8001,24 +9127,24 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/pepeiborra/control-monad-free"; description = "Free monads and monad transformers"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "control-monad-omega" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "control-monad-omega"; - version = "0.3.1"; - sha256 = "383b98ecf5db5add42f318672af9eb1c8b9d99ec42d48c240e209a93b5cf1186"; + version = "0.3.2"; + sha256 = "f62c1e4607481041b66a4c7afd1e4cb1fef72669c142fe73301c84bdfd17a9ff"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "http://github.com/luqui/control-monad-omega"; description = "A breadth-first list monad"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "convertible" = callPackage - ({ mkDerivation, base, bytestring, containers, mtl, old-locale - , old-time, stdenv, text, time + ({ mkDerivation, base, bytestring, containers, lib, mtl, old-locale + , old-time, text, time }: mkDerivation { pname = "convertible"; @@ -8033,16 +9159,16 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://hackage.haskell.org/package/convertible"; description = "Typeclasses and instances for converting between types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cookie" = callPackage - ({ mkDerivation, base, bytestring, data-default-class, deepseq - , stdenv, text, time + ({ mkDerivation, base, bytestring, data-default-class, deepseq, lib + , text, time }: mkDerivation { pname = "cookie"; - version = "0.4.4"; - sha256 = "3245ed04ae933cf7becede816d1f76043b851472700abf558ae90b28414cc0e3"; + version = "0.4.5"; + sha256 = "707f94d1b31018b91d6a1e9e19ef5413e20d02cab00ad93a5fd7d7b3b46a3583"; libraryHaskellDepends = [ base bytestring data-default-class deepseq text time ]; @@ -8050,96 +9176,110 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/snoyberg/cookie"; description = "HTTP cookie parsing and rendering"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "countable" = callPackage - ({ mkDerivation, base, stdenv }: + "core-data" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers, core-text + , hashable, lib, prettyprinter, scientific, text + , unordered-containers, vector + }: mkDerivation { - pname = "countable"; - version = "1.0"; - sha256 = "f9a0eb6f697a044bdf72e9c08126d4cb0f2d6de82cce07e55cb87ddbae6a0e6c"; - libraryHaskellDepends = [ base ]; + pname = "core-data"; + version = "0.2.1.9"; + sha256 = "392c23028ab698a5c6fdfb04a00e7db25f8a30ec8cadd3ef530356f244ef0b25"; + libraryHaskellDepends = [ + aeson base bytestring containers core-text hashable prettyprinter + scientific text unordered-containers vector + ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/AshleyYakeley/countable"; - description = "Countable, Searchable, Finite, Empty classes"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/aesiniath/unbeliever#readme"; + description = "Convenience wrappers around common data structures and encodings"; + license = lib.licenses.bsd3; }) {}; - "country" = callPackage - ({ mkDerivation, aeson, attoparsec, base, bytestring, deepseq - , ghc-prim, hashable, primitive, scientific, stdenv, text - , unordered-containers + "core-program" = callPackage + ({ mkDerivation, async, base, bytestring, chronologique, core-data + , core-text, directory, exceptions, filepath, fsnotify, hashable + , hourglass, lib, mtl, prettyprinter, safe-exceptions, stm + , template-haskell, terminal-size, text, text-short, transformers + , unix }: mkDerivation { - pname = "country"; - version = "0.1.6"; - sha256 = "09b36e30dfb1fa5fa7a2c5c38f316a70e0c740b8a4dd6e340abe9770ad149928"; - revision = "1"; - editedCabalFile = "04a2s0zlm4garihnm3xl9avf88vjnbvpsyb2ckk3z7ydjq0y3938"; + pname = "core-program"; + version = "0.2.7.1"; + sha256 = "ab105088ceb8ceeb68f1654b77a0a730e14d34c6a2d0ab73fd516656db2aa7ae"; libraryHaskellDepends = [ - aeson attoparsec base bytestring deepseq ghc-prim hashable - primitive scientific text unordered-containers + async base bytestring chronologique core-data core-text directory + exceptions filepath fsnotify hashable hourglass mtl prettyprinter + safe-exceptions stm template-haskell terminal-size text text-short + transformers unix ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/andrewthad/country#readme"; - description = "Country data type and functions"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/aesiniath/unbeliever#readme"; + description = "Opinionated Haskell Interoperability"; + license = lib.licenses.bsd3; }) {}; - "courier" = callPackage - ({ mkDerivation, async, base, bytestring, cereal, containers - , hslogger, network, stdenv, stm, text, uuid + "core-text" = callPackage + ({ mkDerivation, ansi-terminal, base, bytestring, colour, deepseq + , fingertree, hashable, lib, prettyprinter, template-haskell, text + , text-short }: mkDerivation { - pname = "courier"; - version = "0.1.1.5"; - sha256 = "ac9e674ff33de347b173da2892859b3807a408b341d10d6101d2a7d07ac334d3"; - isLibrary = true; - isExecutable = true; + pname = "core-text"; + version = "0.3.0.0"; + sha256 = "3dd8075b65a9436fe64ae4bd1b06945db59a68f70839105ba2014eb856686e80"; libraryHaskellDepends = [ - async base bytestring cereal containers hslogger network stm text - uuid + ansi-terminal base bytestring colour deepseq fingertree hashable + prettyprinter template-haskell text text-short ]; - executableHaskellDepends = [ base cereal ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/hargettp/courier"; - description = "A message-passing library for simplifying network applications"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/aesiniath/unbeliever#readme"; + description = "A rope type based on a finger tree over UTF-8 fragments"; + license = lib.licenses.bsd3; }) {}; - "cpio-conduit" = callPackage - ({ mkDerivation, base, base16-bytestring, binary, bytestring - , conduit, conduit-extra, stdenv + "countable" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "countable"; + version = "1.0"; + sha256 = "f9a0eb6f697a044bdf72e9c08126d4cb0f2d6de82cce07e55cb87ddbae6a0e6c"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/AshleyYakeley/countable"; + description = "Countable, Searchable, Finite, Empty classes"; + license = lib.licenses.bsd3; + }) {}; + "country" = callPackage + ({ mkDerivation, aeson, attoparsec, base, bytestring, deepseq + , hashable, lib, primitive, scientific, text, unordered-containers }: mkDerivation { - pname = "cpio-conduit"; - version = "0.7.0"; - sha256 = "8f0be7538b234496ef3b2fb2633336908ae99040ecb6d9832b3dbd1d0750f513"; + pname = "country"; + version = "0.2.1"; + sha256 = "6ae0d696a08bf3a34e6529b331e1f7bdaf59955e740802510530d6a7b8dc8959"; libraryHaskellDepends = [ - base base16-bytestring binary bytestring conduit conduit-extra + aeson attoparsec base bytestring deepseq hashable primitive + scientific text unordered-containers ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/da-x/cpio-conduit"; - description = "Conduit-based CPIO"; - license = stdenv.lib.licenses.asl20; + homepage = "https://github.com/andrewthad/country#readme"; + description = "Country data type and functions"; + license = lib.licenses.bsd3; }) {}; "cpphs" = callPackage - ({ mkDerivation, base, directory, old-locale, old-time, polyparse - , stdenv - }: + ({ mkDerivation, base, directory, lib, polyparse, time }: mkDerivation { pname = "cpphs"; - version = "1.20.8"; - sha256 = "e56d64a7d8058e0fb63f0669397c1c861efb20a0376e0e74d86942ac151105ae"; + version = "1.20.9.1"; + sha256 = "7f59b10bc3374004cee3c04fa4ee4a1b90d0dca84a3d0e436d5861a1aa3b919f"; isLibrary = true; isExecutable = true; - libraryHaskellDepends = [ - base directory old-locale old-time polyparse - ]; - executableHaskellDepends = [ - base directory old-locale old-time polyparse - ]; + libraryHaskellDepends = [ base directory polyparse time ]; + executableHaskellDepends = [ base directory polyparse time ]; doHaddock = false; doCheck = false; homepage = "http://projects.haskell.org/cpphs/"; @@ -8148,7 +9288,7 @@ inherit (pkgs.xorg) libXfixes;}; }) {}; "cprng-aes" = callPackage ({ mkDerivation, base, byteable, bytestring, cipher-aes - , crypto-random, stdenv + , crypto-random, lib }: mkDerivation { pname = "cprng-aes"; @@ -8162,10 +9302,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/vincenthz/hs-cprng-aes"; description = "Crypto Pseudo Random Number Generator using AES in counter mode"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cpu" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "cpu"; version = "0.1.2"; @@ -8178,84 +9318,57 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/vincenthz/hs-cpu"; description = "Cpu information and properties helpers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cpuinfo" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, deepseq, stdenv }: + ({ mkDerivation, attoparsec, base, bytestring, deepseq, lib }: mkDerivation { pname = "cpuinfo"; - version = "0.1.0.1"; - sha256 = "d1b3e3992cc0c82edfb21f30e1684bb66e6a3cb23a26b777a079702362d05655"; + version = "0.1.0.2"; + sha256 = "d97acf3f4b954c3539836e4646e7934f0c457829f8fd58a3ef4041c7de5ce324"; libraryHaskellDepends = [ attoparsec base bytestring deepseq ]; doHaddock = false; doCheck = false; homepage = "https://github.com/TravisWhitaker/cpuinfo"; description = "Haskell Library for Checking CPU Information"; - license = stdenv.lib.licenses.mit; - }) {}; - "cql" = callPackage - ({ mkDerivation, base, bytestring, cereal, containers, Decimal - , iproute, network, stdenv, template-haskell, text, time - , transformers, uuid, vector - }: - mkDerivation { - pname = "cql"; - version = "4.0.1"; - sha256 = "89294c6a6ed2c6f8c6037ee2ca4236d3606bf9019a39df9e39b7ad8dcd573808"; - libraryHaskellDepends = [ - base bytestring cereal containers Decimal iproute network - template-haskell text time transformers uuid vector - ]; - doHaddock = false; - doCheck = false; - homepage = "https://gitlab.com/twittner/cql/"; - description = "Cassandra CQL binary protocol"; - license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; + license = lib.licenses.mit; }) {}; - "cql-io" = callPackage - ({ mkDerivation, async, auto-update, base, bytestring, containers - , cql, cryptohash, data-default-class, exceptions, hashable - , HsOpenSSL, iproute, lens, monad-control, mtl, mwc-random, network - , retry, semigroups, stdenv, stm, text, time, tinylog, transformers - , transformers-base, unordered-containers, uuid, vector + "crackNum" = callPackage + ({ mkDerivation, base, directory, filepath, lib, libBF, process + , sbv, tasty, tasty-golden }: mkDerivation { - pname = "cql-io"; - version = "1.0.1.1"; - sha256 = "ac1353fc3ae4b182877aa518282ea1bd839cf5a3ffb936d6da4807b11d00bbcd"; - libraryHaskellDepends = [ - async auto-update base bytestring containers cql cryptohash - data-default-class exceptions hashable HsOpenSSL iproute lens - monad-control mtl mwc-random network retry semigroups stm text time - tinylog transformers transformers-base unordered-containers uuid - vector + pname = "crackNum"; + version = "3.1"; + sha256 = "33a30ed749177733fd447d3633796c5ad0509ca532ce24c0064c28163ea65be1"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ + base directory filepath libBF process sbv tasty tasty-golden ]; doHaddock = false; doCheck = false; - homepage = "https://gitlab.com/twittner/cql-io/"; - description = "Cassandra CQL client"; - license = stdenv.lib.licenses.mpl20; + homepage = "http://github.com/LeventErkok/CrackNum"; + description = "Crack various integer and floating-point data formats"; + license = lib.licenses.bsd3; }) {}; - "crackNum" = callPackage - ({ mkDerivation, array, base, FloatingHex, stdenv }: + "crc32c" = callPackage + ({ mkDerivation, base, bytestring, c2hs, lib }: mkDerivation { - pname = "crackNum"; - version = "2.3"; - sha256 = "428f25cfa0f7c4c126ee96fb9122966c2b175a194d59c200470a6f689ec038f3"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ array base FloatingHex ]; - executableHaskellDepends = [ array base FloatingHex ]; + pname = "crc32c"; + version = "0.0.0"; + sha256 = "0908682d921cc79249704d8b34fba918f399ad25321376b3a96b471a624500f8"; + libraryHaskellDepends = [ base bytestring ]; + libraryToolDepends = [ c2hs ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/LeventErkok/CrackNum"; - description = "Crack various integer, floating-point data formats"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/leptonyu/crc32c#readme"; + description = "Haskell bindings for crc32c"; + license = lib.licenses.bsd3; }) {}; "credential-store" = callPackage ({ mkDerivation, base, bytestring, containers, cryptonite, dbus - , memory, safe-exceptions, stdenv + , lib, memory, safe-exceptions }: mkDerivation { pname = "credential-store"; @@ -8271,29 +9384,32 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/rblaze/credential-store#readme"; description = "Library to access secure credential storage providers"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; }) {}; "criterion" = callPackage ({ mkDerivation, aeson, ansi-wl-pprint, base, base-compat-batteries - , binary, bytestring, cassava, code-page, containers - , criterion-measurement, deepseq, directory, exceptions, filepath - , Glob, js-flot, js-jquery, microstache, mtl, mwc-random - , optparse-applicative, parsec, statistics, stdenv, text, time + , binary, binary-orphans, bytestring, cassava, code-page + , containers, criterion-measurement, deepseq, directory, exceptions + , filepath, Glob, js-chart, lib, microstache, mtl, mwc-random + , optparse-applicative, parsec, statistics, text, time , transformers, transformers-compat, vector, vector-algorithms }: mkDerivation { pname = "criterion"; - version = "1.5.3.0"; - sha256 = "b602a99439de710778b8d8ad4a3799caf872db4c8c793bfd13b725aa936c049f"; + version = "1.5.9.0"; + sha256 = "21e3f781bbefb7ea165968f3b606e00f049bdb031bc76ae6dfa3059521f51462"; + revision = "1"; + editedCabalFile = "140444pqw65vsqpa168c13cljb66rdgvq41mxnvds296wxq2yz7i"; isLibrary = true; isExecutable = true; enableSeparateDataOutput = true; libraryHaskellDepends = [ - aeson ansi-wl-pprint base base-compat-batteries binary bytestring - cassava code-page containers criterion-measurement deepseq - directory exceptions filepath Glob js-flot js-jquery microstache - mtl mwc-random optparse-applicative parsec statistics text time - transformers transformers-compat vector vector-algorithms + aeson ansi-wl-pprint base base-compat-batteries binary + binary-orphans bytestring cassava code-page containers + criterion-measurement deepseq directory exceptions filepath Glob + js-chart microstache mtl mwc-random optparse-applicative parsec + statistics text time transformers transformers-compat vector + vector-algorithms ]; executableHaskellDepends = [ base base-compat-batteries optparse-applicative @@ -8302,33 +9418,33 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://www.serpentine.com/criterion"; description = "Robust, reliable performance measurement and analysis"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "criterion-measurement" = callPackage ({ mkDerivation, aeson, base, base-compat, binary, containers - , deepseq, stdenv, vector + , deepseq, lib, vector }: mkDerivation { pname = "criterion-measurement"; - version = "0.1.1.0"; - sha256 = "f5f87769386a927dbf487d2f256fc6804f2902078e86dcf113e35178a582ab56"; + version = "0.1.3.0"; + sha256 = "7db86e86cb01a62d76f5d67d03cc817565d89016b6bc9135e85af4562f93d5b9"; libraryHaskellDepends = [ aeson base base-compat binary containers deepseq vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/bos/criterion"; + homepage = "https://github.com/haskell/criterion"; description = "Criterion measurement functionality and associated types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cron" = callPackage - ({ mkDerivation, attoparsec, base, data-default-class, mtl - , mtl-compat, old-locale, semigroups, stdenv, text, time + ({ mkDerivation, attoparsec, base, data-default-class, lib, mtl + , mtl-compat, old-locale, semigroups, text, time }: mkDerivation { pname = "cron"; - version = "0.6.1"; - sha256 = "8c1af53bde729026809b722468f6b36c4f96cb532f26a390f32f1c91fb8b3251"; + version = "0.7.0"; + sha256 = "a5cd48c6fd119430aa8fbd059654806f0f391642df03516d9b3021dfaf581239"; libraryHaskellDepends = [ attoparsec base data-default-class mtl mtl-compat old-locale semigroups text time @@ -8337,29 +9453,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/michaelxavier/cron"; description = "Cron datatypes and Attoparsec parser"; - license = stdenv.lib.licenses.mit; - }) {}; - "crypt-sha512" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, cryptohash-sha512 - , stdenv - }: - mkDerivation { - pname = "crypt-sha512"; - version = "0"; - sha256 = "c2be6252bf12f38c74950eb778039426c730e9a7cd7f034a4cc3e6965d5255f3"; - revision = "2"; - editedCabalFile = "071lxiwsf23ga1fkbjd47ykz7f5irhsh7q7zz2qczzjgnvzadadh"; - libraryHaskellDepends = [ - attoparsec base bytestring cryptohash-sha512 - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/phadej/crypt-sha512"; - description = "Pure Haskell implelementation for GNU SHA512 crypt algorithm"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; "crypto-api" = callPackage - ({ mkDerivation, base, bytestring, cereal, entropy, stdenv, tagged + ({ mkDerivation, base, bytestring, cereal, entropy, lib, tagged , transformers }: mkDerivation { @@ -8375,51 +9472,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/TomMD/crypto-api"; description = "A generic interface for cryptographic operations"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "crypto-api-tests" = callPackage - ({ mkDerivation, base, bytestring, cereal, crypto-api, directory - , filepath, HUnit, QuickCheck, stdenv, test-framework - , test-framework-hunit, test-framework-quickcheck2 - }: - mkDerivation { - pname = "crypto-api-tests"; - version = "0.3"; - sha256 = "f44aecdd4ceb9da9f38330e84d9c17745a82b0611085ebb34442d2dce4207270"; - enableSeparateDataOutput = true; - libraryHaskellDepends = [ - base bytestring cereal crypto-api directory filepath HUnit - QuickCheck test-framework test-framework-hunit - test-framework-quickcheck2 - ]; - doHaddock = false; - doCheck = false; - homepage = "http://trac.haskell.org/crypto-api/wiki"; - description = "A test framework and KATs for cryptographic operations"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "crypto-cipher-tests" = callPackage - ({ mkDerivation, base, byteable, bytestring, crypto-cipher-types - , HUnit, mtl, QuickCheck, securemem, stdenv, test-framework - , test-framework-hunit, test-framework-quickcheck2 - }: - mkDerivation { - pname = "crypto-cipher-tests"; - version = "0.0.11"; - sha256 = "dfb670b73d4091b8683634d0d4d5a40576d573ad160650d5e518244ced8b98a7"; - libraryHaskellDepends = [ - base byteable bytestring crypto-cipher-types HUnit mtl QuickCheck - securemem test-framework test-framework-hunit - test-framework-quickcheck2 - ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/vincenthz/hs-crypto-cipher"; - description = "Generic cryptography cipher tests"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "crypto-cipher-types" = callPackage - ({ mkDerivation, base, byteable, bytestring, securemem, stdenv }: + ({ mkDerivation, base, byteable, bytestring, lib, securemem }: mkDerivation { pname = "crypto-cipher-types"; version = "0.0.9"; @@ -8430,16 +9486,18 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/vincenthz/hs-crypto-cipher"; description = "Generic cryptography cipher types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "crypto-enigma" = callPackage - ({ mkDerivation, ansi-terminal, base, containers - , optparse-applicative, split, stdenv, text + ({ mkDerivation, ansi-terminal, base, containers, lib + , optparse-applicative, split, text }: mkDerivation { pname = "crypto-enigma"; - version = "0.1.1.5"; - sha256 = "829a349dc7945cb257300ba97f9701863b3ca12ed3b7b3093199bb6709a23300"; + version = "0.1.1.6"; + sha256 = "5fec48245fd75d91ed1ac953fb21834eff3dc0b13b5bd100155ce4f4f8cd1d1f"; + revision = "7"; + editedCabalFile = "1i5vlza8rl6a4wz4v3l61m6x7phbv1ly0di0cf3v3amz38x828qz"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base containers split text ]; @@ -8450,29 +9508,47 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/orome/crypto-enigma-hs"; description = "An Enigma machine simulator with display"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "crypto-pubkey-openssh" = callPackage - ({ mkDerivation, asn1-encoding, asn1-types, attoparsec, base - , base64-bytestring, bytestring, cereal, crypto-pubkey-types, pem - , stdenv + "crypto-numbers" = callPackage + ({ mkDerivation, base, bytestring, crypto-random, ghc-prim + , integer-gmp, lib, vector }: mkDerivation { - pname = "crypto-pubkey-openssh"; + pname = "crypto-numbers"; version = "0.2.7"; - sha256 = "849085c854c561b94974f2086bf1ad4004fb17be7168b75068ab0f2a330bab59"; + sha256 = "420aeb17e9cdcfdf8c950c6c6f10c54503c5524d36f611aa7238e3fd65f189a6"; + revision = "1"; + editedCabalFile = "1jjkhid8kwrz5894nad537rqxzzyx6b687bmgyk70nv0ny336j9b"; + libraryHaskellDepends = [ + base bytestring crypto-random ghc-prim integer-gmp vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/vincenthz/hs-crypto-numbers"; + description = "Cryptographic numbers: functions and algorithms"; + license = lib.licenses.bsd3; + }) {}; + "crypto-pubkey" = callPackage + ({ mkDerivation, base, byteable, bytestring, crypto-numbers + , crypto-pubkey-types, crypto-random, cryptohash, lib + }: + mkDerivation { + pname = "crypto-pubkey"; + version = "0.2.8"; + sha256 = "c0ccf2f5c38517de1f1626cb0a2542f35aefad8842f8ad5c1fac0b8c9de8b56e"; libraryHaskellDepends = [ - asn1-encoding asn1-types attoparsec base base64-bytestring - bytestring cereal crypto-pubkey-types pem + base byteable bytestring crypto-numbers crypto-pubkey-types + crypto-random cryptohash ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/knsd/crypto-pubkey-openssh"; - description = "OpenSSH keys decoder/encoder"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/vincenthz/hs-crypto-pubkey"; + description = "Public Key cryptography"; + license = lib.licenses.bsd3; }) {}; "crypto-pubkey-types" = callPackage - ({ mkDerivation, asn1-encoding, asn1-types, base, stdenv }: + ({ mkDerivation, asn1-encoding, asn1-types, base, lib }: mkDerivation { pname = "crypto-pubkey-types"; version = "0.4.3"; @@ -8482,11 +9558,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/vincenthz/hs-crypto-pubkey-types"; description = "Generic cryptography Public keys algorithm types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "crypto-random" = callPackage - ({ mkDerivation, base, bytestring, securemem, stdenv, unix, vector - }: + ({ mkDerivation, base, bytestring, lib, securemem, unix, vector }: mkDerivation { pname = "crypto-random"; version = "0.0.9"; @@ -8498,10 +9573,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/vincenthz/hs-crypto-random"; description = "Simple cryptographic random related types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "crypto-random-api" = callPackage - ({ mkDerivation, base, bytestring, entropy, stdenv }: + ({ mkDerivation, base, bytestring, entropy, lib }: mkDerivation { pname = "crypto-random-api"; version = "0.2.0"; @@ -8511,48 +9586,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/vincenthz/hs-crypto-random-api"; description = "Simple random generators API for cryptography related code"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "cryptocipher" = callPackage - ({ mkDerivation, base, cipher-aes, cipher-blowfish, cipher-camellia - , cipher-des, cipher-rc4, crypto-cipher-types, stdenv - }: - mkDerivation { - pname = "cryptocipher"; - version = "0.6.2"; - sha256 = "34b9e62dee36c4019dd0c0e86576295d0bd1bb573eeb24686ec635a09550e346"; - libraryHaskellDepends = [ - base cipher-aes cipher-blowfish cipher-camellia cipher-des - cipher-rc4 crypto-cipher-types - ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/vincenthz/hs-crypto-cipher"; - description = "Symmetrical block and stream ciphers"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "cryptocompare" = callPackage - ({ mkDerivation, aeson, base, bytestring, containers, directory - , exceptions, http-conduit, MissingH, stdenv, text, time - , transformers, unordered-containers - }: - mkDerivation { - pname = "cryptocompare"; - version = "0.1.1"; - sha256 = "d12e0f6fd133e538852e5700b0a31d81c6885dc8b1e9e88d1b331dcec38316b3"; - libraryHaskellDepends = [ - aeson base bytestring containers directory exceptions http-conduit - MissingH text time transformers unordered-containers - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/aviaviavi/cryptocompare"; - description = "Haskell wrapper for the cryptocompare API"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.bsd3; }) {}; "cryptohash" = callPackage ({ mkDerivation, base, byteable, bytestring, cryptonite, ghc-prim - , memory, stdenv + , lib, memory }: mkDerivation { pname = "cryptohash"; @@ -8565,11 +9603,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/vincenthz/hs-cryptohash"; description = "collection of crypto hashes, fast, pure and practical"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cryptohash-cryptoapi" = callPackage ({ mkDerivation, base, bytestring, cereal, crypto-api, cryptonite - , memory, stdenv, tagged + , lib, memory, tagged }: mkDerivation { pname = "cryptohash-cryptoapi"; @@ -8583,46 +9621,47 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/vincenthz/hs-cryptohash-cryptoapi"; description = "Crypto-api interfaces for cryptohash"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cryptohash-md5" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "cryptohash-md5"; version = "0.11.100.1"; sha256 = "710bd48770fa3e9a3b05428c6dc77fb72c91956d334a1eb89ded11bb843e18f9"; - revision = "3"; - editedCabalFile = "0ld224mdmw9mgzcl20q82rqkyl7d5vmi1iknsyymq58gcvcwdi2m"; + revision = "6"; + editedCabalFile = "191nvffcrlyvr5dq99bbdxxl2qx44bla9adkhklyknf7ipqdd4yj"; libraryHaskellDepends = [ base bytestring ]; doHaddock = false; doCheck = false; homepage = "https://github.com/hvr/cryptohash-md5"; description = "Fast, pure and practical MD5 implementation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cryptohash-sha1" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "cryptohash-sha1"; version = "0.11.100.1"; sha256 = "3c79af33542512442f8f87f6abb1faef7cd43bbfb2859260a33251d861eb0dab"; - revision = "3"; - editedCabalFile = "0i30cc85732v27baibdjy2kjjkdfv335ib5sk5ggwvsysvvvr66l"; + revision = "6"; + editedCabalFile = "10rpxrmqgwihmplczglwxf5q3l13z9j3kvi065z884y4dymmnkgc"; libraryHaskellDepends = [ base bytestring ]; doHaddock = false; doCheck = false; homepage = "https://github.com/hvr/cryptohash-sha1"; description = "Fast, pure and practical SHA-1 implementation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cryptohash-sha256" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "cryptohash-sha256"; - version = "0.11.101.0"; - sha256 = "52756435dbea248e344fbcbcc5df5307f60dfacf337dfd11ae30f1c7a4da05dd"; - revision = "2"; - editedCabalFile = "0m5h68xm60wrjv88gg6cn1q5qki5674mxl4d6sn3vxpbcj9b5417"; + version = "0.11.102.0"; + sha256 = "8ad6e9875a9128f6cd66d65d80f9f85dd0559c73ac00bb37f71fbee820d10519"; + revision = "1"; + editedCabalFile = "0v5ppc7r2lxbk49h1kwj4b5vyb1dw2fnppykvp5m9rm0p3vhlykr"; + configureFlags = [ "-fuse-cbits" ]; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base bytestring ]; @@ -8630,31 +9669,31 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/hvr/cryptohash-sha256"; description = "Fast, pure and practical SHA-256 implementation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cryptohash-sha512" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "cryptohash-sha512"; version = "0.11.100.1"; sha256 = "10698bb9575eaa414a65d9644caa9408f9276c63447406e0a4faef91db1071a9"; - revision = "3"; - editedCabalFile = "19m1fp0i7ba84aa72d5wf59c7j0p4yr1bc43in8pspgywhsr3lfl"; + revision = "6"; + editedCabalFile = "0q9c08qd8ssl428ifa3g30r0lp81a8afcpyv7yzqjp88ihgcnfa6"; libraryHaskellDepends = [ base bytestring ]; doHaddock = false; doCheck = false; homepage = "https://github.com/hvr/cryptohash-sha512"; description = "Fast, pure and practical SHA-512 implementation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cryptonite" = callPackage ({ mkDerivation, base, basement, bytestring, deepseq, ghc-prim - , integer-gmp, memory, stdenv + , integer-gmp, lib, memory }: mkDerivation { pname = "cryptonite"; - version = "0.25"; - sha256 = "89be1a18af8730a7bfe4d718d7d5f6ce858e9df93a411566d15bf992db5a3c8c"; + version = "0.29"; + sha256 = "d83a021cdaae90f3734b725a03ac7b555e999809779ec197011d2da8e1b8b08f"; libraryHaskellDepends = [ base basement bytestring deepseq ghc-prim integer-gmp memory ]; @@ -8662,11 +9701,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/haskell-crypto/cryptonite"; description = "Cryptography Primitives sink"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cryptonite-conduit" = callPackage ({ mkDerivation, base, bytestring, conduit, conduit-extra - , cryptonite, exceptions, memory, resourcet, stdenv, transformers + , cryptonite, exceptions, lib, memory, resourcet, transformers }: mkDerivation { pname = "cryptonite-conduit"; @@ -8682,11 +9721,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/haskell-crypto/cryptonite-conduit"; description = "cryptonite conduit"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cryptonite-openssl" = callPackage - ({ mkDerivation, base, basement, bytestring, cryptonite, memory - , openssl, stdenv + ({ mkDerivation, base, basement, bytestring, cryptonite, lib + , memory, openssl }: mkDerivation { pname = "cryptonite-openssl"; @@ -8700,10 +9739,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/haskell-crypto/cryptonite-openssl"; description = "Crypto stuff using OpenSSL cryptographic library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) openssl;}; "csp" = callPackage - ({ mkDerivation, base, containers, mtl, nondeterminism, stdenv }: + ({ mkDerivation, base, containers, lib, mtl, nondeterminism }: mkDerivation { pname = "csp"; version = "1.4.0"; @@ -8715,21 +9754,21 @@ inherit (pkgs.xorg) libXfixes;}; license = "LGPL"; }) {}; "css-syntax" = callPackage - ({ mkDerivation, base, scientific, stdenv, text }: + ({ mkDerivation, base, lib, scientific, text }: mkDerivation { pname = "css-syntax"; version = "0.1.0.0"; sha256 = "50f386171dc691f2280a695eaafea64ba1ac1cc102fd702994b001f62d00c009"; - revision = "1"; - editedCabalFile = "14241m9nm3wbbhajw95gdj9mvfzf4hmrzvk2wgjvkm71mg4yhwnr"; + revision = "5"; + editedCabalFile = "1i3svb2zy7i3g2xrv8hki5dn6fd5rh2pwjxv72rbmbgl1adp3w3s"; libraryHaskellDepends = [ base scientific text ]; doHaddock = false; doCheck = false; description = "High-performance CSS tokenizer and serializer"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "css-text" = callPackage - ({ mkDerivation, attoparsec, base, stdenv, text }: + ({ mkDerivation, attoparsec, base, lib, text }: mkDerivation { pname = "css-text"; version = "0.1.3.0"; @@ -8739,10 +9778,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/yesodweb/css-text.git#readme"; description = "CSS parser and renderer"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "csv" = callPackage - ({ mkDerivation, base, filepath, parsec, stdenv }: + ({ mkDerivation, base, filepath, lib, parsec }: mkDerivation { pname = "csv"; version = "0.1.2"; @@ -8751,11 +9790,10 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "CSV loader and dumper"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "ctrie" = callPackage - ({ mkDerivation, atomic-primops, base, hashable, primitive, stdenv - }: + ({ mkDerivation, atomic-primops, base, hashable, lib, primitive }: mkDerivation { pname = "ctrie"; version = "0.2"; @@ -8765,17 +9803,17 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/mcschroeder/ctrie"; description = "Non-blocking concurrent map"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "cubicbezier" = callPackage - ({ mkDerivation, base, containers, fast-math, integration, matrices - , microlens, microlens-mtl, microlens-th, mtl, stdenv, vector + ({ mkDerivation, base, containers, fast-math, integration, lib + , matrices, microlens, microlens-mtl, microlens-th, mtl, vector , vector-space }: mkDerivation { pname = "cubicbezier"; - version = "0.6.0.5"; - sha256 = "c5c9825782d97c4059b2261dddd6471fdb270ddac0ff97d6d02d4f0d44b62758"; + version = "0.6.0.6"; + sha256 = "5a73fcde2b92ce138d924c323f04f48427acbfdc2c774ff0f032a10ea60afa68"; libraryHaskellDepends = [ base containers fast-math integration matrices microlens microlens-mtl microlens-th mtl vector vector-space @@ -8783,10 +9821,10 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Efficient manipulating of 2D cubic bezier curves"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cubicspline" = callPackage - ({ mkDerivation, base, hmatrix, safe, stdenv }: + ({ mkDerivation, base, hmatrix, lib, safe }: mkDerivation { pname = "cubicspline"; version = "0.1.2"; @@ -8795,29 +9833,11 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Natural cubic spline interpolation"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "cublas" = callPackage - ({ mkDerivation, base, c2hs, Cabal, cuda, directory, filepath, half - , stdenv, storable-complex, template-haskell - }: - mkDerivation { - pname = "cublas"; - version = "0.5.0.0"; - sha256 = "2e3c94f63fc6f7df9cc517b5a444342654d4314266fc46aabfad8c456be68768"; - setupHaskellDepends = [ base Cabal cuda directory filepath ]; - libraryHaskellDepends = [ - base cuda half storable-complex template-haskell - ]; - libraryToolDepends = [ c2hs ]; - doHaddock = false; - doCheck = false; - description = "FFI bindings to the CUDA BLAS library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "cuckoo-filter" = callPackage ({ mkDerivation, aeson, array, base, bytestring, cereal, containers - , criterion, hashable, random, stdenv, time + , criterion, hashable, lib, random, time }: mkDerivation { pname = "cuckoo-filter"; @@ -8836,72 +9856,31 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/ChrisCoffey/cuckoo-filter#readme"; description = "Pure and impure Cuckoo Filter"; - license = stdenv.lib.licenses.mit; - }) {}; - "cuda" = callPackage - ({ mkDerivation, base, bytestring, c2hs, Cabal, directory, filepath - , pretty, stdenv, template-haskell, uuid-types - }: - mkDerivation { - pname = "cuda"; - version = "0.10.0.0"; - sha256 = "a79fb18d33b8ec5862fdc4f74cde5a58e9057a035df51a10207d32659d40849e"; - isLibrary = true; - isExecutable = true; - setupHaskellDepends = [ base Cabal directory filepath ]; - libraryHaskellDepends = [ - base bytestring filepath template-haskell uuid-types - ]; - libraryToolDepends = [ c2hs ]; - executableHaskellDepends = [ base pretty ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/tmcdonell/cuda"; - description = "FFI binding to the CUDA interface for programming NVIDIA GPUs"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; "cue-sheet" = callPackage - ({ mkDerivation, base, bytestring, containers, data-default-class - , exceptions, megaparsec, mtl, QuickCheck, stdenv, text + ({ mkDerivation, base, bytestring, containers, exceptions, lib + , megaparsec, mtl, QuickCheck, text }: mkDerivation { pname = "cue-sheet"; - version = "2.0.0"; - sha256 = "14dbfc86fc5ec497c4dbacf03225f41a708366cc8c65e04ea5f27c9c79afcff0"; - revision = "1"; - editedCabalFile = "0cnlyy7psk8qcwahiqfdpaybvrw899bv106p0i53lrdjxfdsmf4g"; + version = "2.0.1"; + sha256 = "71e42497329b9ebf74e94920ed2bd7a2ffe15e385906a37cbd5160d607a5575d"; + revision = "3"; + editedCabalFile = "1v8yvvb9sdpkg7m6z5a4sf0hcss7swb318700ap0qc79qn4ifdqb"; enableSeparateDataOutput = true; libraryHaskellDepends = [ - base bytestring containers data-default-class exceptions megaparsec - mtl QuickCheck text + base bytestring containers exceptions megaparsec mtl QuickCheck + text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mrkkrp/cue-sheet"; description = "Support for construction, rendering, and parsing of CUE sheets"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "cufft" = callPackage - ({ mkDerivation, base, c2hs, Cabal, cuda, directory, filepath - , stdenv, template-haskell - }: - mkDerivation { - pname = "cufft"; - version = "0.9.0.1"; - sha256 = "c312aafe408d466eb32b15d9b59b805008f631147f7e0ef4ba2b8548540cc1b1"; - setupHaskellDepends = [ - base Cabal cuda directory filepath template-haskell - ]; - libraryHaskellDepends = [ base cuda ]; - libraryToolDepends = [ c2hs ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/robeverest/cufft"; - description = "Haskell bindings for the CUFFT library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "curl" = callPackage - ({ mkDerivation, base, bytestring, containers, curl, stdenv }: + ({ mkDerivation, base, bytestring, containers, curl, lib }: mkDerivation { pname = "curl"; version = "1.3.8"; @@ -8914,10 +9893,10 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Haskell binding to libcurl"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) curl;}; "currencies" = callPackage - ({ mkDerivation, base, stdenv, text }: + ({ mkDerivation, base, lib, text }: mkDerivation { pname = "currencies"; version = "0.2.0.0"; @@ -8927,11 +9906,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/alx741/currencies#readme"; description = "Currencies representation, pretty printing and conversion"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "currency" = callPackage ({ mkDerivation, base, containers, hashable, iso3166-country-codes - , stdenv + , lib }: mkDerivation { pname = "currency"; @@ -8945,27 +9924,76 @@ inherit (pkgs.xorg) libXfixes;}; homepage = "https://github.com/singpolyma/currency-haskell"; description = "Types representing standard and non-standard currencies"; license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; + hydraPlatforms = lib.platforms.none; }) {}; - "cusparse" = callPackage - ({ mkDerivation, base, c2hs, Cabal, cuda, directory, filepath, half - , stdenv, storable-complex + "cursor" = callPackage + ({ mkDerivation, base, containers, deepseq, lib, microlens, text + , validity, validity-containers, validity-text }: mkDerivation { - pname = "cusparse"; - version = "0.2.0.0"; - sha256 = "06ee8332c9a4f540a9566d09d0903034e06b080281902beb987170d65cb7d8f8"; - setupHaskellDepends = [ base Cabal cuda directory filepath ]; - libraryHaskellDepends = [ base cuda half storable-complex ]; - libraryToolDepends = [ c2hs ]; + pname = "cursor"; + version = "0.3.0.0"; + sha256 = "87aa3d15e212ca43da7d844225b7367610c3322471584ea3d3c1218af60d3dcd"; + libraryHaskellDepends = [ + base containers deepseq microlens text validity validity-containers + validity-text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/cursor"; + description = "Purely Functional Cursors"; + license = lib.licenses.mit; + }) {}; + "cursor-brick" = callPackage + ({ mkDerivation, base, brick, cursor, lib, text }: + mkDerivation { + pname = "cursor-brick"; + version = "0.1.0.0"; + sha256 = "eddb9169dfc71a2156ca13ad62f751a1b3a2e3e93afc0d80c3c948d6b2471105"; + libraryHaskellDepends = [ base brick cursor text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/cursor-brick#readme"; + license = lib.licenses.mit; + }) {}; + "cursor-fuzzy-time" = callPackage + ({ mkDerivation, base, containers, cursor, deepseq, fuzzy-time, lib + , megaparsec, microlens, text, time, validity, validity-time + }: + mkDerivation { + pname = "cursor-fuzzy-time"; + version = "0.0.0.0"; + sha256 = "fa959494f95f7c54a1da1766351e8559e3ec51fc9c6b3d8f23a76429f7b5a0f7"; + libraryHaskellDepends = [ + base containers cursor deepseq fuzzy-time megaparsec microlens text + time validity validity-time + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/fuzzy-time"; + license = lib.licenses.mit; + }) {}; + "cursor-gen" = callPackage + ({ mkDerivation, base, containers, cursor, genvalidity + , genvalidity-containers, genvalidity-text, lib, QuickCheck, text + }: + mkDerivation { + pname = "cursor-gen"; + version = "0.3.0.0"; + sha256 = "0bb3260332670621e293513d8c86c8ff9182329a4dc4245d8eb0a74efef5c76b"; + libraryHaskellDepends = [ + base containers cursor genvalidity genvalidity-containers + genvalidity-text QuickCheck text + ]; doHaddock = false; doCheck = false; - description = "FFI bindings to the CUDA Sparse BLAS library"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/NorfairKing/cursor"; + description = "Generators for Purely Functional Cursors"; + license = lib.licenses.mit; }) {}; "cutter" = callPackage - ({ mkDerivation, base, bytestring, explicit-exception, spreadsheet - , stdenv, utility-ht + ({ mkDerivation, base, bytestring, explicit-exception, lib + , spreadsheet, utility-ht }: mkDerivation { pname = "cutter"; @@ -8979,36 +10007,61 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Cut files according to a position list"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "cyclotomic" = callPackage + ({ mkDerivation, arithmoi, base, containers, lib }: + mkDerivation { + pname = "cyclotomic"; + version = "1.1.1"; + sha256 = "046db2a5553b0fd3c6a3ea4b0b010cb5d588abd2f321cc5681e8e813fb3969d4"; + libraryHaskellDepends = [ arithmoi base containers ]; + doHaddock = false; + doCheck = false; + description = "A subfield of the complex numbers for exact calculation"; + license = lib.licenses.gpl3Only; }) {}; "czipwith" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { pname = "czipwith"; - version = "1.0.1.1"; - sha256 = "4a148579f4ef822544b721a4b59f7a9e62a965e270dee9d2a54a98ceab494243"; + version = "1.0.1.3"; + sha256 = "2dc48540e574ebc924fe13ca2b08be103d228fd42ef90db2896e3727eb0f6687"; libraryHaskellDepends = [ base template-haskell ]; doHaddock = false; doCheck = false; homepage = "https://github.com/lspitzner/czipwith/"; description = "CZipWith class and deriving via TH"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "d10" = callPackage + ({ mkDerivation, base, lib, template-haskell }: + mkDerivation { + pname = "d10"; + version = "0.2.1.6"; + sha256 = "1e95119b7d960c2a5d8ec1caeed6261fafc6997bb1cee1ab57a5f37edd07e228"; + libraryHaskellDepends = [ base template-haskell ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/typeclasses/d10"; + description = "Digits 0-9"; + license = lib.licenses.mit; }) {}; "data-accessor" = callPackage - ({ mkDerivation, array, base, containers, stdenv, transformers }: + ({ mkDerivation, array, base, containers, lib, transformers }: mkDerivation { pname = "data-accessor"; - version = "0.2.2.8"; - sha256 = "ac3f95162df227a16eabf6be65d1d6563e5207d581edf72b680bfcd59f7f04bb"; + version = "0.2.3"; + sha256 = "1d583fd28b16093b408a741a1e05402280bb8f0e203c314dcf0f1391ffde3e38"; libraryHaskellDepends = [ array base containers transformers ]; doHaddock = false; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Record_access"; description = "Utilities for accessing and manipulating fields of records"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-accessor-mtl" = callPackage - ({ mkDerivation, base, data-accessor, mtl, stdenv }: + ({ mkDerivation, base, data-accessor, lib, mtl }: mkDerivation { pname = "data-accessor-mtl"; version = "0.2.0.4"; @@ -9018,16 +10071,18 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Record_access"; description = "Use Accessor to access state in mtl State monad class"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-accessor-template" = callPackage - ({ mkDerivation, base, data-accessor, stdenv, template-haskell + ({ mkDerivation, base, data-accessor, lib, template-haskell , utility-ht }: mkDerivation { pname = "data-accessor-template"; version = "0.2.1.16"; sha256 = "93e7f2120b8974d81a4acc56bd6a5b7121dac4672d974a42512c169c6937ed95"; + revision = "1"; + editedCabalFile = "0zz2v420zvinphs6jnngc40x7h8jn5rqj3nj8alpgfyqx59w41my"; libraryHaskellDepends = [ base data-accessor template-haskell utility-ht ]; @@ -9035,10 +10090,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Record_access"; description = "Utilities for accessing and manipulating fields of records"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-accessor-transformers" = callPackage - ({ mkDerivation, base, data-accessor, stdenv, transformers }: + ({ mkDerivation, base, data-accessor, lib, transformers }: mkDerivation { pname = "data-accessor-transformers"; version = "0.2.1.7"; @@ -9048,10 +10103,28 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Record_access"; description = "Use Accessor to access state in transformers State monad"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "data-ascii" = callPackage + ({ mkDerivation, base, blaze-builder, bytestring, case-insensitive + , hashable, lib, semigroups, text + }: + mkDerivation { + pname = "data-ascii"; + version = "1.0.0.6"; + sha256 = "99bd914be5c8fa4cb0b1c5e5d0e616bb6f033f283d97a319879fb1de5e981549"; + libraryHaskellDepends = [ + base blaze-builder bytestring case-insensitive hashable semigroups + text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/typeclasses/ascii"; + description = "Type-safe, bytestring-based ASCII values"; + license = lib.licenses.bsd3; }) {}; "data-binary-ieee754" = callPackage - ({ mkDerivation, base, binary, stdenv }: + ({ mkDerivation, base, binary, lib }: mkDerivation { pname = "data-binary-ieee754"; version = "0.4.4"; @@ -9061,10 +10134,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://john-millikin.com/software/data-binary-ieee754/"; description = "Parser/Serialiser for IEEE-754 floating-point values"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "data-bword" = callPackage - ({ mkDerivation, base, ghc-prim, stdenv }: + ({ mkDerivation, base, ghc-prim, lib }: mkDerivation { pname = "data-bword"; version = "0.1.0.1"; @@ -9074,10 +10147,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/mvv/data-bword"; description = "Extra operations on binary words of fixed length"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-checked" = callPackage - ({ mkDerivation, base, deepseq, stdenv }: + ({ mkDerivation, base, deepseq, lib }: mkDerivation { pname = "data-checked"; version = "0.3"; @@ -9087,12 +10160,40 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/mvv/data-checked"; description = "Type-indexed runtime-checked properties"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "data-clist" = callPackage + ({ mkDerivation, base, deepseq, lib, QuickCheck }: + mkDerivation { + pname = "data-clist"; + version = "0.1.2.3"; + sha256 = "356910406b1615819fefd87ff50f425bc41bd935750cfaa567718fb8ab858ed7"; + revision = "1"; + editedCabalFile = "13hg7a3d4ky8b765dl03ryxg28lq8iaqj5ky3j51r0i1i4f2a9hy"; + libraryHaskellDepends = [ base deepseq QuickCheck ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/sw17ch/data-clist"; + description = "Simple functional ring type"; + license = lib.licenses.bsd3; + }) {}; + "data-compat" = callPackage + ({ mkDerivation, base, constraints, lib }: + mkDerivation { + pname = "data-compat"; + version = "0.1.0.3"; + sha256 = "efee94d367616cceed449e32a241d277d74e90e9de3d511ad810b51c8329d5f1"; + libraryHaskellDepends = [ base constraints ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/TravisWhitaker/data-compat"; + description = "Define Backwards Compatibility Schemes for Arbitrary Data"; + license = lib.licenses.mit; }) {}; "data-default" = callPackage ({ mkDerivation, base, data-default-class , data-default-instances-containers, data-default-instances-dlist - , data-default-instances-old-locale, stdenv + , data-default-instances-old-locale, lib }: mkDerivation { pname = "data-default"; @@ -9105,10 +10206,10 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "A class for types with a default value"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-default-class" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "data-default-class"; version = "0.1.2.0"; @@ -9117,10 +10218,10 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "A class for types with a default value"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-default-instances-containers" = callPackage - ({ mkDerivation, base, containers, data-default-class, stdenv }: + ({ mkDerivation, base, containers, data-default-class, lib }: mkDerivation { pname = "data-default-instances-containers"; version = "0.0.1"; @@ -9129,10 +10230,10 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Default instances for types in containers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-default-instances-dlist" = callPackage - ({ mkDerivation, base, data-default-class, dlist, stdenv }: + ({ mkDerivation, base, data-default-class, dlist, lib }: mkDerivation { pname = "data-default-instances-dlist"; version = "0.0.1"; @@ -9141,10 +10242,10 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Default instances for types in dlist"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-default-instances-old-locale" = callPackage - ({ mkDerivation, base, data-default-class, old-locale, stdenv }: + ({ mkDerivation, base, data-default-class, lib, old-locale }: mkDerivation { pname = "data-default-instances-old-locale"; version = "0.0.1"; @@ -9153,16 +10254,15 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Default instances for types in old-locale"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-diverse" = callPackage - ({ mkDerivation, base, containers, deepseq, ghc-prim, stdenv - , tagged + ({ mkDerivation, base, containers, deepseq, ghc-prim, lib, tagged }: mkDerivation { pname = "data-diverse"; - version = "4.6.0.0"; - sha256 = "094d44446b2429bad5707b4aef0f1f63a9d101739d9a244cb2131f7646eccbd4"; + version = "4.7.0.0"; + sha256 = "c3cd9658d59b4a1a1862d0c5bc91e04146f5bf111e8469a050ea6ae1265a8b31"; libraryHaskellDepends = [ base containers deepseq ghc-prim tagged ]; @@ -9170,33 +10270,16 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/louispan/data-diverse#readme"; description = "Extensible records and polymorphic variants"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "data-diverse-lens" = callPackage - ({ mkDerivation, base, data-diverse, data-has, lens, profunctors - , stdenv, tagged - }: - mkDerivation { - pname = "data-diverse-lens"; - version = "4.3.0.0"; - sha256 = "97d049769f0a3693428bac8eb8de73e004f6fc9a1d0e3dc0c567f9d39f8ed986"; - libraryHaskellDepends = [ - base data-diverse data-has lens profunctors tagged - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/louispan/data-diverse-lens#readme"; - description = "Isos & Lens for Data.Diverse.Many and Prisms for Data.Diverse.Which"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-dword" = callPackage - ({ mkDerivation, base, data-bword, ghc-prim, hashable, stdenv + ({ mkDerivation, base, data-bword, ghc-prim, hashable, lib , template-haskell }: mkDerivation { pname = "data-dword"; - version = "0.3.1.2"; - sha256 = "6b677600221de86eaee21dd2d4c23c04320370c594a56f7bb3477ef4e4b69120"; + version = "0.3.2"; + sha256 = "dacb39233cc56712e8ced34d82961fb3c991d51553c7404751495d7c517077ab"; libraryHaskellDepends = [ base data-bword ghc-prim hashable template-haskell ]; @@ -9204,10 +10287,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/mvv/data-dword"; description = "Stick two binary words together to get a bigger one"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-endian" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "data-endian"; version = "0.1.1"; @@ -9217,36 +10300,77 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/mvv/data-endian"; description = "Endian-sensitive data"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-fix" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, deepseq, hashable, lib }: mkDerivation { pname = "data-fix"; - version = "0.2.0"; - sha256 = "7e5718055cb27ccac1e0bf25be70ba9bfe2b0d021cfe0a57a163355830341392"; - libraryHaskellDepends = [ base ]; + version = "0.3.1"; + sha256 = "9b45c040472922c197bb33190197b5895afac6318203b2afb30251d4df8bcc79"; + libraryHaskellDepends = [ base deepseq hashable ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/anton-k/data-fix"; + homepage = "https://github.com/spell-music/data-fix"; description = "Fixpoint data types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "data-has" = callPackage - ({ mkDerivation, base, stdenv }: + "data-forest" = callPackage + ({ mkDerivation, base, lib }: mkDerivation { - pname = "data-has"; - version = "0.3.0.0"; - sha256 = "3c25d403605ecb196df53c8c8fb7829cd7b6a88e0ea04b88038602ba7faa7379"; + pname = "data-forest"; + version = "0.1.0.8"; + sha256 = "349b0ad765cfb786d23d2bdfb133f912271006638ea18dbdce0015230a3c2b2d"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/chris-martin/data-forest"; + description = "A simple multi-way tree data structure"; + license = lib.licenses.asl20; + }) {}; + "data-has" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "data-has"; + version = "0.4.0.0"; + sha256 = "7fb52d8840feb0c09455dd09171a197922de0bc91dbf39620230154daab072fe"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/winterland1989/data-has"; description = "Simple extensible product"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "data-hash" = callPackage + ({ mkDerivation, array, base, containers, lib }: + mkDerivation { + pname = "data-hash"; + version = "0.2.0.1"; + sha256 = "9117dd49013ca28ff188fc71c3595ac3af23d56d301c1f39bac93d44d8c60bbe"; + libraryHaskellDepends = [ array base containers ]; + doHaddock = false; + doCheck = false; + description = "Combinators for building fast hashing functions"; + license = lib.licenses.bsd3; + }) {}; + "data-interval" = callPackage + ({ mkDerivation, base, containers, deepseq, extended-reals + , hashable, lattices, lib + }: + mkDerivation { + pname = "data-interval"; + version = "2.1.0"; + sha256 = "98fea6cc3b39912fa53cc5adbef0350b835d196de58f455b74c9935bf17d8d38"; + libraryHaskellDepends = [ + base containers deepseq extended-reals hashable lattices + ]; + doHaddock = false; + doCheck = false; + description = "Interval datatype, interval arithmetic and interval-based containers"; + license = lib.licenses.bsd3; }) {}; "data-inttrie" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "data-inttrie"; version = "0.1.4"; @@ -9256,23 +10380,23 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/luqui/data-inttrie"; description = "A simple lazy, infinite trie from integers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-lens-light" = callPackage - ({ mkDerivation, base, mtl, stdenv, template-haskell }: + ({ mkDerivation, base, lib, mtl, template-haskell }: mkDerivation { pname = "data-lens-light"; - version = "0.1.2.2"; - sha256 = "72d3e6a73bde4a32eccd2024eb58ca96da962d4b659d76baed4ab37f28dcb36e"; + version = "0.1.2.3"; + sha256 = "b471174cbf0c9301e63d1abbe5720c1b9a6bf716dbd0cb13c4250c1b5f5d9ff5"; libraryHaskellDepends = [ base mtl template-haskell ]; doHaddock = false; doCheck = false; homepage = "https://github.com/feuerbach/data-lens-light"; description = "Simple lenses, minimum dependencies"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "data-memocombinators" = callPackage - ({ mkDerivation, array, base, data-inttrie, stdenv }: + ({ mkDerivation, array, base, data-inttrie, lib }: mkDerivation { pname = "data-memocombinators"; version = "0.5.1"; @@ -9282,16 +10406,16 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/luqui/data-memocombinators"; description = "Combinators for building memo tables"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-msgpack" = callPackage ({ mkDerivation, base, binary, bytestring, data-binary-ieee754 - , data-msgpack-types, groom, stdenv, text + , data-msgpack-types, groom, lib, text }: mkDerivation { pname = "data-msgpack"; - version = "0.0.12"; - sha256 = "5c9f8b04fbc30368e0a085de2c33e08cb0601fc9e95f767c38435d5a0ce1f487"; + version = "0.0.13"; + sha256 = "0460cb31f3da58c3e94640f2776aeb8457a51acf4990be822db02ce96f7c58f4"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -9302,16 +10426,16 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://msgpack.org/"; description = "A Haskell implementation of MessagePack"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-msgpack-types" = callPackage ({ mkDerivation, base, bytestring, containers, deepseq, hashable - , QuickCheck, stdenv, text, unordered-containers, vector, void + , lib, QuickCheck, text, unordered-containers, vector, void }: mkDerivation { pname = "data-msgpack-types"; - version = "0.0.2"; - sha256 = "54fdda1fa485c9f86f1f0f2aa8cc71d111b2f36504b7fb9c0a2de95c0b1287a5"; + version = "0.0.3"; + sha256 = "2506e92ed7f34f127fd3609b9fd226aa510e67a94ab91aa0b0970932750a4f16"; libraryHaskellDepends = [ base bytestring containers deepseq hashable QuickCheck text unordered-containers vector void @@ -9320,10 +10444,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://msgpack.org/"; description = "A Haskell implementation of MessagePack"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-or" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "data-or"; version = "1.0.0.5"; @@ -9333,10 +10457,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://code.haskell.org/~wren/"; description = "A data type for non-exclusive disjunction"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-ordlist" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "data-ordlist"; version = "0.4.7.0"; @@ -9345,63 +10469,65 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Set and bag operations on ordered lists"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-ref" = callPackage - ({ mkDerivation, base, stdenv, stm, transformers }: + ({ mkDerivation, base, data-accessor, lib, stm, transformers }: mkDerivation { pname = "data-ref"; - version = "0.0.1.2"; - sha256 = "605cf65aa01f93a5834305001056b2206a95830e25b7f969b34c9479a7e42621"; - libraryHaskellDepends = [ base stm transformers ]; + version = "0.0.2"; + sha256 = "7b14399e9d8df50ed7ee3b10ea2ea4b7fdd8922896da000b171eac742ffb0f77"; + libraryHaskellDepends = [ base data-accessor stm transformers ]; doHaddock = false; doCheck = false; homepage = "http://wiki.haskell.org/Mutable_variable"; description = "Unify STRef and IORef in plain Haskell 98"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-reify" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, hashable, lib + , unordered-containers + }: mkDerivation { pname = "data-reify"; - version = "0.6.1"; - sha256 = "61350a1e96cb1276c2b6b8b13fa1bade5d4e63c702509a3f5e90bbc19ad9b202"; - revision = "1"; - editedCabalFile = "0ixlibqrz7fd4bg9vnnd431a9kqvz4ajx8sbgyvpx9l2yjrabwzp"; + version = "0.6.3"; + sha256 = "a5c05440d75a88ab79ddb6b53905dc3cb8190f6e405d5e101036d89e685c4ce9"; isLibrary = true; isExecutable = true; - libraryHaskellDepends = [ base containers ]; + libraryHaskellDepends = [ + base containers hashable unordered-containers + ]; doHaddock = false; doCheck = false; homepage = "http://ku-fpg.github.io/software/data-reify/"; description = "Reify a recursive data structure into an explicit graph"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-serializer" = callPackage - ({ mkDerivation, base, binary, bytestring, cereal, data-endian - , parsers, semigroups, split, stdenv + ({ mkDerivation, base, binary, bytestring, cereal, data-endian, lib + , parsers, split }: mkDerivation { pname = "data-serializer"; - version = "0.3.4"; - sha256 = "e793156aa2262ca294183a9d045f37e6ff2070825b40d2ffe5a8d64e0b455ec6"; + version = "0.3.5"; + sha256 = "b4a0bfdeef7c8c77006682c46addf4ee9e1c8e51b5e01c7ac324813cd16ffd43"; libraryHaskellDepends = [ - base binary bytestring cereal data-endian parsers semigroups split + base binary bytestring cereal data-endian parsers split ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mvv/data-serializer"; description = "Common API for serialization libraries"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "data-textual" = callPackage - ({ mkDerivation, base, bytestring, parsers, stdenv, text - , text-latin1, text-printer + ({ mkDerivation, base, bytestring, lib, parsers, text, text-latin1 + , text-printer }: mkDerivation { pname = "data-textual"; - version = "0.3.0.2"; - sha256 = "44c530b081a486c50d668004637814223d1f1890716d39f7b692c83644d29830"; + version = "0.3.0.3"; + sha256 = "4b9ee8ccd03f24203dd9307bf9aa67180ff0f07b45c3a01e33d8185ff275ec9a"; libraryHaskellDepends = [ base bytestring parsers text text-latin1 text-printer ]; @@ -9409,32 +10535,19 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/mvv/data-textual"; description = "Human-friendly textual representations"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "data-tree-print" = callPackage - ({ mkDerivation, base, pretty, stdenv, syb }: - mkDerivation { - pname = "data-tree-print"; - version = "0.1.0.2"; - sha256 = "c3ef24d803946a3caf0ff0e51f0c0b9f49055d7dc790518ad518d568d5195002"; - libraryHaskellDepends = [ base pretty syb ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/lspitzner/data-tree-print"; - description = "Print Data instances as a nested tree"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "datadog" = callPackage ({ mkDerivation, aeson, auto-update, base, buffer-builder , bytestring, containers, dlist, http-client, http-client-tls - , http-types, lens, lifted-base, monad-control, network, old-locale - , stdenv, text, time, transformers-base, unliftio + , http-types, lens, lib, lifted-base, monad-control, network + , old-locale, text, time, transformers-base, unliftio , unordered-containers, vector }: mkDerivation { pname = "datadog"; - version = "0.2.3.0"; - sha256 = "9bb5eda1c704261160e0714499eef8c03dc2dd4d8673ad085e80c164445c1934"; + version = "0.2.5.0"; + sha256 = "66c59d1c56489f6f985faff80a5f0b48d5dab2b38c875929074550e112e86b97"; libraryHaskellDepends = [ aeson auto-update base buffer-builder bytestring containers dlist http-client http-client-tls http-types lens lifted-base @@ -9445,11 +10558,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/iand675/datadog"; description = "Datadog client for Haskell. Supports both the HTTP API and StatsD."; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "dataurl" = callPackage ({ mkDerivation, attoparsec, base, base64-bytestring, bytestring - , stdenv, text + , lib, text }: mkDerivation { pname = "dataurl"; @@ -9462,30 +10575,18 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/agrafix/dataurl#readme"; description = "Handle data-urls"; - license = stdenv.lib.licenses.mit; - }) {}; - "dbcleaner" = callPackage - ({ mkDerivation, base, postgresql-simple, stdenv, text }: - mkDerivation { - pname = "dbcleaner"; - version = "0.1.3"; - sha256 = "0817b0e1698d8d48ac58d631f51dc6e34663f4e97af7bac3fd03e31349830f35"; - libraryHaskellDepends = [ base postgresql-simple text ]; - doHaddock = false; - doCheck = false; - description = "Clean database tables automatically around hspec tests"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "dbus" = callPackage ({ mkDerivation, base, bytestring, cereal, conduit, containers - , deepseq, exceptions, filepath, lens, network, parsec, random - , split, stdenv, template-haskell, text, th-lift, transformers - , unix, vector, xml-conduit, xml-types + , deepseq, exceptions, filepath, lens, lib, network, parsec, random + , split, template-haskell, text, th-lift, transformers, unix + , vector, xml-conduit, xml-types }: mkDerivation { pname = "dbus"; - version = "1.2.1"; - sha256 = "99d8c136041d63bf7e2018e5c4f23c324381b9efb5a47f676f866e2a8694b1d7"; + version = "1.2.17"; + sha256 = "3b2f76cbf6566b159961f16e4da3c1c80bfb3a7608f99ccea03b54cbfab4ce47"; libraryHaskellDepends = [ base bytestring cereal conduit containers deepseq exceptions filepath lens network parsec random split template-haskell text @@ -9495,57 +10596,76 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/rblaze/haskell-dbus#readme"; description = "A client library for the D-Bus IPC system"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; }) {}; - "debian-build" = callPackage - ({ mkDerivation, base, directory, filepath, process, split, stdenv - , transformers + "dbus-hslogger" = callPackage + ({ mkDerivation, base, dbus, hslogger, lib, optparse-applicative }: + mkDerivation { + pname = "dbus-hslogger"; + version = "0.1.0.1"; + sha256 = "f103f4ccbc3258af95e6d7b20d9adbbccc94b5377edcb36865a3dca766325e44"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base dbus hslogger ]; + executableHaskellDepends = [ + base dbus hslogger optparse-applicative + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/IvanMalison/dbus-hslogger#readme"; + description = "Expose a dbus server to control hslogger"; + license = lib.licenses.bsd3; + }) {}; + "debian" = callPackage + ({ mkDerivation, base, bytestring, bz2, Cabal, containers + , directory, either, exceptions, filepath, hostname, HUnit, lens + , lib, ListLike, mtl, network-uri, old-locale, parsec, pretty + , process, process-extras, pureMD5, QuickCheck, regex-compat + , regex-tdfa, SHA, syb, template-haskell, temporary, text, th-lift + , th-orphans, time, unix, utf8-string, zlib }: mkDerivation { - pname = "debian-build"; - version = "0.10.1.2"; - sha256 = "1cd3b5f099f0d26d0f14e2611b11b6599e4fad4cc217b88b61d1e478d3ec1641"; + pname = "debian"; + version = "4.0.2"; + sha256 = "e13061ab8349c25d3e472344713490757fc07424e3ea8266df94ba62dedce8ea"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - base directory filepath process split transformers + base bytestring bz2 Cabal containers directory either exceptions + filepath hostname HUnit lens ListLike mtl network-uri old-locale + parsec pretty process process-extras pureMD5 QuickCheck + regex-compat regex-tdfa SHA syb template-haskell temporary text + th-lift th-orphans time unix utf8-string zlib ]; - executableHaskellDepends = [ base filepath transformers ]; + executableHaskellDepends = [ base directory filepath process ]; doHaddock = false; doCheck = false; - homepage = "http://twitter.com/khibino/"; - description = "Debian package build sequence tools"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/clinty/debian-haskell"; + description = "Modules for working with the Debian package system"; + license = lib.licenses.bsd3; }) {}; - "debug" = callPackage - ({ mkDerivation, aeson, base, bytestring, clock, containers - , deepseq, directory, extra, filepath, ghc-prim, hashable, Hoed - , libgraph, open-browser, prettyprinter - , prettyprinter-compat-ansi-wl-pprint, stdenv, template-haskell - , text, uniplate, unordered-containers, vector, yaml + "debian-build" = callPackage + ({ mkDerivation, base, directory, filepath, lib, process, split + , transformers }: mkDerivation { - pname = "debug"; - version = "0.1.1"; - sha256 = "330f44c6341833c5e0cccf08fa7674dd54f14a843a2b5703e25ce08ffed49248"; + pname = "debian-build"; + version = "0.10.2.0"; + sha256 = "5dd8af7f38780b51ad0dd13d2710f950b3d385b39b7a5b02fd5eeccd4ae61afb"; isLibrary = true; isExecutable = true; - enableSeparateDataOutput = true; libraryHaskellDepends = [ - aeson base bytestring clock containers deepseq directory extra - ghc-prim hashable Hoed libgraph open-browser prettyprinter - prettyprinter-compat-ansi-wl-pprint template-haskell text uniplate - unordered-containers vector + base directory filepath process split transformers ]; - executableHaskellDepends = [ aeson base directory filepath yaml ]; + executableHaskellDepends = [ base filepath transformers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/ndmitchell/debug"; - description = "Simple trace-based debugger"; - license = stdenv.lib.licenses.bsd3; + homepage = "http://twitter.com/khibino/"; + description = "Debian package build sequence tools"; + license = lib.licenses.bsd3; }) {}; "debug-trace-var" = callPackage - ({ mkDerivation, base, stdenv, template-haskell, unicode-show }: + ({ mkDerivation, base, lib, template-haskell, unicode-show }: mkDerivation { pname = "debug-trace-var"; version = "0.2.0"; @@ -9555,30 +10675,30 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/ncaq/debug-trace-var#readme"; description = "You do not have to write variable names twice in Debug.Trace"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "decidable" = callPackage - ({ mkDerivation, base, singletons, stdenv }: + "dec" = callPackage + ({ mkDerivation, base, lib }: mkDerivation { - pname = "decidable"; - version = "0.1.4.0"; - sha256 = "7eb222eaa16bdc1780def19cdb7d428c8b44dec1f5f6cf96ce77c4b8a1149c1d"; - libraryHaskellDepends = [ base singletons ]; + pname = "dec"; + version = "0.0.4"; + sha256 = "ecfdbd681299b2653b4d5a17f4113ac156074761372bc119dcd3e1ea9473547b"; + libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/mstksg/decidable#readme"; - description = "Combinators for manipulating dependently-typed predicates"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/phadej/vec"; + description = "Decidable propositions"; + license = lib.licenses.bsd3; }) {}; "declarative" = callPackage - ({ mkDerivation, base, hasty-hamiltonian, kan-extensions, lens + ({ mkDerivation, base, hasty-hamiltonian, kan-extensions, lens, lib , mcmc-types, mighty-metropolis, mwc-probability, pipes, primitive - , speedy-slice, stdenv, transformers + , speedy-slice, transformers }: mkDerivation { pname = "declarative"; - version = "0.5.2"; - sha256 = "1ea8cf5eb0283ed9d9a7e1d46e5386960587c1671f7ce568d6eaf1d1b8ba9a04"; + version = "0.5.4"; + sha256 = "0ade713f725c7d57b3f7d0cf9b0ee50b85996f9ce84f64c0dabcaf47e86fbc81"; libraryHaskellDepends = [ base hasty-hamiltonian kan-extensions lens mcmc-types mighty-metropolis mwc-probability pipes primitive speedy-slice @@ -9588,50 +10708,63 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/jtobin/declarative"; description = "DIY Markov Chains"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "deepseq-generics" = callPackage - ({ mkDerivation, base, deepseq, ghc-prim, stdenv }: + ({ mkDerivation, base, deepseq, ghc-prim, lib }: mkDerivation { pname = "deepseq-generics"; version = "0.2.0.0"; sha256 = "b0b3ef5546c0768ef9194519a90c629f8f2ba0348487e620bb89d512187c7c9d"; - revision = "3"; - editedCabalFile = "0734x6dm7ny1422n5ik4agzmjybvd3yybj1mnrc8z0kb89xdprcs"; + revision = "5"; + editedCabalFile = "1iqgza1larap5n4f1z7d7ag1s3b0zzlvgb91lrwwa5khgw2m7mrg"; libraryHaskellDepends = [ base deepseq ghc-prim ]; doHaddock = false; doCheck = false; homepage = "https://github.com/hvr/deepseq-generics"; description = "GHC.Generics-based Control.DeepSeq.rnf implementation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "deepseq-instances" = callPackage + ({ mkDerivation, array, base, deepseq, lib, stm }: + mkDerivation { + pname = "deepseq-instances"; + version = "0.1.0.1"; + sha256 = "9f884ae92be5c6d9ccb54d59c99d99fb1ef5e05fbaa0b6569e58008fe198106a"; + libraryHaskellDepends = [ array base deepseq stm ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/TravisWhitaker/deepseq-instances"; + description = "Candidate NFData Instances for Types in base"; + license = lib.licenses.mit; }) {}; "deferred-folds" = callPackage - ({ mkDerivation, base, bytestring, containers, foldl, hashable - , primitive, stdenv, transformers, unordered-containers, vector + ({ mkDerivation, base, bytestring, containers, foldl, hashable, lib + , primitive, text, transformers, unordered-containers, vector }: mkDerivation { pname = "deferred-folds"; - version = "0.9.10"; - sha256 = "dd01a39903e9395d0fa38c05609176b3742f55dab5919ae54140f742363b6b67"; + version = "0.9.17"; + sha256 = "90e535fba172c69b448aff7014097a7014675cd48bb04ec6d18565ac31f5c7b6"; libraryHaskellDepends = [ - base bytestring containers foldl hashable primitive transformers - unordered-containers vector + base bytestring containers foldl hashable primitive text + transformers unordered-containers vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/metrix-ai/deferred-folds"; description = "Abstractions over deferred folds"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "dejafu" = callPackage ({ mkDerivation, base, concurrency, containers, contravariant - , deepseq, exceptions, leancheck, profunctors, random, stdenv + , deepseq, exceptions, leancheck, lib, profunctors, random , transformers }: mkDerivation { pname = "dejafu"; - version = "1.11.0.4"; - sha256 = "af25f89cf243d3ccd038f7e9c9d52fc462061587fa05852b7a9e36db70257a7e"; + version = "2.4.0.2"; + sha256 = "306d40969574efa9f7480dc7922b5a89ad3e06801be8a59f34f32a2e65f790c3"; libraryHaskellDepends = [ base concurrency containers contravariant deepseq exceptions leancheck profunctors random transformers @@ -9640,10 +10773,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/barrucadu/dejafu"; description = "A library for unit-testing concurrent programs"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "dense-linear-algebra" = callPackage - ({ mkDerivation, base, deepseq, math-functions, primitive, stdenv + ({ mkDerivation, base, deepseq, lib, math-functions, primitive , vector, vector-algorithms, vector-binary-instances , vector-th-unbox }: @@ -9658,67 +10791,107 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Simple and incomplete pure haskell implementation of linear algebra"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; }) {}; "dependent-map" = callPackage - ({ mkDerivation, base, containers, dependent-sum, stdenv }: + ({ mkDerivation, base, constraints-extras, containers + , dependent-sum, lib + }: mkDerivation { pname = "dependent-map"; - version = "0.2.4.0"; - sha256 = "5db396bdb5d156434af920c074316c3b84b4d39ba8e1cd349c7bb6679cb28246"; - libraryHaskellDepends = [ base containers dependent-sum ]; + version = "0.4.0.0"; + sha256 = "53ce0b52d8be1b85fc6489fb27656f16d837bee4fbe0ddf39c844e3ea8871f2c"; + libraryHaskellDepends = [ + base constraints-extras containers dependent-sum + ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/mokus0/dependent-map"; + homepage = "https://github.com/obsidiansystems/dependent-map"; description = "Dependent finite maps (partial dependent products)"; license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; + hydraPlatforms = lib.platforms.none; }) {}; "dependent-sum" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, constraints-extras, lib, some }: mkDerivation { pname = "dependent-sum"; - version = "0.4"; - sha256 = "a8deecb4153a1878173f8d0a18de0378ab068bc15e5035b9e4cb478e8e4e1a1e"; - libraryHaskellDepends = [ base ]; + version = "0.7.1.0"; + sha256 = "81cb55907f321f62bea095ae72e9711095c4cb7378fa66fbabc483a9f61b462a"; + revision = "1"; + editedCabalFile = "0h9rr26ksrqfnfjibnrzbf6hyp1mmffgzbvjjxjs6vdqylvr4h8f"; + libraryHaskellDepends = [ base constraints-extras some ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/mokus0/dependent-sum"; + homepage = "https://github.com/obsidiansystems/dependent-sum"; description = "Dependent sum type"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "dependent-sum-template" = callPackage - ({ mkDerivation, base, dependent-sum, stdenv, template-haskell + ({ mkDerivation, base, dependent-sum, lib, template-haskell , th-extras }: mkDerivation { pname = "dependent-sum-template"; - version = "0.0.0.6"; - sha256 = "994cb4891949cad1b9ca268052377c58c174f77a469cae44742ac83727be91ad"; + version = "0.1.0.3"; + sha256 = "c8eb17d3fa9966182e041836abefce2e7e42e30d3b01463a254fb7cf806ca4df"; libraryHaskellDepends = [ base dependent-sum template-haskell th-extras ]; doHaddock = false; doCheck = false; - homepage = "/dev/null"; + homepage = "https://github.com/obsidiansystems/dependent-sum"; description = "Template Haskell code to generate instances of classes in dependent-sum package"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; + }) {}; + "depq" = callPackage + ({ mkDerivation, base, containers, deepseq, lib, psqueues + , QuickCheck + }: + mkDerivation { + pname = "depq"; + version = "0.4.2"; + sha256 = "34943171f683b5cc3b710e2222cfa75f469fc947dc804c57931c8f94d92809a3"; + libraryHaskellDepends = [ + base containers deepseq psqueues QuickCheck + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ocramz/depq"; + description = "Double-ended priority queues"; + license = lib.licenses.bsd3; }) {}; "deque" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, hashable, lib, mtl, strict-list }: mkDerivation { pname = "deque"; - version = "0.2.7"; - sha256 = "99513020c8048ad8c13962b8774a5e21d50216cde22c6b3184834b6539f550f3"; - libraryHaskellDepends = [ base ]; + version = "0.4.3"; + sha256 = "b76a0e7d8a5f3b12ca8cf5a583f3e8e4333c7860f56b1e921a3fdfe959e557a5"; + libraryHaskellDepends = [ base hashable mtl strict-list ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nikita-volkov/deque"; - description = "Double-ended queue"; - license = stdenv.lib.licenses.mit; + description = "Double-ended queues"; + license = lib.licenses.mit; + }) {}; + "derive-topdown" = callPackage + ({ mkDerivation, base, lib, mtl, primitive, syb, template-haskell + , th-expand-syns, transformers + }: + mkDerivation { + pname = "derive-topdown"; + version = "0.0.2.2"; + sha256 = "139825ba99564cc5e0e583f12307454cd8f0461d32f1dc6f3cd9678e9b6ad5e7"; + libraryHaskellDepends = [ + base mtl primitive syb template-haskell th-expand-syns transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/HaskellZhangSong/derive-topdown"; + description = "Help Haskellers derive class instances for composited data types"; + license = lib.licenses.bsd3; }) {}; "deriveJsonNoPrefix" = callPackage - ({ mkDerivation, aeson, base, stdenv, template-haskell }: + ({ mkDerivation, aeson, base, lib, template-haskell }: mkDerivation { pname = "deriveJsonNoPrefix"; version = "0.1.0.1"; @@ -9728,19 +10901,29 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://gitlab.com/igrep/deriveJsonNoPrefix"; description = "Derive ToJSON/FromJSON instances in a more prefix-friendly manner"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; + }) {}; + "deriving-aeson" = callPackage + ({ mkDerivation, aeson, base, lib }: + mkDerivation { + pname = "deriving-aeson"; + version = "0.2.7"; + sha256 = "3ffeb1bd6d7441896a9d518b60f5b11096629ea88aa4cbf8e3c9e2c7c247bd0a"; + libraryHaskellDepends = [ aeson base ]; + doHaddock = false; + doCheck = false; + description = "Type driven generic aeson instance customisation"; + license = lib.licenses.bsd3; }) {}; "deriving-compat" = callPackage - ({ mkDerivation, base, containers, ghc-boot-th, ghc-prim, stdenv + ({ mkDerivation, base, containers, ghc-boot-th, ghc-prim, lib , template-haskell, th-abstraction, transformers , transformers-compat }: mkDerivation { pname = "deriving-compat"; - version = "0.5.2"; - sha256 = "495660f8b41bbb5ab372e2d393eaf57ba8ebd5d4f80b1477b2fd5caef875b240"; - revision = "1"; - editedCabalFile = "1s672vc7w96fmvr1p3fkqi9q80sn860j14545sskpxb8iz9f7sxg"; + version = "0.5.10"; + sha256 = "9029e45f0f748853c29bdb50c1191db737e5a66fb71fd255349b87b3742700aa"; libraryHaskellDepends = [ base containers ghc-boot-th ghc-prim template-haskell th-abstraction transformers transformers-compat @@ -9749,85 +10932,71 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/haskell-compat/deriving-compat"; description = "Backports of GHC deriving extensions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "derulo" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "derulo"; - version = "1.0.5"; - sha256 = "9ed69dd320fafe190d296ae24aaf4d1e85688cdb8240cf1fea187a0bb3a1cadf"; + version = "1.0.10"; + sha256 = "ecbed7d9474a200a1b1ff0f09718c80748329d5c41c664b95d12027afdcfb555"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base ]; executableHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/tfausak/derulo#readme"; description = "Parse and render JSON simply"; - license = stdenv.lib.licenses.mit; - }) {}; - "detour-via-sci" = callPackage - ({ mkDerivation, aeson, base, cassava, newtype, scientific - , siggy-chardust, stdenv, template-haskell - }: - mkDerivation { - pname = "detour-via-sci"; - version = "1.0.0"; - sha256 = "451e1194f7bf6a7dea02379679c790313cc20423271fd8e98f164c942e3d81e4"; - revision = "1"; - editedCabalFile = "00dj8vf9gg9ww37sir6mblf3xhcpam8qgfz5bfana23arhf2cixj"; - libraryHaskellDepends = [ - aeson base cassava newtype scientific siggy-chardust - template-haskell - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/blockscope/flare-timing/tree/master/detour-via-sci#readme"; - description = "JSON and CSV encoding for rationals as decimal point numbers"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mit; }) {}; "dhall" = callPackage - ({ mkDerivation, ansi-terminal, base, bytestring, case-insensitive - , cborg, containers, contravariant, cryptonite, Diff, directory - , dotgen, exceptions, filepath, haskeline, http-client - , http-client-tls, http-types, lens-family-core, megaparsec, memory - , mtl, optparse-applicative, parsers, prettyprinter - , prettyprinter-ansi-terminal, repline, scientific, serialise - , stdenv, template-haskell, text, transformers + ({ mkDerivation, aeson, aeson-pretty, ansi-terminal, atomic-write + , base, bytestring, case-insensitive, cborg, cborg-json, containers + , contravariant, cryptonite, data-fix, deepseq, Diff, directory + , dotgen, either, exceptions, filepath, half, hashable, haskeline + , http-client, http-client-tls, http-types, lens-family-core, lib + , megaparsec, memory, mmorph, mtl, network-uri + , optparse-applicative, parser-combinators, parsers, pretty-simple + , prettyprinter, prettyprinter-ansi-terminal, profunctors, repline + , scientific, serialise, template-haskell, text, text-manipulate + , th-lift-instances, transformers, transformers-compat , unordered-containers, uri-encode, vector }: mkDerivation { pname = "dhall"; - version = "1.19.1"; - sha256 = "f8d32a4415c67bbae43d90780c5707cd471a408f20959d233f14b91c3577d291"; + version = "1.39.0"; + sha256 = "4b117a1db8fa86ecd12b11bc55f3b50627e4b4bb96d0d63ebb7ab2e5086ac2af"; revision = "1"; - editedCabalFile = "193h4dmlz1asfr1ldy0saa9spgp64xh60xh3yywzn9lz0hxzbfpg"; + editedCabalFile = "0rb5bnhb88ywgsc5ilxwcs7p6ck32skkziwsbiim322s2f1jm0fn"; isLibrary = true; isExecutable = true; + enableSeparateDataOutput = true; libraryHaskellDepends = [ - ansi-terminal base bytestring case-insensitive cborg containers - contravariant cryptonite Diff directory dotgen exceptions filepath - haskeline http-client http-client-tls http-types lens-family-core - megaparsec memory mtl optparse-applicative parsers prettyprinter - prettyprinter-ansi-terminal repline scientific serialise - template-haskell text transformers unordered-containers uri-encode - vector + aeson aeson-pretty ansi-terminal atomic-write base bytestring + case-insensitive cborg cborg-json containers contravariant + cryptonite data-fix deepseq Diff directory dotgen either exceptions + filepath half hashable haskeline http-client http-client-tls + http-types lens-family-core megaparsec memory mmorph mtl + network-uri optparse-applicative parser-combinators parsers + pretty-simple prettyprinter prettyprinter-ansi-terminal profunctors + repline scientific serialise template-haskell text text-manipulate + th-lift-instances transformers transformers-compat + unordered-containers uri-encode vector ]; executableHaskellDepends = [ base ]; doHaddock = false; doCheck = false; description = "A configuration language guaranteed to terminate"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "dhall-bash" = callPackage - ({ mkDerivation, base, bytestring, containers, dhall - , neat-interpolation, optparse-generic, shell-escape, stdenv, text + ({ mkDerivation, base, bytestring, containers, dhall, lib + , neat-interpolation, optparse-generic, shell-escape, text }: mkDerivation { pname = "dhall-bash"; - version = "1.0.18"; - sha256 = "ceed4dae99f78da28ce68a04cecac2f221167b2301d28207a05b413ec367cc0c"; + version = "1.0.37"; + sha256 = "2df061bcae9341f4627d164c9acd1f2c26b264144e32009a60f94d04abfaa63e"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -9840,55 +11009,93 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Compile Dhall to Bash"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "dhall-json" = callPackage - ({ mkDerivation, aeson, aeson-pretty, base, bytestring, dhall - , optparse-applicative, stdenv, text, unordered-containers, vector - , yaml + ({ mkDerivation, aeson, aeson-pretty, aeson-yaml, ansi-terminal + , base, bytestring, containers, dhall, exceptions, filepath + , lens-family-core, lib, optparse-applicative, prettyprinter + , prettyprinter-ansi-terminal, scientific, text + , unordered-containers, vector }: mkDerivation { pname = "dhall-json"; - version = "1.2.6"; - sha256 = "9989a705a780ccc8b40f242e5dcb8949ade590a0180ae9559bffa25d829d2838"; + version = "1.7.7"; + sha256 = "94d2ef7ec16a36a5f707e839e883a19c5cc9b921083c2c5f6245119019006698"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - aeson base dhall optparse-applicative text unordered-containers + aeson aeson-pretty aeson-yaml base bytestring containers dhall + exceptions filepath lens-family-core optparse-applicative + prettyprinter scientific text unordered-containers vector ]; executableHaskellDepends = [ - aeson aeson-pretty base bytestring dhall optparse-applicative text - vector yaml + aeson aeson-pretty ansi-terminal base bytestring dhall exceptions + optparse-applicative prettyprinter prettyprinter-ansi-terminal text ]; doHaddock = false; doCheck = false; - description = "Compile Dhall to JSON or YAML"; - license = stdenv.lib.licenses.bsd3; + description = "Convert between Dhall and JSON or YAML"; + license = lib.licenses.bsd3; }) {}; - "dhall-text" = callPackage - ({ mkDerivation, base, dhall, optparse-applicative, stdenv, text }: + "dhall-lsp-server" = callPackage + ({ mkDerivation, aeson, aeson-pretty, base, bytestring, containers + , data-default, dhall, dhall-json, directory, filepath, haskell-lsp + , hslogger, lens, lib, megaparsec, mtl, network-uri + , optparse-applicative, prettyprinter, rope-utf16-splay, text + , transformers, unordered-containers, uri-encode + }: mkDerivation { - pname = "dhall-text"; + pname = "dhall-lsp-server"; version = "1.0.15"; - sha256 = "afa2dd0cbb6d261b5cf79988f673cf2405f5419c306c55181d9aae3ec6c932b2"; - isLibrary = false; + sha256 = "1eb7be9e55e522c9e8d7fe6c19f2dbdf7b51407f2549ff53f56d0bf1449a062f"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson aeson-pretty base bytestring containers data-default dhall + dhall-json directory filepath haskell-lsp hslogger lens megaparsec + mtl network-uri prettyprinter rope-utf16-splay text transformers + unordered-containers uri-encode + ]; + executableHaskellDepends = [ base optparse-applicative ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/dhall-lang/dhall-haskell/tree/master/dhall-lsp-server#readme"; + description = "Language Server Protocol (LSP) server for Dhall"; + license = lib.licenses.mit; + }) {}; + "dhall-yaml" = callPackage + ({ mkDerivation, aeson, ansi-terminal, base, bytestring, dhall + , dhall-json, exceptions, HsYAML, HsYAML-aeson, lib + , optparse-applicative, prettyprinter, prettyprinter-ansi-terminal + , text, vector + }: + mkDerivation { + pname = "dhall-yaml"; + version = "1.2.7"; + sha256 = "038cae0074d0cbd9bb324ec6092bbda1afbe00996447444552d9ca0aa9ecd79d"; + isLibrary = true; isExecutable = true; + libraryHaskellDepends = [ + aeson base bytestring dhall dhall-json HsYAML HsYAML-aeson + optparse-applicative text vector + ]; executableHaskellDepends = [ - base dhall optparse-applicative text + aeson ansi-terminal base bytestring dhall dhall-json exceptions + optparse-applicative prettyprinter prettyprinter-ansi-terminal text ]; doHaddock = false; doCheck = false; - description = "Template text using Dhall"; - license = stdenv.lib.licenses.bsd3; + description = "Convert between Dhall and YAML"; + license = lib.licenses.gpl3Only; }) {}; "di-core" = callPackage - ({ mkDerivation, base, containers, safe-exceptions, stdenv, stm - , time + ({ mkDerivation, base, containers, lib, safe-exceptions, stm, time }: mkDerivation { pname = "di-core"; - version = "1.0.3"; - sha256 = "f0900e071c6a4fd99ac5588b1801333bcd50aa73a212222b29c731494d52dfe5"; + version = "1.0.4"; + sha256 = "55634d9afebfa94f5573471ec846f23fbc3716ae524ebee58f27a7f99b153273"; libraryHaskellDepends = [ base containers safe-exceptions stm time ]; @@ -9896,16 +11103,16 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/k0001/di"; description = "Typeful hierarchical structured logging without monad towers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "di-monad" = callPackage - ({ mkDerivation, base, containers, di-core, exceptions, mtl, pipes - , stdenv, stm, transformers + ({ mkDerivation, base, containers, di-core, exceptions, lib, mtl + , pipes, stm, transformers }: mkDerivation { pname = "di-monad"; - version = "1.3"; - sha256 = "54e35bfbd60bcf18b72591a261cdc9cac0cde00858b697eb63066e3a983c3305"; + version = "1.3.1"; + sha256 = "f5ddeae5a199f6e83abdc989a2df8408e761a798646eb7ca5944f7a3383416a4"; libraryHaskellDepends = [ base containers di-core exceptions mtl pipes stm transformers ]; @@ -9913,162 +11120,40 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/k0001/di"; description = "mtl flavoured typeful hierarchical structured logging for di-core"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "diagrams" = callPackage - ({ mkDerivation, diagrams-contrib, diagrams-core, diagrams-lib - , diagrams-svg, stdenv - }: - mkDerivation { - pname = "diagrams"; - version = "1.4"; - sha256 = "8608f6fa682b8c43b9fbe7c42c033c7a6de0680bd7383f6a81ea8bca37999139"; - libraryHaskellDepends = [ - diagrams-contrib diagrams-core diagrams-lib diagrams-svg - ]; - doHaddock = false; - doCheck = false; - homepage = "http://projects.haskell.org/diagrams"; - description = "Embedded domain-specific language for declarative vector graphics"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "diagrams-contrib" = callPackage - ({ mkDerivation, base, circle-packing, colour, containers - , cubicbezier, data-default, data-default-class, diagrams-core - , diagrams-lib, diagrams-solve, force-layout, hashable, lens - , linear, mfsolve, MonadRandom, monoid-extras, mtl, mtl-compat - , parsec, random, semigroups, split, stdenv, text - }: - mkDerivation { - pname = "diagrams-contrib"; - version = "1.4.3"; - sha256 = "65fba87bb7752b1053fb3ab8e4ae30d5920208ff48441c4d8969cdbe73402007"; - revision = "1"; - editedCabalFile = "16ici9kx7cnva1ihhin5nyc1icif17yks3nwcxxzqxjjw556vpig"; - libraryHaskellDepends = [ - base circle-packing colour containers cubicbezier data-default - data-default-class diagrams-core diagrams-lib diagrams-solve - force-layout hashable lens linear mfsolve MonadRandom monoid-extras - mtl mtl-compat parsec random semigroups split text - ]; - doHaddock = false; - doCheck = false; - homepage = "http://projects.haskell.org/diagrams/"; - description = "Collection of user contributions to diagrams EDSL"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "diagrams-core" = callPackage - ({ mkDerivation, adjunctions, base, containers, distributive - , dual-tree, lens, linear, monoid-extras, mtl, profunctors - , semigroups, stdenv, unordered-containers - }: - mkDerivation { - pname = "diagrams-core"; - version = "1.4.1.1"; - sha256 = "a182e9f99e3664efdfa5e18f4b403703112fba33c5b877a91c9eabed1d8bb682"; - revision = "2"; - editedCabalFile = "1lf7xcq42l4hjksgp1nhj7600shvw9q5a27bh729fyfphmvv3xkf"; - libraryHaskellDepends = [ - adjunctions base containers distributive dual-tree lens linear - monoid-extras mtl profunctors semigroups unordered-containers - ]; - doHaddock = false; - doCheck = false; - homepage = "http://projects.haskell.org/diagrams"; - description = "Core libraries for diagrams EDSL"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "diagrams-lib" = callPackage - ({ mkDerivation, active, adjunctions, array, base, bytestring - , cereal, colour, containers, data-default-class, diagrams-core - , diagrams-solve, directory, distributive, dual-tree, exceptions - , filepath, fingertree, fsnotify, hashable, intervals, JuicyPixels - , lens, linear, monoid-extras, mtl, optparse-applicative, process - , profunctors, semigroups, stdenv, tagged, text, transformers - , unordered-containers - }: - mkDerivation { - pname = "diagrams-lib"; - version = "1.4.2.3"; - sha256 = "25a7adccbe3175cdb081a3824413ba431e561026c6ddd9a647cd133e4bfcbe9c"; - revision = "2"; - editedCabalFile = "0gn1lpsq1v9qpyhpizyknn3sfixg1b64s0dsl1jf25lz4kcrpbs7"; - libraryHaskellDepends = [ - active adjunctions array base bytestring cereal colour containers - data-default-class diagrams-core diagrams-solve directory - distributive dual-tree exceptions filepath fingertree fsnotify - hashable intervals JuicyPixels lens linear monoid-extras mtl - optparse-applicative process profunctors semigroups tagged text - transformers unordered-containers - ]; - doHaddock = false; - doCheck = false; - homepage = "http://projects.haskell.org/diagrams"; - description = "Embedded domain-specific language for declarative graphics"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "diagrams-rasterific" = callPackage - ({ mkDerivation, base, bytestring, containers, data-default-class - , diagrams-core, diagrams-lib, file-embed, filepath, FontyFruity - , hashable, JuicyPixels, lens, mtl, optparse-applicative - , Rasterific, stdenv - }: - mkDerivation { - pname = "diagrams-rasterific"; - version = "1.4.1.1"; - sha256 = "f72a87b421b1da874757256d9c9603c40fdad1f0a82be17bf1806820188a5365"; - enableSeparateDataOutput = true; - libraryHaskellDepends = [ - base bytestring containers data-default-class diagrams-core - diagrams-lib file-embed filepath FontyFruity hashable JuicyPixels - lens mtl optparse-applicative Rasterific - ]; - doHaddock = false; - doCheck = false; - homepage = "http://projects.haskell.org/diagrams/"; - description = "Rasterific backend for diagrams"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "diagrams-solve" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "diagrams-solve"; - version = "0.1.1"; - sha256 = "a41f5f410b10f162b1e5c07bd4ca3305544870ff1314ae4f5824c83a31644f9d"; - revision = "4"; - editedCabalFile = "1yjacw17ga4rh6iw70vclk03qm5xjw4y17c7m43gjw8h3cfaq15d"; + version = "0.1.3"; + sha256 = "27b4bba55f5c2aae94903fbe7958f27744c0ff6a805ceb8a046ab4bd36e31827"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "http://projects.haskell.org/diagrams"; description = "Pure Haskell solver routines used by diagrams"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "diagrams-svg" = callPackage - ({ mkDerivation, base, base64-bytestring, bytestring, colour - , containers, diagrams-core, diagrams-lib, filepath, hashable - , JuicyPixels, lens, monoid-extras, mtl, optparse-applicative - , semigroups, split, stdenv, svg-builder, text + "dialogflow-fulfillment" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers, lib, text + , unordered-containers }: mkDerivation { - pname = "diagrams-svg"; - version = "1.4.2"; - sha256 = "5455b68d92826a5405d51490976870cc0fa5b8b56aef0a8f56982b5f48efded2"; - revision = "2"; - editedCabalFile = "15sn85xaachw4cj56w61bjcwrbf4qmnkfl8mbgdapxi5k0y4f2qv"; + pname = "dialogflow-fulfillment"; + version = "0.1.1.4"; + sha256 = "f8fb3b69a4e925d8658ac2a029594493f871e21962857c4ff457c5ac2e82c47b"; libraryHaskellDepends = [ - base base64-bytestring bytestring colour containers diagrams-core - diagrams-lib filepath hashable JuicyPixels lens monoid-extras mtl - optparse-applicative semigroups split svg-builder text + aeson base bytestring containers text unordered-containers ]; doHaddock = false; doCheck = false; - homepage = "http://projects.haskell.org/diagrams/"; - description = "SVG backend for diagrams drawing EDSL"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/mauriciofierrom/dialogflow-fulfillment"; + description = "A Dialogflow Fulfillment library for Haskell"; + license = lib.licenses.bsd3; }) {}; "dictionary-sharing" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "dictionary-sharing"; version = "0.1.0.0"; @@ -10079,23 +11164,23 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Sharing/memoization of class members"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "digest" = callPackage - ({ mkDerivation, base, bytestring, stdenv, zlib }: + ({ mkDerivation, base, bytestring, lib, zlib }: mkDerivation { pname = "digest"; - version = "0.0.1.2"; - sha256 = "641717eb16392abf8965986a9e8dc21eebf1d97775bbb6923c7b7f8fee17fe11"; + version = "0.0.1.3"; + sha256 = "5596a53e17c036b9b2aefbed069ec819b36fefcd4bed21330ae0ee5be840a3d0"; libraryHaskellDepends = [ base bytestring ]; librarySystemDepends = [ zlib ]; doHaddock = false; doCheck = false; description = "Various cryptographic hashes for bytestrings; CRC32 and Adler32 for now"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) zlib;}; "digits" = callPackage - ({ mkDerivation, base, QuickCheck, stdenv }: + ({ mkDerivation, base, lib, QuickCheck }: mkDerivation { pname = "digits"; version = "0.3.1"; @@ -10104,23 +11189,40 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Converts integers to lists of digits and back"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "dimensional" = callPackage + ({ mkDerivation, base, deepseq, exact-pi, ieee754, lib, numtype-dk + , semigroups, vector + }: + mkDerivation { + pname = "dimensional"; + version = "1.4"; + sha256 = "1a5d25018293f95c592a7e10245f680dc02d3723c53bf8f9c39cfa932ebd86a7"; + libraryHaskellDepends = [ + base deepseq exact-pi ieee754 numtype-dk semigroups vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/bjornbm/dimensional/"; + description = "Statically checked physical dimensions"; + license = lib.licenses.bsd3; }) {}; "direct-sqlite" = callPackage - ({ mkDerivation, base, bytestring, semigroups, stdenv, text }: + ({ mkDerivation, base, bytestring, lib, semigroups, text }: mkDerivation { pname = "direct-sqlite"; - version = "2.3.23"; - sha256 = "1fdb6f6ea34ac978e72f61a845786e4b4b945014ccc64ddb07ddcafa1254937b"; + version = "2.3.26"; + sha256 = "7e18237a0129b69b68db394bf1d912b664edf16ce335cbd65330d10eb1e2f9fc"; libraryHaskellDepends = [ base bytestring semigroups text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/IreneKnapp/direct-sqlite"; description = "Low-level binding to SQLite3. Includes UTF8 and BLOB support."; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "directory-tree" = callPackage - ({ mkDerivation, base, directory, filepath, stdenv }: + ({ mkDerivation, base, directory, filepath, lib }: mkDerivation { pname = "directory-tree"; version = "0.12.1"; @@ -10130,10 +11232,27 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://brandon.si/code/directory-tree-module-released/"; description = "A simple directory-like tree datatype, with useful IO functions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "dirichlet" = callPackage + ({ mkDerivation, base, lib, log-domain, math-functions, mwc-random + , primitive, vector + }: + mkDerivation { + pname = "dirichlet"; + version = "0.1.0.4"; + sha256 = "cf0d9aa05696a9e68e46658ae9d3909197d1262bc5a7f58b6edfe7f61bc313e2"; + libraryHaskellDepends = [ + base log-domain math-functions mwc-random primitive vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/dschrempf/dirichlet"; + description = "Multivariate Dirichlet distribution"; + license = lib.licenses.bsd3; }) {}; "discount" = callPackage - ({ mkDerivation, base, bytestring, markdown, stdenv, text }: + ({ mkDerivation, base, bytestring, lib, markdown, text }: mkDerivation { pname = "discount"; version = "0.1.1"; @@ -10144,10 +11263,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/lightquake/discount"; description = "Haskell bindings to the discount Markdown library"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {inherit (pkgs) markdown;}; "disk-free-space" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "disk-free-space"; version = "0.1.0.1"; @@ -10159,16 +11278,16 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/redneb/disk-free-space"; description = "Retrieve information about disk space usage"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "distributed-closure" = callPackage - ({ mkDerivation, async, base, binary, bytestring, constraints - , stdenv, syb, template-haskell + ({ mkDerivation, async, base, binary, bytestring, constraints, lib + , syb, template-haskell }: mkDerivation { pname = "distributed-closure"; - version = "0.4.1"; - sha256 = "de4efea05ec685e9b5b087857ea3460a24d4314862e329279b99ca914b2e7ce6"; + version = "0.4.2.0"; + sha256 = "16d0b35bea1aa1d43d4935d1569b3f3894febd66a5834129b8699437d6a85750"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -10179,30 +11298,30 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/tweag/distributed-closure"; description = "Serializable closures for distributed programming"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "distribution-nixpkgs" = callPackage ({ mkDerivation, aeson, base, bytestring, Cabal, containers - , deepseq, language-nix, lens, pretty, process, split, stdenv + , deepseq, language-nix, lens, lib, pretty, process, split }: mkDerivation { pname = "distribution-nixpkgs"; - version = "1.1.1"; - sha256 = "55eb858a98995f4f2b2eec5fcbc44ba1901284e915ef5e18609e253a5a662499"; + version = "1.5.0"; + sha256 = "f38e7a3c2bc14ad58c377ba52abe26017b7785379e21a25a5f4aa7fffd6ce11f"; libraryHaskellDepends = [ aeson base bytestring Cabal containers deepseq language-nix lens pretty process split ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/peti/distribution-nixpkgs#readme"; + homepage = "https://github.com/peti/distribution-nixpkgs"; description = "Types and functions to manipulate the Nixpkgs distribution"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "distribution-opensuse" = callPackage ({ mkDerivation, aeson, base, binary, bytestring, containers - , deepseq, Diff, extra, foldl, hashable, hsemail, mtl, parsec-class - , pretty, stdenv, text, time, turtle + , deepseq, Diff, extra, foldl, hashable, hsemail, lib, mtl + , parsec-class, pretty, text, time, turtle }: mkDerivation { pname = "distribution-opensuse"; @@ -10219,39 +11338,59 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/peti/distribution-opensuse/"; description = "Types, functions, and tools to manipulate the openSUSE distribution"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "distributive" = callPackage - ({ mkDerivation, base, base-orphans, Cabal, cabal-doctest, stdenv - , tagged, transformers - }: + ({ mkDerivation, base, base-orphans, lib, tagged, transformers }: mkDerivation { pname = "distributive"; - version = "0.6"; - sha256 = "a4af1341a63a430dc569dd1e59631f127c40ebdd353a945a74d18682f6bdc1d4"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "0.6.2.1"; + sha256 = "d7351392e078f58caa46630a4b9c643e1e2e9dddee45848c5c8358e7b1316b91"; libraryHaskellDepends = [ base base-orphans tagged transformers ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/distributive/"; description = "Distributive functors -- Dual to Traversable"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "dl-fedora" = callPackage + ({ mkDerivation, base, bytestring, directory, extra, filepath + , http-client, http-client-tls, http-directory, http-types, lib + , optparse-applicative, regex-posix, simple-cmd, simple-cmd-args + , text, time, unix, xdg-userdirs + }: + mkDerivation { + pname = "dl-fedora"; + version = "0.9"; + sha256 = "edc60ab7a9fb6409e98c6dbb5e22b421efa703a4d20279725be1e658cca6709e"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ + base bytestring directory extra filepath http-client + http-client-tls http-directory http-types optparse-applicative + regex-posix simple-cmd simple-cmd-args text time unix xdg-userdirs + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/juhp/dl-fedora"; + description = "Fedora image download tool"; + license = lib.licenses.gpl3Only; }) {}; "dlist" = callPackage - ({ mkDerivation, base, deepseq, stdenv }: + ({ mkDerivation, base, deepseq, lib }: mkDerivation { pname = "dlist"; - version = "0.8.0.5"; - sha256 = "98a88aa839b40d4aee8b08880030d282d627b63de311f5414dca6e831a951b43"; + version = "1.0"; + sha256 = "173d637328bb173fcc365f30d29ff4a94292a1e0e5558aeb3dfc11de81510115"; libraryHaskellDepends = [ base deepseq ]; doHaddock = false; doCheck = false; homepage = "https://github.com/spl/dlist"; description = "Difference lists"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "dlist-instances" = callPackage - ({ mkDerivation, base, dlist, semigroups, stdenv }: + ({ mkDerivation, base, dlist, lib, semigroups }: mkDerivation { pname = "dlist-instances"; version = "0.1.1.1"; @@ -10261,18 +11400,18 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/gregwebs/dlist-instances"; description = "Difference lists instances"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "dlist-nonempty" = callPackage - ({ mkDerivation, base, base-compat, deepseq, dlist, semigroupoids - , stdenv + ({ mkDerivation, base, base-compat, deepseq, dlist, lib + , semigroupoids }: mkDerivation { pname = "dlist-nonempty"; version = "0.1.1"; sha256 = "40e8a64c979ca07b4f67a38878d1d13c1127fe2d1ad6b2b4daff0ee2dbd54b33"; - revision = "4"; - editedCabalFile = "10kkj4sf1bn87z6744p9gn6mkciqri2d3l9vmg9ylpi8g7priil2"; + revision = "10"; + editedCabalFile = "0k9h3d93ivjykdpblkdcxyv1aybbjq6m5laqjh7bdv6nrdr5va2c"; libraryHaskellDepends = [ base base-compat deepseq dlist semigroupoids ]; @@ -10280,30 +11419,30 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/phadej/dlist-nonempty"; description = "Non-empty difference lists"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "dns" = callPackage - ({ mkDerivation, async, attoparsec, auto-update, base - , base64-bytestring, binary, bytestring, containers, cryptonite - , iproute, mtl, network, psqueues, safe, stdenv, time + ({ mkDerivation, array, async, attoparsec, auto-update, base + , base16-bytestring, base64-bytestring, bytestring, containers + , cryptonite, hourglass, iproute, lib, mtl, network, psqueues }: mkDerivation { pname = "dns"; - version = "3.0.4"; - sha256 = "7b3433b536b7d225914d7b8495c7af1927d9554538d7d86c2644ccf9d3fa44a9"; + version = "4.0.1"; + sha256 = "20cdb4519f19becd5ba321c5acfe03fd3c16b298a78404530b65f10ddb4a68cb"; libraryHaskellDepends = [ - async attoparsec auto-update base base64-bytestring binary - bytestring containers cryptonite iproute mtl network psqueues safe - time + array async attoparsec auto-update base base16-bytestring + base64-bytestring bytestring containers cryptonite hourglass + iproute mtl network psqueues ]; doHaddock = false; doCheck = false; testTarget = "spec"; description = "DNS library in Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "do-list" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "do-list"; version = "1.0.1"; @@ -10313,10 +11452,23 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/tserduke/do-list#readme"; description = "Do notation for free"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "do-notation" = callPackage + ({ mkDerivation, base, indexed, lib }: + mkDerivation { + pname = "do-notation"; + version = "0.1.0.2"; + sha256 = "c9f3783d4b8ede05bf64a9dc7c594306b40fb05a68ae7f4c21dafec52fbc7bf5"; + libraryHaskellDepends = [ base indexed ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/isovector/do-notation#readme"; + description = "Generalize do-notation to work on monads and indexed monads simultaneously"; + license = lib.licenses.bsd3; }) {}; "dockerfile" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "dockerfile"; version = "0.2.0"; @@ -10326,54 +11478,50 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/creichert/dockerfile#readme"; description = "A Haskell DSL for generating Dockerfiles"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "docopt" = callPackage - ({ mkDerivation, base, containers, parsec, stdenv, template-haskell - , th-lift - }: + "doclayout" = callPackage + ({ mkDerivation, base, lib, mtl, safe, text }: mkDerivation { - pname = "docopt"; - version = "0.7.0.5"; - sha256 = "15790808a4896bbf0748c1c0f3ab63c07aea4621d95b93a39886813f829d05ee"; + pname = "doclayout"; + version = "0.3.0.2"; + sha256 = "78ac66b57a4c1c04393bf3745fb3e25bac644e1b25f4df4797b2d55cdc53d8c1"; enableSeparateDataOutput = true; - libraryHaskellDepends = [ - base containers parsec template-haskell th-lift - ]; + libraryHaskellDepends = [ base mtl safe text ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/docopt/docopt.hs"; - description = "A command-line interface parser that will make you smile"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/jgm/doclayout"; + description = "A prettyprinting library for laying out text documents"; + license = lib.licenses.bsd3; }) {}; "doctemplates" = callPackage - ({ mkDerivation, aeson, base, blaze-html, blaze-markup, bytestring - , containers, parsec, scientific, stdenv, text - , unordered-containers, vector + ({ mkDerivation, aeson, base, containers, doclayout, filepath + , HsYAML, lib, mtl, parsec, safe, scientific, text + , text-conversions, unordered-containers, vector }: mkDerivation { pname = "doctemplates"; - version = "0.2.2.1"; - sha256 = "6b0cfb565fc7fa90d71ac56b83aedecf670678e6f1441278877fbf399e9bccbf"; + version = "0.9"; + sha256 = "da262ec09d0689c27a79589d2abecb03609ef3925a4dde3b70012682d4441011"; enableSeparateDataOutput = true; libraryHaskellDepends = [ - aeson base blaze-html blaze-markup bytestring containers parsec - scientific text unordered-containers vector + aeson base containers doclayout filepath HsYAML mtl parsec safe + scientific text text-conversions unordered-containers vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/jgm/doctemplates#readme"; description = "Pandoc-style document templates"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "doctest" = callPackage ({ mkDerivation, base, base-compat, code-page, deepseq, directory - , filepath, ghc, ghc-paths, process, stdenv, syb, transformers + , filepath, ghc, ghc-paths, lib, process, syb, transformers }: mkDerivation { pname = "doctest"; - version = "0.16.0.1"; - sha256 = "9b5275497330607f66aaf2625b798b2ad566867fed3f52cea9de31a23361d780"; + version = "0.17"; + sha256 = "ff12a52057335ff263db3e2ecd36cab2e0140ca5ae8c98bdfd4c7a83dfb31338"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -10388,11 +11536,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/sol/doctest#readme"; description = "Test interactive Haskell examples"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "doctest-discover" = callPackage ({ mkDerivation, aeson, base, bytestring, directory, doctest - , filepath, stdenv + , filepath, lib }: mkDerivation { pname = "doctest-discover"; @@ -10410,14 +11558,14 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/karun012/doctest-discover"; description = "Easy way to run doctests via cabal"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "doctest-driver-gen" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "doctest-driver-gen"; - version = "0.3.0.0"; - sha256 = "614245e6b957ff3d380ef33e750df1ac109870c6d7de242ce5f999034a70a58e"; + version = "0.3.0.4"; + sha256 = "2a787e31482a307e058014bb8c3e50b4468ad21e70d9a3c8f6b04b45348978b9"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base ]; @@ -10426,36 +11574,98 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/Hexirp/doctest-driver-gen#readme"; description = "Generate driver file for doctest's cabal integration"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "dom-parser" = callPackage - ({ mkDerivation, base, case-insensitive, containers, lens, mtl - , scientific, semigroups, stdenv, text, transformers, xml-conduit - , xml-lens + "doctest-exitcode-stdio" = callPackage + ({ mkDerivation, base, doctest-lib, lib, QuickCheck, semigroups + , transformers }: mkDerivation { - pname = "dom-parser"; - version = "3.1.0"; - sha256 = "d7e15cae0b27d708389160517b1616343da1911baf95f2c97e213732a0262ac3"; + pname = "doctest-exitcode-stdio"; + version = "0.0"; + sha256 = "1dec779d5e67ea46c8b0d69d454e0717383654e87323bdebc2bc0a8cb33f6cbc"; libraryHaskellDepends = [ - base case-insensitive containers lens mtl scientific semigroups - text transformers xml-conduit xml-lens + base doctest-lib QuickCheck semigroups transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://hub.darcs.net/thielema/doctest-exitcode-stdio/"; + description = "Run doctest's in a Cabal.Test.exitcode-stdio environment"; + license = lib.licenses.bsd3; + }) {}; + "doctest-extract" = callPackage + ({ mkDerivation, base, doctest-lib, lib, non-empty + , optparse-applicative, pathtype, semigroups, transformers + , utility-ht + }: + mkDerivation { + pname = "doctest-extract"; + version = "0.1"; + sha256 = "ba66bf87c1847a4d5b90ebe78cb0863d23ed0d3e4fd44255e1987dd38ec199d9"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ + base doctest-lib non-empty optparse-applicative pathtype semigroups + transformers utility-ht ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/typeable/dom-parser"; - description = "Simple monadic DOM parser"; - license = stdenv.lib.licenses.mit; + homepage = "https://hub.darcs.net/thielema/doctest-extract/"; + description = "Alternative doctest implementation that extracts comments to modules"; + license = lib.licenses.bsd3; + }) {}; + "doctest-lib" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "doctest-lib"; + version = "0.1"; + sha256 = "02c6fa934b4ebc1abca1f7346920921969fc5080397efb606ca270d840555cef"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://hub.darcs.net/thielema/doctest-lib/"; + description = "Parts of doctest exposed as library"; + license = lib.licenses.mit; + }) {}; + "doldol" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "doldol"; + version = "0.4.1.2"; + sha256 = "6553dcb9fded77f0f0655264a4b071e503690a467b46921679556cef5da43e65"; + revision = "1"; + editedCabalFile = "0xwbdrfzd6z3nwkgnav2drisw2sn464ggkz8fid58cym9hbfpl47"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/QuietJoon/doldol/"; + description = "Flag packer & handler for flaggable data"; + license = lib.licenses.bsd3; + }) {}; + "dot" = callPackage + ({ mkDerivation, base, lib, text }: + mkDerivation { + pname = "dot"; + version = "0.3"; + sha256 = "b6144d948d86fe8f8df6c4ec12d4d127733dc6b194a6d204792a5fadb42e8483"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/andrewthad/dot"; + description = "Datatypes and encoding for graphviz dot files"; + license = lib.licenses.bsd3; }) {}; "dotenv" = callPackage ({ mkDerivation, base, base-compat, containers, directory - , exceptions, megaparsec, optparse-applicative, process, stdenv - , text, transformers, yaml + , exceptions, lib, megaparsec, optparse-applicative, process, text + , transformers, yaml }: mkDerivation { pname = "dotenv"; - version = "0.8.0.0"; - sha256 = "9e9621053792480de87fd0344bf7fdbe7c118d9ec48317a7d4c0cd02f9f9372c"; + version = "0.8.0.7"; + sha256 = "1b0471843ff85d3ee22a049908975d44952e367a778cf9d76ab910475d54a787"; isLibrary = true; isExecutable = true; enableSeparateDataOutput = true; @@ -10471,14 +11681,14 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/stackbuilders/dotenv-hs"; description = "Loads environment variables from dotenv files"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "dotgen" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "dotgen"; - version = "0.4.2"; - sha256 = "cf0de20a435d74aeb9a32b8bcb3ebfa1b6659ac3f26edefe2df9e1aaf1481891"; + version = "0.4.3"; + sha256 = "da1c78f7daf0470465ce095fd0f3b3e8a4e4744d5b582a0f6e590a32522d96c9"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base containers ]; @@ -10486,10 +11696,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/ku-fpg/dotgen"; description = "A simple interface for building .dot graph files."; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "dotnet-timespan" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "dotnet-timespan"; version = "0.0.1.0"; @@ -10499,10 +11709,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/YoEight/dotnet-timespan"; description = ".NET TimeSpan"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "double-conversion" = callPackage - ({ mkDerivation, base, bytestring, ghc-prim, stdenv, text }: + ({ mkDerivation, base, bytestring, ghc-prim, lib, text }: mkDerivation { pname = "double-conversion"; version = "2.0.2.0"; @@ -10512,23 +11722,38 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/bos/double-conversion"; description = "Fast conversion between double precision floating point and text"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "download" = callPackage - ({ mkDerivation, base, bytestring, feed, stdenv, tagsoup, xml }: + ({ mkDerivation, base, bytestring, feed, lib, tagsoup, xml }: mkDerivation { pname = "download"; - version = "0.3.2.6"; - sha256 = "a06d401a2ca58b6ee494ce462c753939ef0a2d11b4d475ae40848884fb44eef2"; + version = "0.3.2.7"; + sha256 = "7154571d2c55c14b7a2d36a924ee10fd56511b70fe856dddbfbd15f04f0be6e1"; libraryHaskellDepends = [ base bytestring feed tagsoup xml ]; doHaddock = false; doCheck = false; homepage = "https://github.com/psibi/download"; description = "High-level file download based on URLs"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "download-curl" = callPackage + ({ mkDerivation, base, bytestring, curl, feed, lib, tagsoup, xml }: + mkDerivation { + pname = "download-curl"; + version = "0.1.4"; + sha256 = "950ede497ff41d72875337861fa41ca3e151b691ad53a9ddddd2443285bbc3f1"; + revision = "2"; + editedCabalFile = "032f19gn7bnx3fpfdwclm1z1hsxaya6yml7p2hcg3b2ad6d11pyl"; + libraryHaskellDepends = [ base bytestring curl feed tagsoup xml ]; + doHaddock = false; + doCheck = false; + homepage = "http://code.haskell.org/~dons/code/download-curl"; + description = "High-level file download based on URLs"; + license = lib.licenses.bsd3; }) {}; "drinkery" = callPackage - ({ mkDerivation, base, exceptions, mtl, stdenv, transformers }: + ({ mkDerivation, base, exceptions, lib, mtl, transformers }: mkDerivation { pname = "drinkery"; version = "0.4"; @@ -10538,14 +11763,14 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/fumieval/drinkery#readme"; description = "Boozy streaming library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "dsp" = callPackage - ({ mkDerivation, array, base, containers, random, stdenv }: + ({ mkDerivation, array, base, containers, lib, random }: mkDerivation { pname = "dsp"; - version = "0.2.4.1"; - sha256 = "3322954e87b279a94c1fb43a5d16e4d0022e7d422a2d2b9be0f3c4b4d346e42c"; + version = "0.2.5.1"; + sha256 = "ce163f8991fc61ca4414dc39fca8818482190b9694991a69a5134a2c2dc6b00e"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ array base containers random ]; @@ -10553,30 +11778,26 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/DSP"; description = "Haskell Digital Signal Processing"; - license = "GPL"; + license = lib.licenses.gpl2Only; }) {}; - "dual-tree" = callPackage - ({ mkDerivation, base, monoid-extras, newtype-generics, semigroups - , stdenv - }: + "dual" = callPackage + ({ mkDerivation, base, lib }: mkDerivation { - pname = "dual-tree"; - version = "0.2.2"; - sha256 = "7412d70cf239da98b5a21df1cbbeab7319fd23d757427d4f5ce71b907dbaa9eb"; - revision = "2"; - editedCabalFile = "0r8idr1haqixa9nlp8db5iw9vr9sdk6rcargkr7w7s6i99lm6jmh"; - libraryHaskellDepends = [ - base monoid-extras newtype-generics semigroups - ]; + pname = "dual"; + version = "0.1.1.1"; + sha256 = "4504b29c4c758457cb6accc00ad4ef4a3f940125ade67301a3549091b9dfc765"; + revision = "1"; + editedCabalFile = "1cm80lc3p8bpzj0crxccx2fp33p171gz4j56r9fc5g5kza390nrb"; + libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - description = "Rose trees with cached and accumulating monoidal annotations"; - license = stdenv.lib.licenses.bsd3; + description = "Dual category"; + license = lib.licenses.bsd3; }) {}; "dublincore-xml-conduit" = callPackage - ({ mkDerivation, base, conduit, conduit-combinators - , safe-exceptions, stdenv, text, time, timerep, uri-bytestring - , xml-conduit, xml-types + ({ mkDerivation, base, conduit, conduit-combinators, lib + , safe-exceptions, text, time, timerep, uri-bytestring, xml-conduit + , xml-types }: mkDerivation { pname = "dublincore-xml-conduit"; @@ -10592,57 +11813,40 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/k0ral/dublincore-xml-conduit"; description = "XML streaming parser/renderer for the Dublin Core standard elements"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "dunai" = callPackage - ({ mkDerivation, base, MonadRandom, stdenv, transformers - , transformers-base + ({ mkDerivation, base, lib, MonadRandom, simple-affine-space + , transformers, transformers-base }: mkDerivation { pname = "dunai"; - version = "0.5.1"; - sha256 = "27a5ba03273afe4e5d3e947fb65e2d70e2f82cb929316b0c3175d1f2cf95731d"; + version = "0.7.0"; + sha256 = "5073a8e2a5bd9f9140e3d558723e4254130f88252a17ac0904539d529a0031be"; libraryHaskellDepends = [ - base MonadRandom transformers transformers-base + base MonadRandom simple-affine-space transformers transformers-base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/ivanperez-keera/dunai"; description = "Generalised reactive framework supporting classic, arrowized and monadic FRP"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "dunai-core" = callPackage - ({ mkDerivation, base, MonadRandom, stdenv, transformers - , transformers-base - }: - mkDerivation { - pname = "dunai-core"; - version = "0.5.1.0"; - sha256 = "ffaf15694944fe046ba2dd385be2edad7a7bd2b9d766804770af85636a3001dd"; - libraryHaskellDepends = [ - base MonadRandom transformers transformers-base - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/turion/dunai-core"; - description = "Generalised reactive framework supporting classic, arrowized and monadic FRP. (Core library fork.)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "duration" = callPackage - ({ mkDerivation, base, parsec, stdenv, template-haskell, time }: + ({ mkDerivation, base, lib, parsec, template-haskell, time }: mkDerivation { pname = "duration"; - version = "0.1.0.0"; - sha256 = "a0b154c270be1d9c42a92fdf8198ab1030bf09a119157df33a2a43694fb212a3"; + version = "0.2.0.0"; + sha256 = "726b86eeb2dffb16f3b237dbd759c1e0af2f8bc41e4913f27d038111b35dafb2"; libraryHaskellDepends = [ base parsec template-haskell time ]; doHaddock = false; doCheck = false; homepage = "https://github.com/ryota-ka/duration#readme"; description = "A tiny compile-time time utility library inspired by zeit/ms"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "dvorak" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "dvorak"; version = "0.1.0.0"; @@ -10652,10 +11856,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/kvanberendonck/codec-dvorak"; description = "Dvorak encoding for Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "dynamic-state" = callPackage - ({ mkDerivation, base, binary, bytestring, hashable, stdenv + ({ mkDerivation, base, binary, bytestring, hashable, lib , unordered-containers }: mkDerivation { @@ -10668,28 +11872,60 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Optionally serializable dynamic state keyed by type"; - license = stdenv.lib.licenses.gpl2; + license = lib.licenses.gpl2Only; }) {}; "dyre" = callPackage ({ mkDerivation, base, binary, directory, executable-path, filepath - , ghc-paths, io-storage, process, stdenv, time, unix, xdg-basedir + , io-storage, lib, process, time, unix, xdg-basedir }: mkDerivation { pname = "dyre"; - version = "0.8.12"; - sha256 = "e224305cc6b38b4143f49489931c2ea94b326915206d34eddf5b2ee2b5a71682"; + version = "0.9.1"; + sha256 = "b03ae822d09c270aa38dc8aba44a9b58513674c32fb3ab47a3e19e02d59637d3"; libraryHaskellDepends = [ - base binary directory executable-path filepath ghc-paths io-storage - process time unix xdg-basedir + base binary directory executable-path filepath io-storage process + time unix xdg-basedir ]; doHaddock = false; doCheck = false; homepage = "http://github.com/willdonnelly/dyre"; description = "Dynamic reconfiguration in Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "eap" = callPackage + ({ mkDerivation, base, binary, bytestring, cryptonite, lib, memory + , mtl, pretty-hex + }: + mkDerivation { + pname = "eap"; + version = "0.9.0.2"; + sha256 = "0ccf6246c1e28d43aea25d1e2e0ca22edcc3bfb21fcf7924410dee7abb3efd2d"; + revision = "1"; + editedCabalFile = "1lsy7pl39s02f45l7g9alw49xwh7m8m4bm3ydcz11rh9xdgcb9jv"; + libraryHaskellDepends = [ + base binary bytestring cryptonite memory mtl pretty-hex + ]; + doHaddock = false; + doCheck = false; + homepage = "https://gitlab.com/codemonkeylabs/eap#readme"; + description = "Extensible Authentication Protocol (EAP)"; + license = lib.licenses.bsd3; + }) {}; + "earcut" = callPackage + ({ mkDerivation, base, lib, vector }: + mkDerivation { + pname = "earcut"; + version = "0.1.0.4"; + sha256 = "4ef7ef928df1b07ae59fe5e6142259b912490c9d04d3b21ce53f9f64eca15a5b"; + libraryHaskellDepends = [ base vector ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/reanimate/earcut"; + description = "Binding to C++ earcut library"; + license = lib.licenses.isc; }) {}; "easy-file" = callPackage - ({ mkDerivation, base, directory, filepath, stdenv, time, unix }: + ({ mkDerivation, base, directory, filepath, lib, time, unix }: mkDerivation { pname = "easy-file"; version = "0.2.2"; @@ -10699,33 +11935,14 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/kazu-yamamoto/easy-file"; description = "Cross-platform File handling"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "easytest" = callPackage - ({ mkDerivation, async, base, call-stack, containers, mtl, random - , stdenv, stm, text, transformers - }: - mkDerivation { - pname = "easytest"; - version = "0.2.1"; - sha256 = "1155c3da78460eae48762e041c033d0f64f7644fa94479be2fa1194e3f57be3d"; - libraryHaskellDepends = [ - async base call-stack containers mtl random stm text transformers - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/joelburget/easytest"; - description = "Simple, expressive testing library"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.bsd3; }) {}; "echo" = callPackage - ({ mkDerivation, base, process, stdenv }: + ({ mkDerivation, base, lib, process }: mkDerivation { pname = "echo"; - version = "0.1.3"; - sha256 = "704f07310f8272d170f8ab7fb2a2c13f15d8501ef8310801e36964c8eff485ef"; - revision = "1"; - editedCabalFile = "0br8wfiybcw5hand4imiw0i5hacdmrax1dv8g95f35gazffbx42l"; + version = "0.1.4"; + sha256 = "c9fe1bf2904825a65b667251ec644f197b71dc5c209d2d254be5de3d496b0e43"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base process ]; @@ -10733,25 +11950,42 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/RyanGlScott/echo"; description = "A cross-platform, cross-console way to handle echoing terminal input"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "ecstasy" = callPackage + ({ mkDerivation, base, containers, kan-extensions, lib, mtl + , transformers + }: + mkDerivation { + pname = "ecstasy"; + version = "0.2.1.0"; + sha256 = "915942d3b8c3d61b98e5b2e825387d48cf3c2d17acdb2d377cb516c26c0fcbc3"; + libraryHaskellDepends = [ + base containers kan-extensions mtl transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/isovector/ecstasy/"; + description = "A GHC.Generics based entity component system."; + license = lib.licenses.bsd3; }) {}; "ed25519" = callPackage - ({ mkDerivation, base, bytestring, ghc-prim, stdenv }: + ({ mkDerivation, base, bytestring, ghc-prim, lib }: mkDerivation { pname = "ed25519"; version = "0.0.5.0"; sha256 = "d8a5958ebfa9309790efade64275dc5c441b568645c45ceed1b0c6ff36d6156d"; - revision = "2"; - editedCabalFile = "1cq6h3jqkb1kvd9fjfhsllg5gq78sdiyf2gy9862xhlbv6wil19f"; + revision = "3"; + editedCabalFile = "1yidh86ymzwmp2b449pwim6vvfcs1qgkkncbixw1zmb7wj6v167v"; libraryHaskellDepends = [ base bytestring ghc-prim ]; doHaddock = false; doCheck = false; homepage = "http://thoughtpolice.github.com/hs-ed25519"; description = "Ed25519 cryptographic signatures"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "edit-distance" = callPackage - ({ mkDerivation, array, base, containers, random, stdenv }: + ({ mkDerivation, array, base, containers, lib, random }: mkDerivation { pname = "edit-distance"; version = "0.2.2.1"; @@ -10763,10 +11997,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/phadej/edit-distance"; description = "Levenshtein and restricted Damerau-Levenshtein edit distances"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "edit-distance-vector" = callPackage - ({ mkDerivation, base, stdenv, vector }: + ({ mkDerivation, base, lib, vector }: mkDerivation { pname = "edit-distance-vector"; version = "1.0.0.4"; @@ -10776,12 +12010,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/thsutton/edit-distance-vector"; description = "Calculate edit distances and edit scripts between vectors"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "editor-open" = callPackage ({ mkDerivation, base, bytestring, conduit, conduit-extra - , directory, process, resourcet, stdenv, temporary, transformers - , unix + , directory, lib, process, resourcet, temporary, transformers, unix }: mkDerivation { pname = "editor-open"; @@ -10801,47 +12034,151 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/pharpend/editor-open"; description = "Open the user's $VISUAL or $EDITOR for text input"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; + }) {}; + "egison" = callPackage + ({ mkDerivation, array, base, containers, directory, exceptions + , filepath, ghc, ghc-paths, hashable, haskeline, lib, megaparsec + , mtl, optparse-applicative, parsec, parser-combinators + , prettyprinter, process, random, regex-tdfa, split, sweet-egison + , text, transformers, unicode-show, unordered-containers, vector + }: + mkDerivation { + pname = "egison"; + version = "4.1.2"; + sha256 = "15dd4a92a8b836d9a25380eef4d609740fe0061f3478dfdfbf513e758f4668c0"; + isLibrary = true; + isExecutable = true; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + array base containers directory ghc ghc-paths hashable haskeline + megaparsec mtl optparse-applicative parsec parser-combinators + prettyprinter process random regex-tdfa split sweet-egison text + transformers unicode-show unordered-containers vector + ]; + executableHaskellDepends = [ + array base containers directory exceptions filepath ghc ghc-paths + haskeline mtl optparse-applicative parsec prettyprinter process + regex-tdfa split text transformers unordered-containers vector + ]; + doHaddock = false; + doCheck = false; + homepage = "http://www.egison.org"; + description = "Programming language with non-linear pattern-matching against non-free data"; + license = lib.licenses.mit; + }) {}; + "egison-pattern-src" = callPackage + ({ mkDerivation, base, containers, free, lib, megaparsec, mtl + , parser-combinators, prettyprinter, recursion-schemes, text + }: + mkDerivation { + pname = "egison-pattern-src"; + version = "0.2.1.2"; + sha256 = "6e075b8ff4d028f6725eeecfbd66ebf32afe1dc436961c2192a30cc2521de191"; + libraryHaskellDepends = [ + base containers free megaparsec mtl parser-combinators + prettyprinter recursion-schemes text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/egison/egison-pattern-src#readme"; + description = "Manipulating Egison patterns: abstract syntax, parser, and pretty-printer"; + license = lib.licenses.bsd3; + }) {}; + "egison-pattern-src-th-mode" = callPackage + ({ mkDerivation, base, egison-pattern-src, haskell-src-exts + , haskell-src-meta, lib, mtl, pretty, template-haskell, text + }: + mkDerivation { + pname = "egison-pattern-src-th-mode"; + version = "0.2.1.2"; + sha256 = "cd4749f7fbfc5f1b90f1bd1af9ed022e90508c4313facc39830a76b68d6ea37e"; + libraryHaskellDepends = [ + base egison-pattern-src haskell-src-exts haskell-src-meta mtl + pretty template-haskell text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/egison/egison-pattern-src#readme"; + description = "Parser and pretty printer for Egison pattern expressions to use with TH"; + license = lib.licenses.bsd3; }) {}; "either" = callPackage - ({ mkDerivation, base, bifunctors, mtl, profunctors, semigroupoids - , semigroups, stdenv + ({ mkDerivation, base, bifunctors, lib, mtl, profunctors + , semigroupoids }: mkDerivation { pname = "either"; - version = "5.0.1"; - sha256 = "6cb6eb3f60223f5ffedfcd749589e870a81d272e130cafd1d17fb6d3a8939018"; + version = "5.0.1.1"; + sha256 = "0243d51d6a02ecb541e4854a588a9b6219a4690ebcbdb79387dd14ad519cdf27"; revision = "1"; - editedCabalFile = "1kf0dy6nki64kkmjw8214jz3n086g1pghfm26f012b6qv0iakzca"; + editedCabalFile = "03bgnq55lc6f1nx4p662gidfsyyfm3xm4fi84h77wnsppxrpa5j1"; libraryHaskellDepends = [ - base bifunctors mtl profunctors semigroupoids semigroups + base bifunctors mtl profunctors semigroupoids ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/either/"; description = "Combinators for working with sums"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "either-both" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "either-both"; - version = "0.1.0.0"; - sha256 = "f4b6bbafbc658f028f000fa0711e038206688c9b9ce842bf62e6c3ba16547bd1"; + version = "0.1.1.1"; + sha256 = "6ea467bbcb62d2aded238d3b078fc6fdce44a2137b6be40b209562be3978a6b2"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; description = "Either or both"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "either-unwrap" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "either-unwrap"; + version = "1.1"; + sha256 = "ccabd6f87118abc8dcba481b316c76b8195ac9e8a8f3ddb478de5eb64e2d2e3c"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/gcross/either-unwrap"; + description = "Functions for probing and unwrapping values inside of Either"; + license = lib.licenses.bsd3; + }) {}; + "ekg" = callPackage + ({ mkDerivation, aeson, base, bytestring, ekg-core, ekg-json + , filepath, lib, network, snap-core, snap-server, text, time + , transformers, unordered-containers + }: + mkDerivation { + pname = "ekg"; + version = "0.4.0.15"; + sha256 = "482ae3be495cfe4f03332ad1c79ce8b5ad4f9c8eec824980c664808ae32c6dcc"; + revision = "8"; + editedCabalFile = "05k50vx956zlh7dvkhi7qvd9f7x48hg5hwgqjqsf5fwzm1cqir6n"; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + aeson base bytestring ekg-core ekg-json filepath network snap-core + snap-server text time transformers unordered-containers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/tibbe/ekg"; + description = "Remote monitoring of processes"; + license = lib.licenses.bsd3; }) {}; "ekg-core" = callPackage - ({ mkDerivation, base, containers, ghc-prim, stdenv, text + ({ mkDerivation, base, containers, ghc-prim, lib, text , unordered-containers }: mkDerivation { pname = "ekg-core"; - version = "0.1.1.6"; - sha256 = "66a8dd79ad27659052168f08dd41fabb8593e364de00fb857ef5cc943acd5742"; + version = "0.1.1.7"; + sha256 = "45813f2b94fde0b92c7979bd37de52f09b8b645560f5789276c3acfc7934db12"; + revision = "1"; + editedCabalFile = "17rfxsns0za7jqp3069mwp0lbd433gwb7lrnla02y7hfxbpnldf4"; libraryHaskellDepends = [ base containers ghc-prim text unordered-containers ]; @@ -10849,18 +12186,35 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/tibbe/ekg-core"; description = "Tracking of system metrics"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "ekg-json" = callPackage + ({ mkDerivation, aeson, base, ekg-core, lib, text + , unordered-containers + }: + mkDerivation { + pname = "ekg-json"; + version = "0.1.0.6"; + sha256 = "1e6a80aa0a28bbf41c9c6364cbb5731160d14fa54145f27a82d0b3467a04dd47"; + revision = "7"; + editedCabalFile = "1f53dh7h48j07xw4jdxzwipndap8wdg36d857zdkaxmf14dzqvp1"; + libraryHaskellDepends = [ + aeson base ekg-core text unordered-containers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/tibbe/ekg-json"; + description = "JSON encoding of ekg metrics"; + license = lib.licenses.bsd3; }) {}; "ekg-statsd" = callPackage - ({ mkDerivation, base, bytestring, ekg-core, network, stdenv, text + ({ mkDerivation, base, bytestring, ekg-core, lib, network, text , time, unordered-containers }: mkDerivation { pname = "ekg-statsd"; - version = "0.2.4.0"; - sha256 = "5e74bf63a1cd347c939d4eb7beb9181556b7bd033a60e5f6f4df0505e98a7adb"; - revision = "2"; - editedCabalFile = "1l0lh77qy4kbybkys1d4gg563fc593w27wpf4k1cg9j6ix6y604x"; + version = "0.2.5.0"; + sha256 = "22f947644019f13db105aea665088673fbdcdf6a671e7ec1a72c6134bbd64f0b"; libraryHaskellDepends = [ base bytestring ekg-core network text time unordered-containers ]; @@ -10868,10 +12222,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/tibbe/ekg-statsd"; description = "Push metrics to statsd"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "elerea" = callPackage - ({ mkDerivation, base, containers, stdenv, transformers + ({ mkDerivation, base, containers, lib, transformers , transformers-base }: mkDerivation { @@ -10884,29 +12238,31 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "A minimalistic FRP library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "elf" = callPackage - ({ mkDerivation, base, binary, bytestring, stdenv }: + ({ mkDerivation, base, binary, bytestring, lib }: mkDerivation { pname = "elf"; - version = "0.29"; - sha256 = "426509f12279bdc5a0228f74edef86997dbb47fddc19d83e9815dd301d4a8fac"; + version = "0.30"; + sha256 = "97b0a2cfeff33dcc0640fbd878643e3f87bc88e2da02982f2698728735beee99"; libraryHaskellDepends = [ base binary bytestring ]; doHaddock = false; doCheck = false; homepage = "https://github.com/wangbj/elf"; description = "An Elf parser"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "eliminators" = callPackage - ({ mkDerivation, base, extra, singleton-nats, singletons, stdenv + ({ mkDerivation, base, extra, lib, singleton-nats, singletons , template-haskell, th-abstraction, th-desugar }: mkDerivation { pname = "eliminators"; - version = "0.5"; - sha256 = "f97f4c7b9a2bdc236cb3b8ea14bfbc02e5b21e181b25848b88ea898cee152d34"; + version = "0.7"; + sha256 = "db68ea07eccef20b812b906acc90cbdf5058de151ec9488ffa4b3ea08f0370c0"; + revision = "1"; + editedCabalFile = "1bp8745kynqd8kll3dw36ws9s9j2bzgsr88ij14fx8hab4fm72cn"; libraryHaskellDepends = [ base extra singleton-nats singletons template-haskell th-abstraction th-desugar @@ -10915,10 +12271,23 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/RyanGlScott/eliminators"; description = "Dependently typed elimination functions using singletons"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "elm-bridge" = callPackage + ({ mkDerivation, aeson, base, lib, template-haskell }: + mkDerivation { + pname = "elm-bridge"; + version = "0.6.1"; + sha256 = "fd219fa8c4cb35d57b311e5f2f676ecf73ba2c5ec42e21809d9dcfbf8ffce160"; + libraryHaskellDepends = [ aeson base template-haskell ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/agrafix/elm-bridge"; + description = "Derive Elm types and Json code from Haskell types, using aeson's options"; + license = lib.licenses.bsd3; }) {}; "elm-core-sources" = callPackage - ({ mkDerivation, base, bytestring, containers, file-embed, stdenv + ({ mkDerivation, base, bytestring, containers, file-embed, lib , template-haskell }: mkDerivation { @@ -10932,11 +12301,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/JoeyEremondi/elm-build-lib"; description = "Source files for the Elm runtime and standard libraries"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "elm-export" = callPackage ({ mkDerivation, base, bytestring, containers, directory - , formatting, mtl, stdenv, text, time, wl-pprint-text + , formatting, lib, mtl, text, time, wl-pprint-text }: mkDerivation { pname = "elm-export"; @@ -10951,18 +12320,18 @@ inherit (pkgs.xorg) libXfixes;}; homepage = "http://github.com/krisajenkins/elm-export"; description = "A library to generate Elm types from Haskell source"; license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; + hydraPlatforms = lib.platforms.none; }) {}; "elm2nix" = callPackage ({ mkDerivation, aeson, ansi-wl-pprint, async, base, binary , bytestring, containers, data-default, directory, filepath, here - , mtl, optparse-applicative, process, req, stdenv, text - , transformers, unordered-containers + , lib, mtl, optparse-applicative, process, req, text, transformers + , unordered-containers }: mkDerivation { pname = "elm2nix"; - version = "0.1.0"; - sha256 = "9ec1f1f694a38b466ebd03aaa1a035bbdb9bdae390be5b9a030611bcbfd91890"; + version = "0.2.1"; + sha256 = "79b8854bf4fbc28a05d6f85dabc989937d791db8427878a6ba2a05525a5df8d1"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -10977,102 +12346,212 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/domenkozar/elm2nix#readme"; description = "Turn your Elm project into buildable Nix project"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "emacs-module" = callPackage - ({ mkDerivation, base, bytestring, deepseq, exceptions - , monad-control, mtl, prettyprinter, resourcet - , safe-exceptions-checked, stdenv, template-haskell, text - , transformers-base, vector, void + "elynx" = callPackage + ({ mkDerivation, aeson, base, bytestring, elynx-tools, lib + , optparse-applicative, slynx, tlynx }: mkDerivation { - pname = "emacs-module"; - version = "0.1.1"; - sha256 = "1ee0fd9cde2e218d604c5d1670f24194575f975510936510fe9fc2f6e066d9d4"; - libraryHaskellDepends = [ - base bytestring deepseq exceptions monad-control mtl prettyprinter - resourcet safe-exceptions-checked template-haskell text - transformers-base vector void + pname = "elynx"; + version = "0.5.1.1"; + sha256 = "8ab7cd5306276732dbb0d5319b9f40db1f0566b444eec740f5ab9078bc3704ca"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ + aeson base bytestring elynx-tools optparse-applicative slynx tlynx ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/sergv/emacs-module"; - description = "Utilities to write Emacs dynamic modules"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/dschrempf/elynx#readme"; + description = "Validate and (optionally) redo ELynx analyses"; + license = lib.licenses.gpl3Plus; }) {}; - "email-validate" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, stdenv - , template-haskell + "elynx-markov" = callPackage + ({ mkDerivation, async, attoparsec, base, bytestring, containers + , elynx-seq, hmatrix, integration, lib, math-functions, mwc-random + , primitive, statistics, vector }: mkDerivation { - pname = "email-validate"; - version = "2.3.2.9"; - sha256 = "aeac6eea61192683bbde6bb8bdcf2150a03f79fa2bf4a1deb5e838a0011a4e8b"; + pname = "elynx-markov"; + version = "0.5.1.1"; + sha256 = "6b07aaf5519baa92111259ad1b02b3cee23a703575e64a7ba8c3cdaf237a5d48"; libraryHaskellDepends = [ - attoparsec base bytestring template-haskell + async attoparsec base bytestring containers elynx-seq hmatrix + integration math-functions mwc-random primitive statistics vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/Porges/email-validate-hs"; - description = "Email address validation"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/dschrempf/elynx#readme"; + description = "Simulate molecular sequences along trees"; + license = lib.licenses.gpl3Plus; }) {}; - "emd" = callPackage - ({ mkDerivation, base, binary, containers, data-default-class - , finite-typelits, ghc-typelits-knownnat, ghc-typelits-natnormalise - , stdenv, transformers, typelits-witnesses, vector, vector-sized - }: + "elynx-nexus" = callPackage + ({ mkDerivation, attoparsec, base, bytestring, lib }: mkDerivation { - pname = "emd"; - version = "0.1.4.0"; - sha256 = "fc2775d68f625ae6d3f4bff02b3d62e7ee15f09c123345a0f15a12eb8cf73357"; - libraryHaskellDepends = [ - base binary containers data-default-class finite-typelits - ghc-typelits-knownnat ghc-typelits-natnormalise transformers - typelits-witnesses vector vector-sized - ]; + pname = "elynx-nexus"; + version = "0.5.1.1"; + sha256 = "4f46cdcf4530410dc70532f27792ef59aeb4c6c2ad6717d3aa6a984c6c14bddc"; + libraryHaskellDepends = [ attoparsec base bytestring ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/mstksg/emd#readme"; - description = "Empirical Mode Decomposition and Hilbert-Huang Transform"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/dschrempf/elynx#readme"; + description = "Import and export Nexus files"; + license = lib.licenses.gpl3Plus; }) {}; - "enclosed-exceptions" = callPackage - ({ mkDerivation, base, deepseq, lifted-base, monad-control, stdenv - , transformers, transformers-base + "elynx-seq" = callPackage + ({ mkDerivation, aeson, attoparsec, base, bytestring, containers + , lib, matrices, mwc-random, parallel, primitive, vector + , vector-th-unbox, word8 }: mkDerivation { - pname = "enclosed-exceptions"; - version = "1.0.3"; - sha256 = "af6d93f113ac92b89a32af1fed52f445f492afcc0be93980cbadc5698f94f0b9"; + pname = "elynx-seq"; + version = "0.5.1.1"; + sha256 = "abab6f82325d2d0f6f84874083ab99264a57c8038ee7d20f9cf8a34848445532"; libraryHaskellDepends = [ - base deepseq lifted-base monad-control transformers - transformers-base + aeson attoparsec base bytestring containers matrices mwc-random + parallel primitive vector vector-th-unbox word8 ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/jcristovao/enclosed-exceptions"; - description = "Catching all exceptions from within an enclosed computation"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/dschrempf/elynx#readme"; + description = "Handle molecular sequences"; + license = lib.licenses.gpl3Plus; }) {}; - "entropy" = callPackage - ({ mkDerivation, base, bytestring, Cabal, directory, filepath - , process, stdenv, unix + "elynx-tools" = callPackage + ({ mkDerivation, aeson, attoparsec, base, base16-bytestring + , bytestring, cryptohash-sha256, deepseq, directory, hmatrix, lib + , monad-control, monad-logger, mwc-random, optparse-applicative + , primitive, template-haskell, text, time, transformers + , transformers-base, vector, zlib }: mkDerivation { - pname = "entropy"; - version = "0.4.1.4"; - sha256 = "2e3f6a65c8fde3551a8fb03b0a519b718762fc3278b1a5750f96d399e821eeb9"; + pname = "elynx-tools"; + version = "0.5.1.1"; + sha256 = "a3b8ee323069c427261990242511ea3f2dc30edbc37fff20cefc337b9d4a9c99"; + libraryHaskellDepends = [ + aeson attoparsec base base16-bytestring bytestring + cryptohash-sha256 deepseq directory hmatrix monad-control + monad-logger mwc-random optparse-applicative primitive + template-haskell text time transformers transformers-base vector + zlib + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/dschrempf/elynx#readme"; + description = "Tools for ELynx"; + license = lib.licenses.gpl3Plus; + }) {}; + "elynx-tree" = callPackage + ({ mkDerivation, aeson, attoparsec, base, bytestring, comonad + , containers, deepseq, double-conversion, elynx-nexus, lib + , math-functions, mwc-random, parallel, primitive, statistics + }: + mkDerivation { + pname = "elynx-tree"; + version = "0.5.1.1"; + sha256 = "b3b83f982efa4c60a593bcb47a4b16755545ffbd8c27a59baf5bfa2511915072"; + libraryHaskellDepends = [ + aeson attoparsec base bytestring comonad containers deepseq + double-conversion elynx-nexus math-functions mwc-random parallel + primitive statistics + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/dschrempf/elynx#readme"; + description = "Handle phylogenetic trees"; + license = lib.licenses.gpl3Plus; + }) {}; + "email-validate" = callPackage + ({ mkDerivation, attoparsec, base, bytestring, lib + , template-haskell + }: + mkDerivation { + pname = "email-validate"; + version = "2.3.2.15"; + sha256 = "f0955ce4c550f4493ded8b291d48d9cdb5b508501acee5a7e390a269b4e6c758"; + libraryHaskellDepends = [ + attoparsec base bytestring template-haskell + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/Porges/email-validate-hs"; + description = "Email address validation"; + license = lib.licenses.bsd3; + }) {}; + "emd" = callPackage + ({ mkDerivation, array, base, binary, carray, conduino, containers + , data-default-class, deepseq, fft, finite-typelits, free + , ghc-typelits-knownnat, ghc-typelits-natnormalise, lib + , transformers, typelits-witnesses, vector, vector-sized + }: + mkDerivation { + pname = "emd"; + version = "0.2.0.0"; + sha256 = "3502472517abbc27ca7ed84ca0b03e1a73e064448fb7822fe29cdf5a36c28987"; + libraryHaskellDepends = [ + array base binary carray conduino containers data-default-class + deepseq fft finite-typelits free ghc-typelits-knownnat + ghc-typelits-natnormalise transformers typelits-witnesses vector + vector-sized + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/mstksg/emd#readme"; + description = "Empirical Mode Decomposition and Hilbert-Huang Transform"; + license = lib.licenses.bsd3; + }) {}; + "emojis" = callPackage + ({ mkDerivation, base, containers, lib, text }: + mkDerivation { + pname = "emojis"; + version = "0.1"; + sha256 = "5a03c36ff41989d3309c225bf8dfab81d7733d04c5e6b61e483eccfa929cdfb0"; + libraryHaskellDepends = [ base containers text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jgm/emojis#readme"; + description = "Conversion between emoji characters and their names"; + license = lib.licenses.bsd3; + }) {}; + "enclosed-exceptions" = callPackage + ({ mkDerivation, base, deepseq, lib, lifted-base, monad-control + , transformers, transformers-base + }: + mkDerivation { + pname = "enclosed-exceptions"; + version = "1.0.3"; + sha256 = "af6d93f113ac92b89a32af1fed52f445f492afcc0be93980cbadc5698f94f0b9"; + libraryHaskellDepends = [ + base deepseq lifted-base monad-control transformers + transformers-base + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jcristovao/enclosed-exceptions"; + description = "Catching all exceptions from within an enclosed computation"; + license = lib.licenses.mit; + }) {}; + "entropy" = callPackage + ({ mkDerivation, base, bytestring, Cabal, directory, filepath, lib + , process, unix + }: + mkDerivation { + pname = "entropy"; + version = "0.4.1.6"; + sha256 = "adc759ff756a6d71a450422ba511177632f43a33bf673901fd2334f53ef8bf62"; + revision = "1"; + editedCabalFile = "0jyyyn1cfi1cjisbgym90nw2vx2082ghvwg54ibnjzbii9aj7fj9"; setupHaskellDepends = [ base Cabal directory filepath process ]; libraryHaskellDepends = [ base bytestring unix ]; doHaddock = false; doCheck = false; homepage = "https://github.com/TomMD/entropy"; description = "A platform independent entropy source"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "enum-subset-generate" = callPackage - ({ mkDerivation, base, microlens, stdenv, template-haskell }: + ({ mkDerivation, base, lib, microlens, template-haskell }: mkDerivation { pname = "enum-subset-generate"; version = "0.1.0.0"; @@ -11082,26 +12561,39 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/0xd34df00d/enum-subset-generate#readme"; description = "Generate an ADT being a subset of another ADT, and the corresponding mappings"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "enummapset" = callPackage + ({ mkDerivation, base, containers, deepseq, lib, semigroups }: + mkDerivation { + pname = "enummapset"; + version = "0.6.0.3"; + sha256 = "5eacc9a4ef2e1a48b65d48dc7c8295c42050edb506245e134566a73f0a78ab6b"; + libraryHaskellDepends = [ base containers deepseq semigroups ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/Mikolaj/enummapset"; + description = "IntMap and IntSet with Enum keys/elements"; + license = lib.licenses.bsd3; }) {}; "enumset" = callPackage - ({ mkDerivation, base, data-accessor, semigroups, stdenv + ({ mkDerivation, base, data-accessor, lib, semigroups , storable-record }: mkDerivation { pname = "enumset"; - version = "0.0.4.1"; - sha256 = "5f9d115f7f2b2d4dba290f9d62cd7e9f52f6f6f8235ac5ed9bbf6e982a51d054"; + version = "0.0.5"; + sha256 = "31629409abbdcc40131b59bdb10e6cbbafc69e815f45b2a06b9eb35a0fb53435"; libraryHaskellDepends = [ base data-accessor semigroups storable-record ]; doHaddock = false; doCheck = false; description = "Sets of enumeration values represented by machine words"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "envelope" = callPackage - ({ mkDerivation, aeson, base, http-api-data, mtl, stdenv, text }: + ({ mkDerivation, aeson, base, http-api-data, lib, mtl, text }: mkDerivation { pname = "envelope"; version = "0.2.2.0"; @@ -11111,27 +12603,42 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/cdepillabout/envelope#readme"; description = "Defines generic 'Envelope' type to wrap reponses from a JSON API"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "envparse" = callPackage + ({ mkDerivation, base, containers, lib }: + mkDerivation { + pname = "envparse"; + version = "0.4.1"; + sha256 = "a181daf00f8c1ac74dbc844af323547aff340a4de3653d92848877c6051b2300"; + libraryHaskellDepends = [ base containers ]; + doHaddock = false; + doCheck = false; + homepage = "https://supki.github.io/envparse"; + description = "Parse environment variables"; + license = lib.licenses.bsd3; }) {}; "envy" = callPackage - ({ mkDerivation, base, bytestring, containers, mtl, stdenv, text - , time, transformers + ({ mkDerivation, base, bytestring, containers, lib, mtl, text, time + , transformers }: mkDerivation { pname = "envy"; - version = "1.5.1.0"; - sha256 = "2dcacbb9901603f44e8e933849b532ba7b56ee2d7feff3980f9c7b556c4041e4"; + version = "2.1.0.0"; + sha256 = "c873b552549d47a708406858402ffdf035b812e37242db2c2c1d5c7badb8d268"; + revision = "1"; + editedCabalFile = "1girkgynrr5md1fa892cpg2cyy21hs5g463p5rb0fkhsnvci52xm"; libraryHaskellDepends = [ base bytestring containers mtl text time transformers ]; doHaddock = false; doCheck = false; description = "An environmentally friendly way to deal with environment variables"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "epub-metadata" = callPackage ({ mkDerivation, base, bytestring, containers, directory, filepath - , hxt, mtl, regex-compat-tdfa, stdenv, utf8-string, zip-archive + , hxt, lib, mtl, regex-compat-tdfa, utf8-string, zip-archive }: mkDerivation { pname = "epub-metadata"; @@ -11148,24 +12655,24 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://hub.darcs.net/dino/epub-metadata"; description = "Library for parsing epub document metadata"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "eq" = callPackage - ({ mkDerivation, base, semigroupoids, stdenv }: + ({ mkDerivation, base, lib, semigroupoids }: mkDerivation { pname = "eq"; - version = "4.2"; - sha256 = "4160703a06af1c7518b8ff3244a04013fc7c04a012637dd26be31308e23970e8"; + version = "4.2.1"; + sha256 = "ca7164440922cd945f0ee32c7e174e471e38653ef48098406be9e8d8d6959bad"; libraryHaskellDepends = [ base semigroupoids ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/eq/"; description = "Leibnizian equality"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "equal-files" = callPackage ({ mkDerivation, base, bytestring, explicit-exception, filemanip - , stdenv, transformers, utility-ht + , lib, transformers, utility-ht }: mkDerivation { pname = "equal-files"; @@ -11183,8 +12690,44 @@ inherit (pkgs.xorg) libXfixes;}; description = "Shell command for finding equal files"; license = "GPL"; }) {}; + "equational-reasoning" = callPackage + ({ mkDerivation, base, containers, lib, template-haskell + , th-desugar, void + }: + mkDerivation { + pname = "equational-reasoning"; + version = "0.7.0.0"; + sha256 = "3000e9eb284ed3decc01ec24a56a9a851f2f315169d175856706fa3508f6cf50"; + revision = "2"; + editedCabalFile = "0zlcd62kapcybli65w47mb1kg5fnyzgdnf7kr8y8qgslg0lidzpp"; + libraryHaskellDepends = [ + base containers template-haskell th-desugar void + ]; + doHaddock = false; + doCheck = false; + description = "Proof assistant for Haskell using DataKinds & PolyKinds"; + license = lib.licenses.bsd3; + }) {}; + "equivalence" = callPackage + ({ mkDerivation, base, containers, fail, lib, mtl, STMonadTrans + , transformers, transformers-compat + }: + mkDerivation { + pname = "equivalence"; + version = "0.3.5"; + sha256 = "17ab5a2a6759f6855de40acdd9dde0d0f89e9d9219a4bc8e52623816da97f698"; + libraryHaskellDepends = [ + base containers fail mtl STMonadTrans transformers + transformers-compat + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/pa-ba/equivalence"; + description = "Maintaining an equivalence relation implemented as union-find using STT"; + license = lib.licenses.bsd3; + }) {}; "erf" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "erf"; version = "2.0.0.0"; @@ -11193,23 +12736,36 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "The error function, erf, and related functions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "error-util" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + "error-or" = callPackage + ({ mkDerivation, base, containers, lib, text }: mkDerivation { - pname = "error-util"; - version = "0.0.1.2"; - sha256 = "df1916a2de007697b7b1a9f83eacab4588d8dc472fd0f21395dce83b085e4e06"; - libraryHaskellDepends = [ base transformers ]; + pname = "error-or"; + version = "0.1.2.0"; + sha256 = "b562d9f8641502ce9f824e9a3a0f57085295c5be83ef834a3c34d7f3e136c067"; + libraryHaskellDepends = [ base containers text ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/pmlodawski/error-util"; - description = "Set of utils and operators for error handling"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/luntain/error-or-bundle/blob/master/error-or#readme"; + description = "Composable, hierarchical errors"; + license = lib.licenses.bsd3; + }) {}; + "error-or-utils" = callPackage + ({ mkDerivation, base, containers, error-or, lib, text }: + mkDerivation { + pname = "error-or-utils"; + version = "0.1.1"; + sha256 = "9fd76db907fb9bc74ec1a2ef3ba99a9e5fca656c5b2119cd1adadac99381c592"; + libraryHaskellDepends = [ base containers error-or text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/luntain/error-or-bundle/blob/master/error-or-utils#readme"; + description = "Utilities using ErrorOr datatype"; + license = lib.licenses.bsd3; }) {}; "errors" = callPackage - ({ mkDerivation, base, exceptions, safe, stdenv, text, transformers + ({ mkDerivation, base, exceptions, lib, safe, text, transformers , transformers-compat }: mkDerivation { @@ -11222,11 +12778,11 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Simplified error-handling"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "errors-ext" = callPackage - ({ mkDerivation, base, errors, exceptions, monad-control, mtl - , stdenv, transformers + ({ mkDerivation, base, errors, exceptions, lib, monad-control, mtl + , transformers }: mkDerivation { pname = "errors-ext"; @@ -11239,37 +12795,127 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/A1-Triard/errors-ext#readme"; description = "`bracket`-like functions for `ExceptT` over `IO` monad"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; }) {}; "ersatz" = callPackage - ({ mkDerivation, array, attoparsec, base, bytestring, Cabal - , cabal-doctest, containers, data-default, lens, mtl, parsec - , process, semigroups, stdenv, temporary, transformers - , unordered-containers + ({ mkDerivation, array, attoparsec, base, bytestring, containers + , data-default, fail, lens, lib, mtl, parsec, process, semigroups + , temporary, transformers, unordered-containers }: mkDerivation { pname = "ersatz"; - version = "0.4.4"; - sha256 = "42dca507046c32e00459bf6167d02bb508b72bb47669470a0eb3fba20b73a019"; + version = "0.4.9"; + sha256 = "cd557b1507f53a50a02bc8c8f51892b9f9584caab46808e50587bbb9fff9d8de"; isLibrary = true; isExecutable = true; enableSeparateDataOutput = true; - setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ array attoparsec base bytestring containers data-default lens mtl process semigroups temporary transformers unordered-containers ]; executableHaskellDepends = [ - array base containers lens mtl parsec semigroups + array base containers fail lens mtl parsec semigroups ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/ersatz"; description = "A monad for expressing SAT or QSAT problems using observable sharing"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "esqueleto" = callPackage + ({ mkDerivation, aeson, attoparsec, base, blaze-html, bytestring + , conduit, containers, lib, monad-logger, persistent, resourcet + , tagged, text, time, transformers, unliftio, unordered-containers + }: + mkDerivation { + pname = "esqueleto"; + version = "3.5.2.1"; + sha256 = "1a28f528c41ddea8bb193721e9b5388110ed560c0a0f14df641ff0b258daa3c3"; + libraryHaskellDepends = [ + aeson attoparsec base blaze-html bytestring conduit containers + monad-logger persistent resourcet tagged text time transformers + unliftio unordered-containers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/bitemyapp/esqueleto"; + description = "Type-safe EDSL for SQL queries on persistent backends"; + license = lib.licenses.bsd3; + }) {}; + "essence-of-live-coding" = callPackage + ({ mkDerivation, base, containers, foreign-store, lib, syb, time + , transformers, vector-sized + }: + mkDerivation { + pname = "essence-of-live-coding"; + version = "0.2.5"; + sha256 = "f9effda00f725ed57b40346abd1b17b12e689e973a4e190d6f1b75976032ebbd"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base containers foreign-store syb time transformers vector-sized + ]; + executableHaskellDepends = [ base transformers ]; + doHaddock = false; + doCheck = false; + homepage = "https://www.manuelbaerenz.de/#computerscience"; + description = "General purpose live coding framework"; + license = lib.licenses.bsd3; + }) {}; + "essence-of-live-coding-gloss" = callPackage + ({ mkDerivation, base, essence-of-live-coding, foreign-store, gloss + , lib, syb, transformers + }: + mkDerivation { + pname = "essence-of-live-coding-gloss"; + version = "0.2.5"; + sha256 = "fbea4bf5925da2c978d5536bb1e72ba45758fec2c2f6d03e09a6080363a841f5"; + libraryHaskellDepends = [ + base essence-of-live-coding foreign-store gloss syb transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://www.manuelbaerenz.de/#computerscience"; + description = "General purpose live coding framework - Gloss backend"; + license = lib.licenses.bsd3; + }) {}; + "essence-of-live-coding-pulse" = callPackage + ({ mkDerivation, base, essence-of-live-coding, foreign-store, lib + , pulse-simple, transformers + }: + mkDerivation { + pname = "essence-of-live-coding-pulse"; + version = "0.2.5"; + sha256 = "18c0875da66386fe5223d86aab49ff417760333633a8222730884bc3f4974f54"; + libraryHaskellDepends = [ + base essence-of-live-coding foreign-store pulse-simple transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://www.manuelbaerenz.de/#computerscience"; + description = "General purpose live coding framework - pulse backend"; + license = lib.licenses.bsd3; + }) {}; + "essence-of-live-coding-quickcheck" = callPackage + ({ mkDerivation, base, boltzmann-samplers, essence-of-live-coding + , lib, QuickCheck, syb, transformers + }: + mkDerivation { + pname = "essence-of-live-coding-quickcheck"; + version = "0.2.5"; + sha256 = "d5087477b0321d9bc656dfe610d8128f6c751f4b17ea246f4179ed30bd341c1f"; + libraryHaskellDepends = [ + base boltzmann-samplers essence-of-live-coding QuickCheck syb + transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://www.manuelbaerenz.de/#computerscience"; + description = "General purpose live coding framework - QuickCheck integration"; + license = lib.licenses.bsd3; }) {}; "etc" = callPackage - ({ mkDerivation, aeson, base, rio, stdenv, template-haskell, text + ({ mkDerivation, aeson, base, lib, rio, template-haskell, text , typed-process, unliftio }: mkDerivation { @@ -11284,10 +12930,27 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/roman/Haskell-etc"; description = "Declarative configuration spec for Haskell projects"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "eve" = callPackage + ({ mkDerivation, base, containers, data-default, free, lens, lib + , mtl + }: + mkDerivation { + pname = "eve"; + version = "0.1.9.0"; + sha256 = "c9236a105e311b2ad9106df919155025273a72b54ef8cb8f039c6bfa96c76219"; + libraryHaskellDepends = [ + base containers data-default free lens mtl + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ChrisPenner/eve#readme"; + description = "An extensible event framework"; + license = lib.licenses.bsd3; }) {}; "event-list" = callPackage - ({ mkDerivation, base, non-negative, QuickCheck, semigroups, stdenv + ({ mkDerivation, base, lib, non-negative, QuickCheck, semigroups , transformers, utility-ht }: mkDerivation { @@ -11305,7 +12968,7 @@ inherit (pkgs.xorg) libXfixes;}; }) {}; "eventful-core" = callPackage ({ mkDerivation, aeson, base, containers, contravariant - , http-api-data, path-pieces, stdenv, sum-type-boilerplate + , http-api-data, lib, path-pieces, sum-type-boilerplate , template-haskell, text, transformers, uuid }: mkDerivation { @@ -11320,64 +12983,11 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/jdreaver/eventful#readme"; description = "Core module for eventful"; - license = stdenv.lib.licenses.mit; - }) {}; - "eventful-memory" = callPackage - ({ mkDerivation, base, containers, eventful-core, mtl, safe, stdenv - , stm - }: - mkDerivation { - pname = "eventful-memory"; - version = "0.2.0"; - sha256 = "6a7c3e0a12e3c4e572927929020ad92075933e5d3c66ea61ff615a3ac217adb9"; - libraryHaskellDepends = [ - base containers eventful-core mtl safe stm - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/jdreaver/eventful#readme"; - description = "In-memory implementations for eventful"; - license = stdenv.lib.licenses.mit; - }) {}; - "eventful-sql-common" = callPackage - ({ mkDerivation, aeson, base, bytestring, eventful-core, mtl - , persistent, persistent-template, stdenv, text, uuid - }: - mkDerivation { - pname = "eventful-sql-common"; - version = "0.2.0"; - sha256 = "a46ea18cbbb5bd04b3a6846273e8161b7e4208660d0abf5a401192b07636aebc"; - libraryHaskellDepends = [ - aeson base bytestring eventful-core mtl persistent - persistent-template text uuid - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/jdreaver/eventful#readme"; - description = "Common library for SQL event stores"; - license = stdenv.lib.licenses.mit; - }) {}; - "eventful-sqlite" = callPackage - ({ mkDerivation, aeson, base, bytestring, eventful-core - , eventful-sql-common, mtl, persistent, stdenv, text, uuid - }: - mkDerivation { - pname = "eventful-sqlite"; - version = "0.2.0"; - sha256 = "c0bbea0ebd1f0a4891a74b190f499caf85ac026f49b9401fc76f181b0041dfef"; - libraryHaskellDepends = [ - aeson base bytestring eventful-core eventful-sql-common mtl - persistent text uuid - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/jdreaver/eventful#readme"; - description = "SQLite implementations for eventful"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "eventful-test-helpers" = callPackage ({ mkDerivation, aeson, aeson-casing, base, eventful-core, extra - , hspec, monad-logger, stdenv, text + , hspec, lib, monad-logger, text }: mkDerivation { pname = "eventful-test-helpers"; @@ -11390,38 +13000,38 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/jdreaver/eventful#readme"; description = "Common module used for eventful tests"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "eventstore" = callPackage ({ mkDerivation, aeson, array, base, bifunctors, bytestring, cereal - , clock, connection, containers, dns, dotnet-timespan, ekg-core - , exceptions, fast-logger, hashable, http-client, interpolate - , lifted-async, lifted-base, machines, monad-control, monad-logger + , clock, connection, containers, dns, dotnet-timespan, exceptions + , fast-logger, hashable, http-client, interpolate, lib + , lifted-async, lifted-base, monad-control, monad-logger , mono-traversable, mtl, protobuf, random, safe, safe-exceptions - , semigroups, stdenv, stm, stm-chans, streaming, text, time - , transformers-base, unordered-containers, uuid + , semigroups, stm, stm-chans, streaming, text, time + , transformers-base, unordered-containers, uuid, vector }: mkDerivation { pname = "eventstore"; - version = "1.2.1"; - sha256 = "c813b213db61addee309aa04d360c8bc49108f1d0a2197557eeee9319728cafb"; + version = "1.4.1"; + sha256 = "b2a286d3711d4137ba494c07b93f4e9ed8d3e14a6e7bcb1dad2803954f5414b5"; libraryHaskellDepends = [ aeson array base bifunctors bytestring cereal clock connection - containers dns dotnet-timespan ekg-core exceptions fast-logger - hashable http-client interpolate lifted-async lifted-base machines - monad-control monad-logger mono-traversable mtl protobuf random - safe safe-exceptions semigroups stm stm-chans streaming text time - transformers-base unordered-containers uuid + containers dns dotnet-timespan exceptions fast-logger hashable + http-client interpolate lifted-async lifted-base monad-control + monad-logger mono-traversable mtl protobuf random safe + safe-exceptions semigroups stm stm-chans streaming text time + transformers-base unordered-containers uuid vector ]; doHaddock = false; doCheck = false; - homepage = "https://gitlab.com/YoEight/eventstore-hs"; + homepage = "https://github.com/YoEight/eventstore"; description = "EventStore TCP Client"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; platforms = [ "x86_64-darwin" "x86_64-linux" ]; }) {}; "every" = callPackage - ({ mkDerivation, async, base, stdenv, stm }: + ({ mkDerivation, async, base, lib, stm }: mkDerivation { pname = "every"; version = "0.0.1"; @@ -11431,36 +13041,51 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/athanclark/every#readme"; description = "Run a process every so often"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "exact-combinatorics" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "exact-combinatorics"; - version = "0.2.0.8"; - sha256 = "32a822b109ab6e9f62fe23d76bd5af593c20ba0e589005d3985ccda00dd4475e"; + version = "0.2.0.9"; + sha256 = "725785ac22c252b0753aefffd8eb591f8a4184cec08a5d50bca1d57c5345c9ab"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "http://code.haskell.org/~wren/"; + homepage = "https://wrengr.org/"; description = "Efficient exact computation of combinatoric functions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "exact-pi" = callPackage - ({ mkDerivation, base, numtype-dk, stdenv }: + ({ mkDerivation, base, lib, numtype-dk }: mkDerivation { pname = "exact-pi"; version = "0.5.0.1"; sha256 = "5d8156ec8b044a36c2ac789b85bf65116be24304868fff472d033977ebcc1860"; + revision = "1"; + editedCabalFile = "1l55d7x61i2d5rlh7sh2nhn0af9cyp92gzdmqqnnjzg55d347qsm"; libraryHaskellDepends = [ base numtype-dk ]; doHaddock = false; doCheck = false; homepage = "https://github.com/dmcclean/exact-pi/"; description = "Exact rational multiples of pi (and integer powers of pi)"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "exception-hierarchy" = callPackage + ({ mkDerivation, base, lib, template-haskell }: + mkDerivation { + pname = "exception-hierarchy"; + version = "0.1.0.4"; + sha256 = "dd560fd889b1874cdca2f8c2fa76e452aed7ec4d10d784bfda8cd2f26c3df042"; + libraryHaskellDepends = [ base template-haskell ]; + doHaddock = false; + doCheck = false; + homepage = "yet"; + description = "Exception type hierarchy with TemplateHaskell"; + license = lib.licenses.bsd3; }) {}; "exception-mtl" = callPackage - ({ mkDerivation, base, exception-transformers, mtl, stdenv + ({ mkDerivation, base, exception-transformers, lib, mtl , transformers }: mkDerivation { @@ -11473,85 +13098,54 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Exception monad transformer instances for mtl classes"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "exception-transformers" = callPackage - ({ mkDerivation, base, stdenv, stm, transformers - , transformers-compat - }: + ({ mkDerivation, base, lib, transformers, transformers-compat }: mkDerivation { pname = "exception-transformers"; - version = "0.4.0.7"; - sha256 = "925b61eb3d19148a521e79f8b4c8ac097f6e0dea6a09cc2f533279f3abf1f2ef"; - revision = "1"; - editedCabalFile = "0sahi93f75acvmqagkjc1lcwx31crja6z9hyww9abj85x45pqa6f"; - libraryHaskellDepends = [ - base stm transformers transformers-compat - ]; + version = "0.4.0.9"; + sha256 = "25b50743900747372ac421a3f4fe025eb3f90c297fe054204dc5f1cf60457f0c"; + libraryHaskellDepends = [ base transformers transformers-compat ]; doHaddock = false; doCheck = false; description = "Type classes and monads for unchecked extensible exceptions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "exceptional" = callPackage - ({ mkDerivation, base, exceptions, stdenv }: + "exception-via" = callPackage + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { - pname = "exceptional"; - version = "0.3.0.0"; - sha256 = "da866ed28ea14d245cc065271f4ddd6da0a91b83e8d83daddcd1ef0623e99f06"; - libraryHaskellDepends = [ base exceptions ]; + pname = "exception-via"; + version = "0.1.0.0"; + sha256 = "d518adb5491466ef463060ea9cc6e6c6880ab0552cb1848361610f2e0f3ace10"; + libraryHaskellDepends = [ base template-haskell ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/"; - description = "Essentially the Maybe type with error messages"; - license = stdenv.lib.licenses.bsd2; + homepage = "https://github.com/parsonsmatt/exception-via#readme"; + description = "DerivingVia for your hierarchical exceptions"; + license = lib.licenses.bsd3; }) {}; "exceptions" = callPackage - ({ mkDerivation, base, mtl, stdenv, stm, template-haskell - , transformers, transformers-compat + ({ mkDerivation, base, lib, mtl, stm, template-haskell + , transformers }: mkDerivation { pname = "exceptions"; - version = "0.10.0"; - sha256 = "1edd912e5ea5cbda37941b06738597d35214dc247d332b1bfffc82adadfa49d7"; + version = "0.10.4"; + sha256 = "4d0bfb4355cffcd67d300811df9d5fe44ea3594ed63750795bfc1f797abd84cf"; revision = "2"; - editedCabalFile = "0aiihbjfrlmxzw9q8idvr6mihhs7kbx9s3w1vj8x3pz27p0ncq7g"; + editedCabalFile = "1154g0dqil2xf4wc1v6gndzhnbf5saf2dzf77c6lcjxssx360m6j"; libraryHaskellDepends = [ - base mtl stm template-haskell transformers transformers-compat + base mtl stm template-haskell transformers ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/exceptions/"; description = "Extensible optionally-pure exceptions"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "executable-hash" = callPackage - ({ mkDerivation, base, bytestring, Cabal, cryptohash, directory - , executable-path, file-embed, filepath, stdenv, template-haskell - }: - mkDerivation { - pname = "executable-hash"; - version = "0.2.0.4"; - sha256 = "34eaf5662d90d3b7841f66b322ac5bc54900b0e3cb06792852b08b3c05a42ba4"; - isLibrary = true; - isExecutable = true; - setupHaskellDepends = [ - base bytestring Cabal cryptohash directory file-embed filepath - template-haskell - ]; - libraryHaskellDepends = [ - base bytestring cryptohash directory executable-path file-embed - template-haskell - ]; - executableHaskellDepends = [ base ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/fpco/executable-hash"; - description = "Provides the SHA1 hash of the program executable"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.bsd3; }) {}; "executable-path" = callPackage - ({ mkDerivation, base, directory, filepath, stdenv, unix }: + ({ mkDerivation, base, directory, filepath, lib, unix }: mkDerivation { pname = "executable-path"; version = "0.0.3.1"; @@ -11561,10 +13155,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://code.haskell.org/~bkomuves/"; description = "Finding out the full path of the executable"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "exit-codes" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "exit-codes"; version = "1.0.0"; @@ -11574,10 +13168,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/JustusAdam/exit-codes"; description = "Exit codes as defined by BSD"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "exomizer" = callPackage - ({ mkDerivation, base, bytestring, c2hs, stdenv }: + ({ mkDerivation, base, bytestring, c2hs, lib }: mkDerivation { pname = "exomizer"; version = "1.0.0"; @@ -11590,18 +13184,16 @@ inherit (pkgs.xorg) libXfixes;}; homepage = "https://github.com/alexkazik/exomizer#readme"; description = "Compression and decompression in the exomizer format"; license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; + hydraPlatforms = lib.platforms.none; }) {}; "exp-pairs" = callPackage - ({ mkDerivation, base, containers, deepseq, ghc-prim, prettyprinter - , stdenv + ({ mkDerivation, base, containers, deepseq, ghc-prim, lib + , prettyprinter }: mkDerivation { pname = "exp-pairs"; - version = "0.2.0.0"; - sha256 = "57471bfd498570247c03863ec4532ff06c20198efe7a7fe4484478d7139ac967"; - revision = "1"; - editedCabalFile = "1fkllbgsygzm1lw3g3a9l8fg8ap74bx0x7ja8yx3lbrjjsaqh8pa"; + version = "0.2.1.0"; + sha256 = "d7b66f17ed5c652a7f2f1ff52cd845dbb022b9bebb5cf8e9df0c23b0c8784307"; libraryHaskellDepends = [ base containers deepseq ghc-prim prettyprinter ]; @@ -11609,10 +13201,35 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/Bodigrim/exp-pairs"; description = "Linear programming over exponent pairs"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; + }) {}; + "experimenter" = callPackage + ({ mkDerivation, aeson, base, bytestring, cereal, cereal-vector + , conduit, containers, deepseq, directory, esqueleto, filepath + , HaTeX, hostname, lens, lib, matrix, monad-logger, mtl, mwc-random + , parallel, persistent, persistent-postgresql, persistent-template + , process, resource-pool, resourcet, stm, text, time, transformers + , unix, unliftio-core, vector + }: + mkDerivation { + pname = "experimenter"; + version = "0.1.0.12"; + sha256 = "a61518b44aedf1d169437bf70ee30d223c64308025c8375bac49c147283f5569"; + libraryHaskellDepends = [ + aeson base bytestring cereal cereal-vector conduit containers + deepseq directory esqueleto filepath HaTeX hostname lens matrix + monad-logger mtl mwc-random parallel persistent + persistent-postgresql persistent-template process resource-pool + resourcet stm text time transformers unix unliftio-core vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/schnecki/experimenter#readme"; + description = "Perform scientific experiments stored in a DB, and generate reports"; + license = lib.licenses.bsd3; }) {}; "expiring-cache-map" = callPackage - ({ mkDerivation, base, containers, hashable, stdenv + ({ mkDerivation, base, containers, hashable, lib , unordered-containers }: mkDerivation { @@ -11626,14 +13243,14 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/elblake/expiring-cache-map"; description = "General purpose simple caching"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "explicit-exception" = callPackage - ({ mkDerivation, base, deepseq, semigroups, stdenv, transformers }: + ({ mkDerivation, base, deepseq, lib, semigroups, transformers }: mkDerivation { pname = "explicit-exception"; - version = "0.1.9.2"; - sha256 = "60f6029777f80ec958e28cef19a15723242987a01f09f6bfef252f24207649f6"; + version = "0.1.10"; + sha256 = "00d467d6f75751db37adfbc5ab238db3d92f16ca642f872f912aed8e7f00f8bc"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base deepseq semigroups transformers ]; @@ -11641,28 +13258,69 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Exception"; description = "Exceptions which are explicit in the type signature"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "extensible-exceptions" = callPackage - ({ mkDerivation, base, stdenv }: + "express" = callPackage + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { - pname = "extensible-exceptions"; - version = "0.1.1.4"; - sha256 = "6ce5e8801760385a408dab71b53550f87629e661b260bdc2cd41c6a439b6e388"; - libraryHaskellDepends = [ base ]; + pname = "express"; + version = "0.1.16"; + sha256 = "244ec4e77084ead5602acd3c9d263ce07140910e0effedc13ad1fadfc68e4111"; + libraryHaskellDepends = [ base template-haskell ]; doHaddock = false; doCheck = false; - description = "Extensible exceptions"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/rudymatela/express#readme"; + description = "Dynamically-typed expressions involving function application and variables"; + license = lib.licenses.bsd3; }) {}; - "extra" = callPackage - ({ mkDerivation, base, clock, directory, filepath, process, stdenv - , time, unix - }: + "extended-reals" = callPackage + ({ mkDerivation, base, deepseq, hashable, lib }: mkDerivation { - pname = "extra"; - version = "1.6.14"; - sha256 = "a60641530d96653ecc365aa042f4061892154995915d91f432ea5a2e3aaf129c"; + pname = "extended-reals"; + version = "0.2.4.0"; + sha256 = "0c2c664abe60a105207b1678ab699c1b5cf2708976bc6b2b8c3a4e54e93faea5"; + libraryHaskellDepends = [ base deepseq hashable ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/msakai/extended-reals/"; + description = "Extension of real numbers with positive/negative infinities"; + license = lib.licenses.bsd3; + }) {}; + "extensible-effects" = callPackage + ({ mkDerivation, base, lib, monad-control, transformers-base }: + mkDerivation { + pname = "extensible-effects"; + version = "5.0.0.1"; + sha256 = "c3b3165893d3738c5ec7ffd0d8c46a7af855b7d3087e159d6da516e78880c039"; + revision = "1"; + editedCabalFile = "1ihcxj58a3ca80zfyxgbzjzgps9izy96vnj7h4sk9wwb9khbxl1f"; + libraryHaskellDepends = [ base monad-control transformers-base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/suhailshergill/extensible-effects"; + description = "An Alternative to Monad Transformers"; + license = lib.licenses.mit; + }) {}; + "extensible-exceptions" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "extensible-exceptions"; + version = "0.1.1.4"; + sha256 = "6ce5e8801760385a408dab71b53550f87629e661b260bdc2cd41c6a439b6e388"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + description = "Extensible exceptions"; + license = lib.licenses.bsd3; + }) {}; + "extra" = callPackage + ({ mkDerivation, base, clock, directory, filepath, lib, process + , time, unix + }: + mkDerivation { + pname = "extra"; + version = "1.7.9"; + sha256 = "f66e26a63b216f0ca33665a75c08eada0a96af192ace83a18d87839d79afdf9d"; libraryHaskellDepends = [ base clock directory filepath process time unix ]; @@ -11670,10 +13328,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/ndmitchell/extra#readme"; description = "Extra functions I use"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "extractable-singleton" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "extractable-singleton"; version = "0.0.1"; @@ -11683,27 +13341,27 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/athanclark/extractable-singleton#readme"; description = "A functor, where the \"stored\" value is isomorphic to Identity"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "extrapolate" = callPackage - ({ mkDerivation, base, leancheck, speculate, stdenv + ({ mkDerivation, base, express, leancheck, lib, speculate , template-haskell }: mkDerivation { pname = "extrapolate"; - version = "0.3.3"; - sha256 = "22fff22a2c5b36a6545b27495c0eba63e8e3f72baccb3f9d687967c6532381d5"; + version = "0.4.6"; + sha256 = "04f706ae73fd97a2e0ec0077dff3012793d2bb67b2e1b2a096256575ce58a210"; libraryHaskellDepends = [ - base leancheck speculate template-haskell + base express leancheck speculate template-haskell ]; doHaddock = false; doCheck = false; homepage = "https://github.com/rudymatela/extrapolate#readme"; description = "generalize counter-examples of test properties"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "fail" = callPackage - ({ mkDerivation, stdenv }: + ({ mkDerivation, lib }: mkDerivation { pname = "fail"; version = "4.9.0.0"; @@ -11712,42 +13370,125 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://prime.haskell.org/wiki/Libraries/Proposals/MonadFail"; description = "Forward-compatible MonadFail class"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "farmhash" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + "failable" = callPackage + ({ mkDerivation, base, lib, mtl, transformers }: mkDerivation { - pname = "farmhash"; - version = "0.1.0.5"; - sha256 = "0e685a5445f7bce88682d209bccb47d03f06065a627475df44a8e2af8bc20fa1"; - libraryHaskellDepends = [ base bytestring ]; + pname = "failable"; + version = "1.2.4.0"; + sha256 = "8fd367b3408e6f2be38a4a9c9136c76ace2acea1910c65d6bf8e77c5bdccceed"; + libraryHaskellDepends = [ base mtl transformers ]; + doHaddock = false; + doCheck = false; + description = "A 'Failable' error monad class to unify failure across monads that can fail"; + license = lib.licenses.bsd3; + }) {}; + "fakedata" = callPackage + ({ mkDerivation, attoparsec, base, bytestring, containers + , directory, exceptions, fakedata-parser, filepath, hashable, lib + , random, string-random, template-haskell, text, time + , unordered-containers, vector, yaml + }: + mkDerivation { + pname = "fakedata"; + version = "0.8.0"; + sha256 = "e522e3662289c652b545c11adce04f33b532c8dfae7df3d7b8d9b689cff7c946"; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + attoparsec base bytestring containers directory exceptions + fakedata-parser filepath hashable random string-random + template-haskell text time unordered-containers vector yaml + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/psibi/fakedata#readme"; + description = "Library for producing fake data"; + license = lib.licenses.bsd3; + }) {}; + "fakedata-parser" = callPackage + ({ mkDerivation, attoparsec, base, lib, text }: + mkDerivation { + pname = "fakedata-parser"; + version = "0.1.0.0"; + sha256 = "975137a25965e6daaa245294d6a7edf3f3428d7a71641bf506e79e9352aec465"; + libraryHaskellDepends = [ attoparsec base text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/psibi/fakedata-parser#readme"; + license = lib.licenses.bsd3; + }) {}; + "fakefs" = callPackage + ({ mkDerivation, base, containers, exceptions, lib, mtl }: + mkDerivation { + pname = "fakefs"; + version = "0.3.0.2"; + sha256 = "0b899496184a505cbf0eee6e8d38747c7451ccec5ea7fd1b0f3e1f0930540f9a"; + libraryHaskellDepends = [ base containers exceptions mtl ]; + doHaddock = false; + doCheck = false; + homepage = "https://gitlab.com/igrep/haskell-fakefs#readme"; + description = "Extensible fake file system for testing"; + license = lib.licenses.asl20; + }) {}; + "fakepull" = callPackage + ({ mkDerivation, base, exceptions, lib, mtl }: + mkDerivation { + pname = "fakepull"; + version = "0.3.0.2"; + sha256 = "14de772b868836c3e36e3f3a71e6057b5cb66e3afa8f66de2258e351f9c0b7b6"; + libraryHaskellDepends = [ base exceptions mtl ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/igrep/haskell-fakepull#readme"; + description = "Monad to pull from fake stream-like objects"; + license = lib.licenses.asl20; + }) {}; + "faktory" = callPackage + ({ mkDerivation, aeson, aeson-casing, base, bytestring, connection + , cryptonite, errors, lib, megaparsec, memory, mtl, network, random + , safe-exceptions, scanner, semigroups, text, time, unix + , unordered-containers + }: + mkDerivation { + pname = "faktory"; + version = "1.0.3.1"; + sha256 = "4f375eb6e26db321af67c79b20db3dbb43a2ba6ae7ea35ac0ae05037bae6c929"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson aeson-casing base bytestring connection cryptonite errors + megaparsec memory mtl network random safe-exceptions scanner + semigroups text time unix unordered-containers + ]; + executableHaskellDepends = [ aeson base safe-exceptions ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/abhinav/farmhash"; - description = "Fast hash functions"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/frontrowed/faktory_worker_haskell#readme"; + description = "Faktory Worker for Haskell"; + license = lib.licenses.mit; }) {}; "fast-digits" = callPackage - ({ mkDerivation, base, integer-gmp, stdenv }: + ({ mkDerivation, base, integer-gmp, lib }: mkDerivation { pname = "fast-digits"; - version = "0.2.1.0"; - sha256 = "ec84576e479202de8257c7c499b66e91bcf18444f7683475d74b575e166dd83b"; + version = "0.3.0.0"; + sha256 = "da29dd74592a48dcbb7979d7ffb8eda5e13a3f14d5a99873e0d5865d279595ee"; libraryHaskellDepends = [ base integer-gmp ]; doHaddock = false; doCheck = false; homepage = "https://github.com/Bodigrim/fast-digits"; - description = "The fast library for integer-to-digits conversion"; - license = stdenv.lib.licenses.gpl3; + description = "Integer-to-digits conversion"; + license = lib.licenses.gpl3Only; }) {}; "fast-logger" = callPackage ({ mkDerivation, array, auto-update, base, bytestring, directory - , easy-file, filepath, stdenv, text, unix-compat, unix-time + , easy-file, filepath, lib, text, unix-compat, unix-time }: mkDerivation { pname = "fast-logger"; - version = "2.4.13"; - sha256 = "4bd4ef406f661e603320a34c353c29c5160644e3c4a446dd47efb279088a32b2"; + version = "3.0.5"; + sha256 = "a693bfda13ea7220dc4d516134880bc0ba5652639f0d5148222f52640d5476d5"; libraryHaskellDepends = [ array auto-update base bytestring directory easy-file filepath text unix-compat unix-time @@ -11756,10 +13497,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/kazu-yamamoto/logger"; description = "A fast logging system"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "fast-math" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "fast-math"; version = "1.0.2"; @@ -11768,51 +13509,50 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Non IEEE-754 compliant compile-time floating-point optimisations"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "fb" = callPackage - ({ mkDerivation, aeson, attoparsec, base, base16-bytestring - , base64-bytestring, bytestring, cereal, conduit, conduit-extra - , crypto-api, cryptohash, cryptohash-cryptoapi, data-default - , http-client, http-conduit, http-types, monad-logger, old-locale - , resourcet, stdenv, text, time, transformers, transformers-base - , unliftio, unliftio-core, unordered-containers + ({ mkDerivation, aeson, attoparsec, base, bytestring, conduit + , conduit-extra, cryptonite, data-default, http-client + , http-conduit, http-types, lib, memory, monad-logger, resourcet + , text, time, transformers, transformers-base, unliftio + , unliftio-core, unordered-containers }: mkDerivation { pname = "fb"; - version = "1.2.1"; - sha256 = "a9d670a763e2ccf3e457e6b310769d5d8977cb1c00a78c8825861999da055d15"; + version = "2.1.1"; + sha256 = "49a726c7319fe9f93d15d39da4f711894a401e76ce47cfc5757aaab0f3645948"; libraryHaskellDepends = [ - aeson attoparsec base base16-bytestring base64-bytestring - bytestring cereal conduit conduit-extra crypto-api cryptohash - cryptohash-cryptoapi data-default http-client http-conduit - http-types monad-logger old-locale resourcet text time transformers - transformers-base unliftio unliftio-core unordered-containers + aeson attoparsec base bytestring conduit conduit-extra cryptonite + data-default http-client http-conduit http-types memory + monad-logger resourcet text time transformers transformers-base + unliftio unliftio-core unordered-containers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/psibi/fb"; description = "Bindings to Facebook's API"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "fclabels" = callPackage - ({ mkDerivation, base, mtl, stdenv, template-haskell, transformers + ({ mkDerivation, base, base-orphans, lib, mtl, template-haskell + , transformers }: mkDerivation { pname = "fclabels"; - version = "2.0.3.3"; - sha256 = "9a9472a46dc23b5acc0545d345ecd708f7b003f72ab212e2d12125b902b9c2e0"; - revision = "3"; - editedCabalFile = "1wncfnvh4mv87gh0ddhiqf839d63rqs1qzi3y386y6r8hfnvra0l"; - libraryHaskellDepends = [ base mtl template-haskell transformers ]; + version = "2.0.5.1"; + sha256 = "939c4075fb2aeb0ea69d6d8e252dd2b8c4743cc4fcc4acaed54e2d516f518c3c"; + libraryHaskellDepends = [ + base base-orphans mtl template-haskell transformers + ]; doHaddock = false; doCheck = false; homepage = "https://github.com/sebastiaanvisser/fclabels"; description = "First class accessor labels implemented as lenses"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "feature-flags" = callPackage - ({ mkDerivation, base, stdenv, text }: + ({ mkDerivation, base, lib, text }: mkDerivation { pname = "feature-flags"; version = "0.1.0.1"; @@ -11822,49 +13562,53 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/iand675/feature-flags"; description = "A simple library for dynamically enabling and disabling functionality"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "fedora-dists" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "fedora-dists"; - version = "1.0.0.2"; - sha256 = "d4d2436703278d09df0f310b7e7877fc42d414379513d6e272bc53f7c59e8749"; + version = "1.1.2"; + sha256 = "bcd8a8b3f51261281ac8269eaa5253a6a0cec35d5b7d0694ad1b90c422afd643"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/juhp/fedora-dists"; description = "Library for Fedora distribution versions"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; }) {}; "fedora-haskell-tools" = callPackage - ({ mkDerivation, base, csv, directory, filepath, HTTP, process - , stdenv, time, unix + ({ mkDerivation, base, csv, directory, fedora-dists, filepath, HTTP + , lib, optparse-applicative, process, simple-cmd, simple-cmd-args + , split, time, unix }: mkDerivation { pname = "fedora-haskell-tools"; - version = "0.6"; - sha256 = "a47af60fe0fba6934cea3d10414e96329419311ba202aea7051f373d3d34d91b"; + version = "0.9"; + sha256 = "b6468349b91cfbc6280b6e4b1b9c7df6ec63486fe77181466f8f2b6902a30fff"; isLibrary = false; isExecutable = true; executableHaskellDepends = [ - base csv directory filepath HTTP process time unix + base csv directory fedora-dists filepath HTTP optparse-applicative + process simple-cmd simple-cmd-args split time unix ]; doHaddock = false; doCheck = false; homepage = "https://github.com/fedora-haskell/fedora-haskell-tools"; description = "Building and maintenance tools for Fedora Haskell"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; }) {}; "feed" = callPackage - ({ mkDerivation, base, base-compat, bytestring, old-locale - , old-time, safe, stdenv, text, time, time-locale-compat - , utf8-string, xml-conduit, xml-types + ({ mkDerivation, base, base-compat, bytestring, lib, old-locale + , old-time, safe, text, time, time-locale-compat, utf8-string + , xml-conduit, xml-types }: mkDerivation { pname = "feed"; - version = "1.0.1.0"; - sha256 = "87bd055b13c43f54e997f716a33d647c6bc1cdb78337c840d144c0b5fdccd31c"; + version = "1.3.2.0"; + sha256 = "b311c7e0568d6f6186500d18e5e6495222caeb0b550457e7e690626947df634f"; + revision = "1"; + editedCabalFile = "0lg9yphl07hbknzx0nvdxvcw05bpxc5ac9sqb26lv4d9nkb72blg"; enableSeparateDataOutput = true; libraryHaskellDepends = [ base base-compat bytestring old-locale old-time safe text time @@ -11874,16 +13618,16 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/bergmark/feed"; description = "Interfacing with RSS (v 0.9x, 2.x, 1.0) + Atom feeds."; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "fft" = callPackage ({ mkDerivation, array, base, carray, fftw, fftwFloat, ix-shapable - , stdenv, storable-complex, syb, transformers + , lib, storable-complex, syb, transformers }: mkDerivation { pname = "fft"; - version = "0.1.8.6"; - sha256 = "2ed8d8301903283c9a62eda1f1cf49db0c471c4c128fbfdef562d598401e5b42"; + version = "0.1.8.7"; + sha256 = "7f9b26ec09c3b658959883edc784c0140acbcc41c5ddf3d37bf2e98f11e06dce"; libraryHaskellDepends = [ array base carray ix-shapable storable-complex syb transformers ]; @@ -11891,32 +13635,32 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Bindings to the FFTW library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) fftw; inherit (pkgs) fftwFloat;}; "fgl" = callPackage - ({ mkDerivation, array, base, containers, deepseq, stdenv + ({ mkDerivation, array, base, containers, deepseq, lib , transformers }: mkDerivation { pname = "fgl"; - version = "5.7.0.1"; - sha256 = "ffce7af67d4e7ee2f6a7c44fbb749c4253ce9bb35b8b1ffe1c93a173a01fe910"; + version = "5.7.0.3"; + sha256 = "2969b813b9067eb80708b056434da576fcd134a0ec757dd8e4018d566e7e6512"; libraryHaskellDepends = [ array base containers deepseq transformers ]; doHaddock = false; doCheck = false; description = "Martin Erwig's Functional Graph Library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "file-embed" = callPackage - ({ mkDerivation, base, bytestring, directory, filepath, stdenv + ({ mkDerivation, base, bytestring, directory, filepath, lib , template-haskell }: mkDerivation { pname = "file-embed"; - version = "0.0.11"; - sha256 = "eea5d00973808e440f346972b7477c8d8c2194a7036cc532eafeffc5189fcd50"; + version = "0.0.14.0"; + sha256 = "050267dbb2fb9033f16c66659fa739b6972775591fddf747e13f8d71c2f485ac"; libraryHaskellDepends = [ base bytestring directory filepath template-haskell ]; @@ -11924,19 +13668,19 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/snoyberg/file-embed"; description = "Use Template Haskell to embed file contents directly"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "file-embed-lzma" = callPackage ({ mkDerivation, base, base-compat, bytestring, directory, filepath - , lzma, stdenv, template-haskell, text, th-lift-instances + , lib, lzma, template-haskell, text, th-lift-instances , transformers }: mkDerivation { pname = "file-embed-lzma"; version = "0"; sha256 = "e86cf44f747cf403898158e9fdf9342871e293097a29679fcf587aed497f0c77"; - revision = "2"; - editedCabalFile = "0dmg69gsj2k9lf112bvqw6z2w8hl0p1lx5zxdvlvk85bb3qz6304"; + revision = "6"; + editedCabalFile = "0m2ay6krrjs2cgmy7divlavx0wvgwhwgba97f1m3ppcxxm1y4ikv"; libraryHaskellDepends = [ base base-compat bytestring directory filepath lzma template-haskell text th-lift-instances transformers @@ -11945,65 +13689,42 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/phadej/file-embed-lzma"; description = "Use Template Haskell to embed (LZMA compressed) data"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "file-modules" = callPackage - ({ mkDerivation, async, base, directory, filepath, haskell-src-exts - , MissingH, regex-compat, regex-pcre, stdenv - }: - mkDerivation { - pname = "file-modules"; - version = "0.1.2.4"; - sha256 = "ffea2dbd51f77ed76f8559d8519674a1210611a35e2dbea72dfb41d7d5f0f235"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - async base directory filepath haskell-src-exts MissingH - regex-compat regex-pcre - ]; - executableHaskellDepends = [ - async base directory filepath haskell-src-exts MissingH - regex-compat regex-pcre - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/yamadapc/stack-run-auto"; - description = "Takes a Haskell source-code file and outputs its modules"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.bsd3; }) {}; - "filecache" = callPackage - ({ mkDerivation, base, containers, directory, exceptions, filepath - , fsnotify, mtl, stdenv, stm, strict-base-types, time + "file-path-th" = callPackage + ({ mkDerivation, base, directory, file-embed, filepath, lib + , template-haskell }: mkDerivation { - pname = "filecache"; - version = "0.4.1"; - sha256 = "c502a8b43cf08694c8d2657dc282306d811cdd91f284614a6a9945267c93cb9d"; + pname = "file-path-th"; + version = "0.1.0.0"; + sha256 = "e59e9c79f656bf23c1f484dcf84d48c99e9ec36998c589fba03f63e222956297"; + revision = "1"; + editedCabalFile = "0v1hfgw2sqscbxlzidqzdljz92mihydk765370sq6hmjiw98a5fk"; libraryHaskellDepends = [ - base containers directory exceptions filepath fsnotify mtl stm - strict-base-types time + base directory file-embed filepath template-haskell ]; doHaddock = false; doCheck = false; - homepage = "http://lpuppet.banquise.net/"; - description = "A cache system associating values to files"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/Simspace/file-path-th#readme"; + description = "Template Haskell utilities for filepaths"; + license = lib.licenses.mit; }) {}; "filelock" = callPackage - ({ mkDerivation, base, stdenv, unix }: + ({ mkDerivation, base, lib, unix }: mkDerivation { pname = "filelock"; - version = "0.1.1.2"; - sha256 = "0ff1dcb13ec619f72496035e2a1298ef9dc6a814ba304d882cd9b145eae3203d"; + version = "0.1.1.5"; + sha256 = "50ebea81e8443356af26f32221d4594709d94102445931673fcd94a44e244419"; libraryHaskellDepends = [ base unix ]; doHaddock = false; doCheck = false; homepage = "http://github.com/takano-akio/filelock"; description = "Portable interface to file locking (flock / LockFileEx)"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "filemanip" = callPackage - ({ mkDerivation, base, bytestring, directory, filepath, mtl, stdenv + ({ mkDerivation, base, bytestring, directory, filepath, lib, mtl , unix-compat }: mkDerivation { @@ -12017,10 +13738,35 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/bos/filemanip"; description = "Expressive file and directory manipulation for Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "filepath-bytestring" = callPackage + ({ mkDerivation, base, bytestring, lib, unix }: + mkDerivation { + pname = "filepath-bytestring"; + version = "1.4.2.1.7"; + sha256 = "3610968b4f535ac3d072bf02c875eaacbca5181aa8df0ba4276b638125f6aa03"; + libraryHaskellDepends = [ base bytestring unix ]; + doHaddock = false; + doCheck = false; + description = "Library for manipulating RawFilePaths in a cross platform way"; + license = lib.licenses.bsd3; + }) {}; + "filepattern" = callPackage + ({ mkDerivation, base, directory, extra, filepath, lib }: + mkDerivation { + pname = "filepattern"; + version = "0.1.2"; + sha256 = "d92912ee0db0b8c50d6b2ffdc1ae91ee30e2704b47896aa325b42b58a2fcf65b"; + libraryHaskellDepends = [ base directory extra filepath ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ndmitchell/filepattern#readme"; + description = "File path glob-like matching"; + license = lib.licenses.bsd3; }) {}; "fileplow" = callPackage - ({ mkDerivation, base, binary-search, bytestring, stdenv, vector }: + ({ mkDerivation, base, binary-search, bytestring, lib, vector }: mkDerivation { pname = "fileplow"; version = "0.1.0.0"; @@ -12030,60 +13776,40 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/agrafix/fileplow#readme"; description = "Library to process and search large files or a collection of files"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "filter-logger" = callPackage - ({ mkDerivation, aeson, aeson-pretty, ansi-terminal, base - , bytestring, data-default, fast-logger, http-types, scotty - , semigroups, stdenv, time, wai, wai-extra, wai-logger - }: - mkDerivation { - pname = "filter-logger"; - version = "0.6.0.0"; - sha256 = "7884124056950a7f7ff393ebb7d1622695f9b66f898c60aeb8bc991c73642f21"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - aeson aeson-pretty ansi-terminal base bytestring data-default - fast-logger http-types semigroups time wai wai-extra wai-logger - ]; - executableHaskellDepends = [ aeson base bytestring scotty ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/caneroj1/filter-logger#readme"; - description = "Filterable request logging wai middleware. Change how data is logged and when."; - license = stdenv.lib.licenses.mit; + license = lib.licenses.bsd3; }) {}; "filtrable" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "filtrable"; - version = "0.1.1.0"; - sha256 = "d6a53889a7d114a7ea411026b994c9f73ebfeffe68ea338ce2abf9dc977e363c"; - libraryHaskellDepends = [ base ]; + version = "0.1.4.0"; + sha256 = "cf76049204f59dcd8847cfbef8f61749109879d3cb5b0507a3fa866078d24a86"; + libraryHaskellDepends = [ base transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/strake/filtrable.hs"; description = "Class of filtrable containers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "fin" = callPackage - ({ mkDerivation, base, deepseq, hashable, stdenv }: + ({ mkDerivation, base, dec, deepseq, hashable, lib, QuickCheck + , universe-base + }: mkDerivation { pname = "fin"; - version = "0.0.1"; - sha256 = "34d28a951f2899f1d27bfb75d53818204d6d7e5aeaaef1a326c50ae915361a57"; - revision = "1"; - editedCabalFile = "056d22f1j1xv5ka2qr7a3z5ad5w1im76qdf77v6dqdi4vaz52vd1"; - libraryHaskellDepends = [ base deepseq hashable ]; + version = "0.2"; + sha256 = "239a34834869abc3519353783dd86d84c1650da07e4241c1f28c6843f76bc3f7"; + libraryHaskellDepends = [ + base dec deepseq hashable QuickCheck universe-base + ]; doHaddock = false; doCheck = false; homepage = "https://github.com/phadej/vec"; description = "Nat and Fin: peano naturals and finite numbers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "fingertree" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "fingertree"; version = "0.1.4.2"; @@ -12092,10 +13818,10 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Generic finger-tree structure, with example instances"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "finite-typelits" = callPackage - ({ mkDerivation, base, deepseq, stdenv }: + ({ mkDerivation, base, deepseq, lib }: mkDerivation { pname = "finite-typelits"; version = "0.1.4.2"; @@ -12105,43 +13831,40 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/mniip/finite-typelits"; description = "A type inhabited by finitely many values, indexed by type-level naturals"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "first-class-families" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "first-class-families"; - version = "0.3.0.1"; - sha256 = "2b761dcb4361d2628147c13f2d024782d02f8a7e0df78df004439c14640b491c"; - revision = "1"; - editedCabalFile = "1gybi18yw6dzp3r82x0xq9364m3isqq31gvaa1agf6hk9c9szfl2"; + version = "0.8.0.1"; + sha256 = "4a1c8fbdbe01757ea8dc3190050d7a4a72c86e205d23676182292fe192c1da72"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/Lysxia/first-class-families#readme"; - description = "First class type families"; - license = stdenv.lib.licenses.mit; + description = "First-class type families"; + license = lib.licenses.mit; }) {}; "first-class-patterns" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "first-class-patterns"; - version = "0.3.2.4"; - sha256 = "3bf42829097277a89043021d02b82bde24950de9c30d19b33c0ffa5e1f2482b5"; + version = "0.3.2.5"; + sha256 = "7a4bcfe2c9907d7964d2a29816ea37aac64b0506fdebd34241d0dd735cb308ae"; libraryHaskellDepends = [ base transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/kowainik/first-class-patterns"; description = "First class patterns and pattern matching, using type families"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "fitspec" = callPackage - ({ mkDerivation, base, cmdargs, leancheck, stdenv, template-haskell - }: + ({ mkDerivation, base, cmdargs, leancheck, lib, template-haskell }: mkDerivation { pname = "fitspec"; - version = "0.4.7"; - sha256 = "b8dc00aad234b30d1d383075062c0756bb7d412a5bf4b766f2aad0d7ac30716a"; + version = "0.4.10"; + sha256 = "332469d895c8f3ba00f55b7a70b1401d26c93d04063b7f1d923015cc675e04cb"; libraryHaskellDepends = [ base cmdargs leancheck template-haskell ]; @@ -12149,40 +13872,60 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/rudymatela/fitspec#readme"; description = "refining property sets for testing Haskell programs"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "fix-whitespace" = callPackage + ({ mkDerivation, base, directory, extra, filepath, filepattern, lib + , text, yaml + }: + mkDerivation { + pname = "fix-whitespace"; + version = "0.0.5"; + sha256 = "c7c33394122ceff27d41ffd9aed5516182def30f9d1d829b5e332bdc5080e49c"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ + base directory extra filepath filepattern text yaml + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/agda/fix-whitespace"; + description = "Fixes whitespace issues"; + license = "unknown"; + hydraPlatforms = lib.platforms.none; }) {}; "fixed" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "fixed"; - version = "0.2.1.1"; - sha256 = "24a9e1e251998c9d06037bb771d9eab2980a91132de59a19d0166a1c51e715e2"; + version = "0.3"; + sha256 = "9218ebd3af3f07335db8dcd148b3ce40acf984734c244cce5959f57402d48282"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/fixed"; description = "Signed 15.16 precision fixed point arithmetic"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "fixed-length" = callPackage - ({ mkDerivation, base, non-empty, stdenv, storable-record, tfp + ({ mkDerivation, base, lib, non-empty, storable-record, tfp , utility-ht }: mkDerivation { pname = "fixed-length"; - version = "0.2.1"; - sha256 = "a151b68802538e8f98d05f582bd23fad94c869e1ad1f5506579524f5d2764b49"; + version = "0.2.2.1"; + sha256 = "071b851a24fb9db200daf1143ae4e17243227e948979598804d0a01683f77188"; libraryHaskellDepends = [ base non-empty storable-record tfp utility-ht ]; doHaddock = false; doCheck = false; - homepage = "http://hub.darcs.net/thielema/fixed-length/"; + homepage = "https://hub.darcs.net/thielema/fixed-length/"; description = "Lists with statically known length based on non-empty package"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "fixed-vector" = callPackage - ({ mkDerivation, base, deepseq, primitive, stdenv }: + ({ mkDerivation, base, deepseq, lib, primitive }: mkDerivation { pname = "fixed-vector"; version = "1.2.0.0"; @@ -12191,71 +13934,105 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Generic vectors with statically known size"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "fixed-vector-hetero" = callPackage - ({ mkDerivation, base, deepseq, fixed-vector, primitive, stdenv }: + ({ mkDerivation, base, deepseq, fixed-vector, lib, primitive }: mkDerivation { pname = "fixed-vector-hetero"; - version = "0.5.0.0"; - sha256 = "a3f25968b260c953c6ad4ec75ba5211238b2bb07185fe1f33fb98301a4ee8690"; + version = "0.6.1.0"; + sha256 = "2894e7d37488f3e4b2dbf03e9da1dae0f80e3837e26fd4dd24187d9cf4ad35ea"; libraryHaskellDepends = [ base deepseq fixed-vector primitive ]; doHaddock = false; doCheck = false; homepage = "http://github.org/Shimuuar/fixed-vector-hetero"; - description = "Generic heterogeneous vectors"; - license = stdenv.lib.licenses.bsd3; + description = "Library for working with product types generically"; + license = lib.licenses.bsd3; }) {}; "flac" = callPackage - ({ mkDerivation, base, bytestring, containers, data-default-class - , directory, exceptions, filepath, FLAC, mtl, stdenv, text - , transformers, vector, wave + ({ mkDerivation, base, bytestring, containers, directory + , exceptions, filepath, FLAC, lib, mtl, text, transformers, vector + , wave }: mkDerivation { pname = "flac"; - version = "0.1.2"; - sha256 = "5692b3dfc561cbeed25b1cf9280705f58eadd8c400aa2e6a725fd5562042ac29"; - revision = "4"; - editedCabalFile = "0bmhd56fg4idz62maig3kykk7dyqy9dpm27fdljqg8jccl0vbwbm"; + version = "0.2.0"; + sha256 = "6c8ca5fbe7ac4c6d9475678fc3bcc3b132a75fea870a3591d646cc79add5f50f"; + revision = "2"; + editedCabalFile = "1b3cbhvvhbv1d0gkfwgn9j9jx9cjn3w606vbpfhak2cyjmw26q36"; enableSeparateDataOutput = true; libraryHaskellDepends = [ - base bytestring containers data-default-class directory exceptions - filepath mtl text transformers vector wave + base bytestring containers directory exceptions filepath mtl text + transformers vector wave ]; librarySystemDepends = [ FLAC ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mrkkrp/flac"; description = "Complete high-level binding to libFLAC"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) FLAC;}; "flac-picture" = callPackage - ({ mkDerivation, base, bytestring, flac, JuicyPixels, stdenv }: + ({ mkDerivation, base, bytestring, flac, JuicyPixels, lib }: mkDerivation { pname = "flac-picture"; - version = "0.1.1"; - sha256 = "3c1cf80c48521370ce6351d4b544c14891442bfe47c65e5bf436fe58f6fec1ce"; + version = "0.1.2"; + sha256 = "15689d14d382588697ec0da88a0025c2b156061c060979deaec0d75ecc37030a"; revision = "1"; - editedCabalFile = "02vdh61nzig0yrv6ja6fjlgfcznj5k4iqh3i5f9g5p078ycqb17w"; + editedCabalFile = "1ib9ypz06i81bgkj08aw6fdyxi6fbl2029vwlcqybbhz9cnya1pm"; enableSeparateDataOutput = true; libraryHaskellDepends = [ base bytestring flac JuicyPixels ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mrkkrp/flac-picture"; description = "Support for writing picture to FLAC metadata blocks with JuicyPixels"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "flags-applicative" = callPackage + ({ mkDerivation, base, casing, containers, lib, mtl, network, text + }: + mkDerivation { + pname = "flags-applicative"; + version = "0.1.0.3"; + sha256 = "e317eb536d13dc54973c4de13f30bee898889705874e26547949a7948451f469"; + libraryHaskellDepends = [ + base casing containers mtl network text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/mtth/flags-applicative"; + description = "Applicative flag parsing"; + license = lib.licenses.bsd3; + }) {}; + "flat" = callPackage + ({ mkDerivation, array, base, bytestring, containers, deepseq + , dlist, ghc-prim, hashable, lib, mono-traversable, pretty + , primitive, semigroups, text, unordered-containers, vector + }: + mkDerivation { + pname = "flat"; + version = "0.4.4"; + sha256 = "e39eaab6362851a67bff6cc501e17fa23ef0461b4d4c11c6d521d43affb7240a"; + libraryHaskellDepends = [ + array base bytestring containers deepseq dlist ghc-prim hashable + mono-traversable pretty primitive semigroups text + unordered-containers vector + ]; + doHaddock = false; + doCheck = false; + homepage = "http://quid2.org"; + description = "Principled and efficient bit-oriented binary serialization"; + license = lib.licenses.bsd3; }) {}; "flat-mcmc" = callPackage - ({ mkDerivation, base, formatting, mcmc-types, monad-par - , monad-par-extras, mwc-probability, pipes, primitive, stdenv, text + ({ mkDerivation, base, formatting, lib, mcmc-types, monad-par + , monad-par-extras, mwc-probability, pipes, primitive, text , transformers, vector }: mkDerivation { pname = "flat-mcmc"; - version = "1.5.0"; - sha256 = "87cea9deac6e2d32d9984741ba222ccb2fb0d5f8c58e843684476bfe7632f1fd"; - revision = "1"; - editedCabalFile = "1pjkyvs4c6yx6jva08zw2b1qfhhv9q71sy806f5lddjsknnym2fn"; + version = "1.5.2"; + sha256 = "3b2693f09558f877ba4a402a44c6662fa35257d1d3ff75108f60419378acad8f"; libraryHaskellDepends = [ base formatting mcmc-types monad-par monad-par-extras mwc-probability pipes primitive text transformers vector @@ -12264,29 +14041,16 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/jtobin/flat-mcmc"; description = "Painless general-purpose sampling"; - license = stdenv.lib.licenses.mit; - }) {}; - "flay" = callPackage - ({ mkDerivation, base, constraints, stdenv, transformers }: - mkDerivation { - pname = "flay"; - version = "0.4"; - sha256 = "01ff3e642eab48807e4369fd8c1336e22d7abdcf4374cd1322b1fe259c9413ef"; - libraryHaskellDepends = [ base constraints transformers ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/k0001/flay"; - description = "Work generically on your datatype without knowing its shape nor its contents"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; "flexible-defaults" = callPackage - ({ mkDerivation, base, containers, stdenv, template-haskell - , th-extras, transformers + ({ mkDerivation, base, containers, lib, template-haskell, th-extras + , transformers }: mkDerivation { pname = "flexible-defaults"; - version = "0.0.2"; - sha256 = "f3d5d41a6dd69dbb585dd10fe6b7fe9023bc4308bac1320a55b62758acc18a64"; + version = "0.0.3"; + sha256 = "6586f6fce40e64f95e6d3de6d0730f9fe6668825d0dfd81336842fa8c62a630b"; libraryHaskellDepends = [ base containers template-haskell th-extras transformers ]; @@ -12294,10 +14058,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/peti/flexible-defaults"; description = "Generate default function implementations for complex type classes"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "floatshow" = callPackage - ({ mkDerivation, array, base, integer-gmp, stdenv }: + ({ mkDerivation, array, base, integer-gmp, lib }: mkDerivation { pname = "floatshow"; version = "0.2.4"; @@ -12307,45 +14071,55 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://bitbucket.org/dafis/floatshow"; description = "Alternative faster String representations for Double and Float, String representations for more general numeric types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "flow" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "flow"; - version = "1.0.17"; - sha256 = "86ec19d8bec13afc58e21d53f4225c3fcafda2ff902b05f64062919edbe84d19"; + version = "1.0.22"; + sha256 = "39aa145ece6a2fa8e931b077f430ca3338f661998141d4c0081da94aa17251f7"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/tfausak/flow#readme"; description = "Write more understandable Haskell"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "flush-queue" = callPackage + ({ mkDerivation, atomic-primops, base, containers, lib, stm }: + mkDerivation { + pname = "flush-queue"; + version = "1.0.0"; + sha256 = "c9ac0f566bf673d685f5264b941ba46153a3acfe935cd8fe982d277bdf8f669d"; + libraryHaskellDepends = [ atomic-primops base containers stm ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/fpco/flush-queue#readme"; + description = "Concurrent bouded blocking queues optimized for flushing. Both IO and STM implementations."; + license = lib.licenses.bsd3; }) {}; "fmlist" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "fmlist"; - version = "0.9.2"; - sha256 = "8fc4b55d04e7f216740a01acd2f38293e3bd9409a9495e6042a162580c420609"; + version = "0.9.4"; + sha256 = "2dbdc1850e6768fd5f4e4c45d011ef6796d8b2d639ec200da7f4407ae02d09a6"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/sjoerdvisscher/fmlist"; description = "FoldMap lists"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "fmt" = callPackage ({ mkDerivation, base, base64-bytestring, bytestring, call-stack - , containers, formatting, microlens, stdenv, text, time + , containers, formatting, lib, microlens, text, time , time-locale-compat }: mkDerivation { pname = "fmt"; - version = "0.6.1.1"; - sha256 = "26220b578d56591cb154cfcb1d98ee8f81c1df97f5955dba91dd00061549d2ad"; - revision = "1"; - editedCabalFile = "13ypmyg0axadzhycfl0g1s73bk9a2myshf38y8dslf3hlg76wbmv"; + version = "0.6.1.2"; + sha256 = "78ed7bddb25c0bc4355ca2be2be3c4d8af796bce7e76e20f04b6aebbcbab8ab9"; libraryHaskellDepends = [ base base64-bytestring bytestring call-stack containers formatting microlens text time time-locale-compat @@ -12354,12 +14128,12 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/aelve/fmt"; description = "A new formatting library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "fn" = callPackage ({ mkDerivation, base, blaze-builder, bytestring, directory - , filepath, http-types, resourcet, stdenv, text - , unordered-containers, wai, wai-extra + , filepath, http-types, lib, resourcet, text, unordered-containers + , wai, wai-extra }: mkDerivation { pname = "fn"; @@ -12373,31 +14147,29 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/positiondev/fn#readme"; description = "A functional web framework"; - license = stdenv.lib.licenses.isc; + license = lib.licenses.isc; }) {}; "focus" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "focus"; - version = "1.0.1.2"; - sha256 = "adf4e7fd24a441548a450828881baea013f6374811230beb6437cfcdc2616e02"; + version = "1.0.2"; + sha256 = "8d829d69dad7ff4c8377141b35e8ba81f764e55db7961591657c6c3bcd2ba825"; libraryHaskellDepends = [ base transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nikita-volkov/focus"; description = "A general abstraction for manipulating elements of container data structures"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "focuslist" = callPackage - ({ mkDerivation, base, Cabal, cabal-doctest, containers, lens - , mono-traversable, QuickCheck, stdenv + ({ mkDerivation, base, Cabal, cabal-doctest, containers, lens, lib + , mono-traversable, QuickCheck }: mkDerivation { pname = "focuslist"; - version = "0.1.0.1"; - sha256 = "fdee9ae7a68f139f9b4b88df27e4f373815293da93a1df91e5c2f3dc558f05e3"; - revision = "2"; - editedCabalFile = "12x38kxhcjdqfwl8y8zdrwcpv6jdm7jaqc48ww3hg6fpv8rvvd49"; + version = "0.1.0.2"; + sha256 = "78527aad6212617d4c8c3183c02750693d5bd30be1a26f1caff7db434b31481b"; isLibrary = true; isExecutable = true; setupHaskellDepends = [ base Cabal cabal-doctest ]; @@ -12408,16 +14180,16 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/cdepillabout/focuslist"; description = "Lists with a focused element"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "fold-debounce" = callPackage - ({ mkDerivation, base, data-default-class, stdenv, stm, stm-delay + ({ mkDerivation, base, data-default-class, lib, stm, stm-delay , time }: mkDerivation { pname = "fold-debounce"; - version = "0.2.0.8"; - sha256 = "fc6b3ef028517f642886c2ffa270726cc38c79be75d1233e28f760816d08fbc8"; + version = "0.2.0.9"; + sha256 = "98931e65001dd5d7be5a767837e74e6fc7a5ec16cbdd09408fa7e97a17995b0c"; libraryHaskellDepends = [ base data-default-class stm stm-delay time ]; @@ -12425,16 +14197,16 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/debug-ito/fold-debounce"; description = "Fold multiple events that happen in a given period of time"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "fold-debounce-conduit" = callPackage - ({ mkDerivation, base, conduit, fold-debounce, resourcet, stdenv - , stm, transformers, transformers-base + ({ mkDerivation, base, conduit, fold-debounce, lib, resourcet, stm + , transformers, transformers-base }: mkDerivation { pname = "fold-debounce-conduit"; - version = "0.2.0.3"; - sha256 = "97c80c4ca7f84260539829ee7ebf0eaa6b127005158eb910411ae0b17157ef67"; + version = "0.2.0.6"; + sha256 = "c5e7eba252df2019a30a99e5c29d1d0dcf8cbbe767d23c347381f00545dec677"; libraryHaskellDepends = [ base conduit fold-debounce resourcet stm transformers transformers-base @@ -12443,10 +14215,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/debug-ito/fold-debounce-conduit"; description = "Regulate input traffic from conduit Source with Control.FoldDebounce"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "foldable1" = callPackage - ({ mkDerivation, base, stdenv, transformers, util }: + ({ mkDerivation, base, lib, transformers, util }: mkDerivation { pname = "foldable1"; version = "0.1.0.0"; @@ -12455,40 +14227,38 @@ inherit (pkgs.xorg) libXfixes;}; doHaddock = false; doCheck = false; description = "Foldable types with at least 1 element"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "foldl" = callPackage ({ mkDerivation, base, bytestring, comonad, containers - , contravariant, hashable, mwc-random, primitive, profunctors - , semigroupoids, semigroups, stdenv, text, transformers - , unordered-containers, vector, vector-builder + , contravariant, hashable, lib, primitive, profunctors, random + , semigroupoids, text, transformers, unordered-containers, vector }: mkDerivation { pname = "foldl"; - version = "1.4.5"; - sha256 = "0ba0bd8a8b4273feef61b66b6e251e70f70537c113f8b7f0e3aeab77d8af12a7"; + version = "1.4.12"; + sha256 = "4f59360d96fb9ff10861944dd8a89b2448ea2b7dedc376546f4de80125f5c47d"; libraryHaskellDepends = [ - base bytestring comonad containers contravariant hashable - mwc-random primitive profunctors semigroupoids semigroups text - transformers unordered-containers vector vector-builder + base bytestring comonad containers contravariant hashable primitive + profunctors random semigroupoids text transformers + unordered-containers vector ]; doHaddock = false; doCheck = false; description = "Composable, streaming, and efficient left folds"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "folds" = callPackage - ({ mkDerivation, adjunctions, base, bifunctors, Cabal - , cabal-doctest, comonad, constraints, contravariant, data-reify - , distributive, lens, mtl, pointed, profunctors, reflection - , semigroupoids, stdenv, transformers, unordered-containers, vector + ({ mkDerivation, adjunctions, base, bifunctors, comonad + , constraints, contravariant, data-reify, distributive, lens, lib + , mtl, pointed, profunctors, reflection, semigroupoids + , transformers, unordered-containers, vector }: mkDerivation { pname = "folds"; - version = "0.7.4"; - sha256 = "5c6e6f7c9c852cbe3d5372f93ed99f82400d15ae99ecf8e9e005481647734572"; + version = "0.7.6"; + sha256 = "7bb089c16effc87be55bc591208a09ea27faf7653a8bfacdc7679e41b31a5e1b"; configureFlags = [ "-f-test-hlint" ]; - setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ adjunctions base bifunctors comonad constraints contravariant data-reify distributive lens mtl pointed profunctors reflection @@ -12498,28 +14268,36 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/ekmett/folds"; description = "Beautiful Folding"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "force-layout" = callPackage - ({ mkDerivation, base, containers, data-default-class, lens, linear - , stdenv + "follow-file" = callPackage + ({ mkDerivation, attoparsec, attoparsec-path, base, bytestring + , conduit, conduit-combinators, directory, exceptions, hinotify + , lib, monad-control, mtl, path, text, unix, utf8-string }: mkDerivation { - pname = "force-layout"; - version = "0.4.0.6"; - sha256 = "f7729855b1b14e0b255325faaca9f4834004e02bd21def6a865d2c55c734259d"; - revision = "4"; - editedCabalFile = "0hpr1z68lflgcdl9gbmva0i52wbgfhh4qj3iwdvzipsp8mwav7s7"; + pname = "follow-file"; + version = "0.0.3"; + sha256 = "232de19ab42130273aac870e5b8d13e55996af670b28c12a192fcb664fe0bb5b"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - base containers data-default-class lens linear + attoparsec attoparsec-path base bytestring conduit directory + exceptions hinotify monad-control mtl path text unix utf8-string + ]; + executableHaskellDepends = [ + attoparsec attoparsec-path base bytestring conduit + conduit-combinators directory exceptions hinotify monad-control mtl + path text unix utf8-string ]; doHaddock = false; doCheck = false; - description = "Simple force-directed layout"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/athanclark/follow-file#readme"; + description = "Be notified when a file gets appended, solely with what was added. Warning - only works on linux and for files that are strictly appended, like log files."; + license = lib.licenses.bsd3; }) {}; "foreign-store" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "foreign-store"; version = "0.2"; @@ -12529,10 +14307,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/chrisdone/foreign-store"; description = "Store a stable pointer in a foreign context to be retrieved later"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "forkable-monad" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "forkable-monad"; version = "0.2.0.3"; @@ -12542,18 +14320,18 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/System-Indystress/ForkableMonad#readme"; description = "An implementation of forkIO for monad stacks"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "forma" = callPackage - ({ mkDerivation, aeson, base, containers, mtl, stdenv, text + ({ mkDerivation, aeson, base, containers, lib, mtl, text , unordered-containers }: mkDerivation { pname = "forma"; - version = "1.1.0"; - sha256 = "b7dc7270e0a294cdaf40e99f067928411d82ed50af4dad51a6088830d539c325"; - revision = "2"; - editedCabalFile = "1yc9gv1rjbl4lsxscp5idfpn7jp27c38j6gm9v7isxgyaih0j4v4"; + version = "1.1.3"; + sha256 = "0c6c4f31688802ca44e477022c9d05f426109e3fc8cc4a98e07339b7e2c7a25d"; + revision = "1"; + editedCabalFile = "0p8cxv068d2fhpym28p49wxsiz6qdm1gb8mgw86lgs8yykqzwsy8"; libraryHaskellDepends = [ aeson base containers mtl text unordered-containers ]; @@ -12561,78 +14339,118 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/mrkkrp/forma"; description = "Parse and validate forms in JSON format"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "format-numbers" = callPackage - ({ mkDerivation, base, stdenv, text }: + ({ mkDerivation, base, lib, text }: mkDerivation { pname = "format-numbers"; - version = "0.1.0.0"; - sha256 = "0ca4561b55c888552f7bf0eb68e97b62acedcb0d5e5e1cc4afd94402d01231a6"; + version = "0.1.0.1"; + sha256 = "5c450e4bf0d955a5eaa163468176385c46298fc086f217c3ca801fb786dc76a4"; libraryHaskellDepends = [ base text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/agrafix/format-numbers#readme"; description = "Various number formatting functions"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "formatting" = callPackage - ({ mkDerivation, array, base, bytestring, clock, ghc-prim - , integer-gmp, old-locale, scientific, semigroups, stdenv, text - , time, transformers + ({ mkDerivation, base, clock, double-conversion, ghc-prim, lib + , old-locale, scientific, text, time, transformers }: mkDerivation { pname = "formatting"; - version = "6.3.7"; - sha256 = "0cdb4fc2c33612db08cd07926ac4fbea6b9f3c31955ed7d212ae04586f585c1a"; + version = "7.1.3"; + sha256 = "8061bbe29278e6b7bb2268b00e1717385643dfa04e7b58b012bd53b342142cef"; libraryHaskellDepends = [ - array base bytestring clock ghc-prim integer-gmp old-locale - scientific semigroups text time transformers + base clock double-conversion ghc-prim old-locale scientific text + time transformers ]; doHaddock = false; doCheck = false; + homepage = "https://github.com/AJChapman/formatting#readme"; description = "Combinator-based type-safe formatting (like printf() or FORMAT)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "foundation" = callPackage - ({ mkDerivation, base, basement, ghc-prim, stdenv }: + ({ mkDerivation, base, basement, ghc-prim, lib }: mkDerivation { pname = "foundation"; - version = "0.0.21"; - sha256 = "4ed3a0e7f8052b52d27c9806eff3bea51acc2587f74f81db4b8e03e938f283e0"; - revision = "1"; - editedCabalFile = "07mzfc75wl7kn2lr2gmbx4i0a5gxyi9b066rz0x2pqxqav3fwqs0"; + version = "0.0.26.1"; + sha256 = "ad7024365e0b5d59314bca6106d64b03903db317d5bd308c81d01a87551e31c3"; libraryHaskellDepends = [ base basement ghc-prim ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-foundation/foundation"; description = "Alternative prelude with batteries and no dependencies"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "fourmolu" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers, directory + , dlist, exceptions, filepath, ghc-lib-parser, gitrev, HsYAML + , HsYAML-aeson, lib, mtl, optparse-applicative, syb, text + }: + mkDerivation { + pname = "fourmolu"; + version = "0.3.0.0"; + sha256 = "ba7201c78ee61665eaf1fce10cd297dd5383d36053cd3984e41a5094d96e096d"; + revision = "2"; + editedCabalFile = "16ky7wzmnwhzkk18r63ynq78vlrg065z6mp3hqgs92khpjr33g1l"; + isLibrary = true; + isExecutable = true; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + aeson base bytestring containers directory dlist exceptions + filepath ghc-lib-parser HsYAML HsYAML-aeson mtl syb text + ]; + executableHaskellDepends = [ + base directory ghc-lib-parser gitrev optparse-applicative text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/parsonsmatt/fourmolu"; + description = "A formatter for Haskell source code"; + license = lib.licenses.bsd3; }) {}; "free" = callPackage ({ mkDerivation, base, comonad, containers, distributive - , exceptions, mtl, profunctors, semigroupoids, stdenv - , template-haskell, transformers, transformers-base + , exceptions, indexed-traversable, lib, mtl, profunctors + , semigroupoids, template-haskell, th-abstraction, transformers + , transformers-base }: mkDerivation { pname = "free"; - version = "5.1"; - sha256 = "70424d5c82dea36a0a29c4f5f6bc047597a947ad46f3d66312e47bbee2eeea84"; + version = "5.1.7"; + sha256 = "b230d1e7e6bd0da6b8a1c83fe0c1609cb510bbec9fef7804b3604cd979402b88"; libraryHaskellDepends = [ - base comonad containers distributive exceptions mtl profunctors - semigroupoids template-haskell transformers transformers-base + base comonad containers distributive exceptions indexed-traversable + mtl profunctors semigroupoids template-haskell th-abstraction + transformers transformers-base ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/free/"; description = "Monads for free"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "free-vl" = callPackage - ({ mkDerivation, base, stdenv }: + "free-categories" = callPackage + ({ mkDerivation, base, lib }: mkDerivation { - pname = "free-vl"; - version = "0.1.4"; + pname = "free-categories"; + version = "0.2.0.2"; + sha256 = "99d40de81383c1cfbd47e3f34ba0e722e473bfc469af8cff981ce2a70f6daee8"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/morphismtech/free-categories"; + description = "free categories"; + license = lib.licenses.bsd3; + }) {}; + "free-vl" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "free-vl"; + version = "0.1.4"; sha256 = "57f63ed35b42fc54fefb3cc183d0655e0d6c4a28d5371dba00fc9c9d3fa602bf"; revision = "1"; editedCabalFile = "1711k76b6w7gfqvc8z9jnylj4hhk3rvx7ap31y1mmq4g2a4s82qm"; @@ -12644,10 +14462,10 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "http://github.com/aaronlevin/free-vl"; description = "van Laarhoven encoded Free Monad with Extensible Effects"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "freenect" = callPackage - ({ mkDerivation, base, freenect, freenect_sync, libfreenect, stdenv + ({ mkDerivation, base, freenect, freenect_sync, lib, libfreenect , vector }: mkDerivation { @@ -12661,17 +14479,19 @@ inherit (pkgs.xorg) libXfixes;}; doCheck = false; homepage = "https://github.com/chrisdone/freenect"; description = "Interface to the Kinect device"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) freenect; inherit (pkgs) freenect_sync; inherit (pkgs) libfreenect;}; "freer-simple" = callPackage - ({ mkDerivation, base, natural-transformation, stdenv + ({ mkDerivation, base, lib, natural-transformation , template-haskell, transformers-base }: mkDerivation { pname = "freer-simple"; - version = "1.2.1.0"; - sha256 = "ac288f691a86e2e3cbf94601f9964ddd4a10b9c6c7fd96ab8033744efc782ca5"; + version = "1.2.1.1"; + sha256 = "27cc3eaebef74268421c25d87c088003f7d8f175dd8b39818e66f62e4ecc0b6f"; + revision = "1"; + editedCabalFile = "10c7m8v7s8pqmhyym014xnb875z41sh3sq27b7sy7j15ay0vw694"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -12682,24 +14502,24 @@ inherit (pkgs) libfreenect;}; doCheck = false; homepage = "https://github.com/lexi-lambda/freer-simple#readme"; description = "Implementation of a friendly effect system for Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "freetype2" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "freetype2"; - version = "0.1.2"; - sha256 = "517e80298890e903b03134d7840d3d1a517bfdad53127ed57c2fdd18cbfae302"; + version = "0.2.0"; + sha256 = "55b93f3a18c10b1db4da86634e5388ad97a38a4881fca2feebcb2c464d85bfb9"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - description = "Haskell binding for FreeType 2 library"; - license = stdenv.lib.licenses.bsd3; + description = "Haskell bindings for FreeType 2 library"; + license = lib.licenses.bsd3; }) {}; "friendly-time" = callPackage - ({ mkDerivation, base, old-locale, stdenv, time }: + ({ mkDerivation, base, lib, old-locale, time }: mkDerivation { pname = "friendly-time"; version = "0.4.1"; @@ -12710,37 +14530,23 @@ inherit (pkgs) libfreenect;}; doHaddock = false; doCheck = false; description = "Print time information in friendly ways"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "frisby" = callPackage - ({ mkDerivation, array, base, containers, mtl, semigroups, stdenv - }: - mkDerivation { - pname = "frisby"; - version = "0.2.2"; - sha256 = "c1b318dbf54d56e1012955cc47a1633af5fd77facc128c725353718c0663b6d5"; - libraryHaskellDepends = [ array base containers mtl semigroups ]; - doHaddock = false; - doCheck = false; - homepage = "http://repetae.net/computer/frisby/"; - description = "Linear time composable parser for PEG grammars"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "from-sum" = callPackage - ({ mkDerivation, base, mtl, stdenv }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "from-sum"; - version = "0.2.1.0"; - sha256 = "a1ed8a433b98df8a70be2f9199abae3e5ed7fb4c2f2b3fb1268b6b588f326667"; - libraryHaskellDepends = [ base mtl ]; + version = "0.2.3.0"; + sha256 = "015582194287e21259db9c60b92d4c896a88e9f6e92356def001e15aa3f5bae5"; + libraryHaskellDepends = [ base transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/cdepillabout/from-sum"; - description = "Canonical fromMaybeM and fromEitherM functions"; - license = stdenv.lib.licenses.bsd3; + description = "Combinators for working with Maybe and Either"; + license = lib.licenses.bsd3; }) {}; "frontmatter" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, stdenv, yaml }: + ({ mkDerivation, attoparsec, base, bytestring, lib, yaml }: mkDerivation { pname = "frontmatter"; version = "0.1.0.2"; @@ -12750,11 +14556,11 @@ inherit (pkgs) libfreenect;}; doCheck = false; homepage = "https://github.com/yamadapc/haskell-frontmatter"; description = "Parses frontmatter as used in Jekyll markdown files"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "fsnotify" = callPackage ({ mkDerivation, async, base, bytestring, containers, directory - , filepath, hinotify, shelly, stdenv, text, time, unix, unix-compat + , filepath, hinotify, lib, shelly, text, time, unix, unix-compat }: mkDerivation { pname = "fsnotify"; @@ -12770,11 +14576,11 @@ inherit (pkgs) libfreenect;}; doCheck = false; homepage = "https://github.com/haskell-fswatch/hfsnotify"; description = "Cross platform library for file change notification"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "fsnotify-conduit" = callPackage - ({ mkDerivation, base, conduit, directory, filepath, fsnotify - , resourcet, stdenv, transformers + ({ mkDerivation, base, conduit, directory, filepath, fsnotify, lib + , resourcet, transformers }: mkDerivation { pname = "fsnotify-conduit"; @@ -12787,16 +14593,16 @@ inherit (pkgs) libfreenect;}; doCheck = false; homepage = "https://github.com/fpco/fsnotify-conduit#readme"; description = "Get filesystem notifications as a stream of events"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "ftp-client" = callPackage ({ mkDerivation, attoparsec, base, bytestring, connection - , containers, exceptions, network, stdenv, transformers + , containers, exceptions, lib, network, transformers }: mkDerivation { pname = "ftp-client"; - version = "0.5.1.1"; - sha256 = "6432f8a933051ac890420cf49ce89d57d05df97f1f8d1b84cb785ae1c468c805"; + version = "0.5.1.4"; + sha256 = "8e166b3f59451a40ca2c8c1e628da779f2c88888bf7fd2f573b94622b0b05d30"; libraryHaskellDepends = [ attoparsec base bytestring connection containers exceptions network transformers @@ -12805,16 +14611,16 @@ inherit (pkgs) libfreenect;}; doCheck = false; homepage = "https://github.com/mr/ftp-client"; description = "Transfer files with FTP and FTPS"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "ftp-client-conduit" = callPackage ({ mkDerivation, base, bytestring, conduit, connection, exceptions - , ftp-client, resourcet, stdenv + , ftp-client, lib, resourcet }: mkDerivation { pname = "ftp-client-conduit"; - version = "0.5.0.4"; - sha256 = "b1c58ff47c1555a39762c26dede087a0c3b4a16ca52ada7b748c328f89729a70"; + version = "0.5.0.5"; + sha256 = "426a34cfd8d8b388a5339a3a0c6378ffa38815ed25830cf9314292493e32a138"; libraryHaskellDepends = [ base bytestring conduit connection exceptions ftp-client resourcet ]; @@ -12822,10 +14628,10 @@ inherit (pkgs) libfreenect;}; doCheck = false; homepage = "https://github.com/mr/ftp-client"; description = "Transfer file with FTP and FTPS with Conduit"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "funcmp" = callPackage - ({ mkDerivation, base, filepath, pretty, process, stdenv }: + ({ mkDerivation, base, filepath, lib, pretty, process }: mkDerivation { pname = "funcmp"; version = "1.9"; @@ -12836,18 +14642,29 @@ inherit (pkgs) libfreenect;}; doCheck = false; homepage = "https://github.com/peti/funcmp"; description = "Functional MetaPost is a Haskell frontend to the MetaPost language"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; + }) {}; + "function-builder" = callPackage + ({ mkDerivation, base, lib, tagged }: + mkDerivation { + pname = "function-builder"; + version = "0.3.0.1"; + sha256 = "932d61d4622f84effcb67def19531f0baab34aa3adaff0417a6840a580f5eedf"; + libraryHaskellDepends = [ base tagged ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/sheyll/function-builder#readme"; + description = "Create poly variadic functions for monoidal results"; + license = lib.licenses.bsd3; }) {}; "functor-classes-compat" = callPackage - ({ mkDerivation, base, containers, hashable, stdenv + ({ mkDerivation, base, containers, hashable, lib , unordered-containers, vector }: mkDerivation { pname = "functor-classes-compat"; - version = "1"; - sha256 = "ef11f94f44a74d6657ee61dcd2cfbc6d0889d233a2fb4caae6a29d9c59a1366f"; - revision = "3"; - editedCabalFile = "1jx552ysdnxvd8wdvsf4bgxlsgldpb7a8zi54abyjmxv6mkp98ys"; + version = "1.0.1"; + sha256 = "234212061aa6ddf21f49aa43347cd7374839fb9b1cc6275e063ad6e883e4d35c"; configureFlags = [ "-fcontainers" ]; libraryHaskellDepends = [ base containers hashable unordered-containers vector @@ -12856,24 +14673,66 @@ inherit (pkgs) libfreenect;}; doCheck = false; homepage = "https://github.com/phadej/functor-classes-compat#readme"; description = "Data.Functor.Classes instances for core packages"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "fused-effects" = callPackage - ({ mkDerivation, base, deepseq, MonadRandom, random, stdenv }: + "functor-combinators" = callPackage + ({ mkDerivation, assoc, base, bifunctors, comonad, constraints + , containers, contravariant, deriving-compat, free, invariant + , kan-extensions, lib, mmorph, mtl, natural-transformation + , nonempty-containers, pointed, profunctors, semigroupoids + , sop-core, tagged, these, transformers, trivial-constraint, vinyl + }: mkDerivation { - pname = "fused-effects"; - version = "0.1.2.1"; - sha256 = "d6274dba440c69c2d0d5aaee05f99d00754094581c3d1cc1176586e8be289902"; - libraryHaskellDepends = [ base deepseq MonadRandom random ]; + pname = "functor-combinators"; + version = "0.3.6.0"; + sha256 = "0ef95f7446a0839d16962d18de350220e9bdfb4140834a66d9e536d54d42ae45"; + libraryHaskellDepends = [ + assoc base bifunctors comonad constraints containers contravariant + deriving-compat free invariant kan-extensions mmorph mtl + natural-transformation nonempty-containers pointed profunctors + semigroupoids sop-core tagged these transformers trivial-constraint + vinyl + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/mstksg/functor-combinators#readme"; + description = "Tools for functor combinator-based program design"; + license = lib.licenses.bsd3; + }) {}; + "fusion-plugin" = callPackage + ({ mkDerivation, base, containers, directory, filepath + , fusion-plugin-types, ghc, lib, syb, time, transformers + }: + mkDerivation { + pname = "fusion-plugin"; + version = "0.2.3"; + sha256 = "d8bbdc25b56c2ac6f1ea166f31859db27f044bdf2a7a121a77a86ea746cb74d2"; + libraryHaskellDepends = [ + base containers directory filepath fusion-plugin-types ghc syb time + transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/composewell/fusion-plugin"; + description = "GHC plugin to make stream fusion more predictable"; + license = lib.licenses.asl20; + }) {}; + "fusion-plugin-types" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "fusion-plugin-types"; + version = "0.1.0"; + sha256 = "6d0453886b0aca46ab311b8ac8031fd249417e96a1b675248fca196565f59f92"; + libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/robrix/fused-effects"; - description = "A fast, flexible, fused effect system"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/composewell/fusion-plugin-types"; + description = "Types for the fusion-plugin package"; + license = lib.licenses.bsd3; }) {}; "fuzzcheck" = callPackage - ({ mkDerivation, base, lifted-base, monad-control, QuickCheck - , random, stdenv, transformers + ({ mkDerivation, base, lib, lifted-base, monad-control, QuickCheck + , random, transformers }: mkDerivation { pname = "fuzzcheck"; @@ -12886,47 +14745,75 @@ inherit (pkgs) libfreenect;}; doCheck = false; homepage = "https://github.com/fpco/fuzzcheck"; description = "A simple checker for stress testing monadic code"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "fuzzy" = callPackage + ({ mkDerivation, base, lib, monoid-subclasses }: + mkDerivation { + pname = "fuzzy"; + version = "0.1.0.0"; + sha256 = "820a7a2b52163c1ecf0924780604ec903979560901cc1b9f27a68ff17256e9cb"; + libraryHaskellDepends = [ base monoid-subclasses ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/joom/fuzzy"; + description = "Filters a list based on a fuzzy string search"; + license = lib.licenses.mit; }) {}; "fuzzy-dates" = callPackage - ({ mkDerivation, base, hourglass, hspec, lens, parsec, stdenv }: + ({ mkDerivation, base, hourglass, hspec, lens, lib, parsec }: mkDerivation { pname = "fuzzy-dates"; - version = "0.1.1.1"; - sha256 = "e33406933fbb45172f5ee9b10194397333effecc3ce5f1495521bc903faf56c1"; + version = "0.1.1.2"; + sha256 = "a9b14c118be1f2c815c9e879121174f3e05b7b572b06741e33b39a3b4933ea89"; libraryHaskellDepends = [ base hourglass hspec lens parsec ]; doHaddock = false; doCheck = false; homepage = "https://github.com/ReedOei/fuzzy-dates#readme"; description = "Libary for parsing dates in strings in varied formats"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "fuzzy-time" = callPackage + ({ mkDerivation, base, containers, deepseq, lib, megaparsec, text + , time, validity, validity-time + }: + mkDerivation { + pname = "fuzzy-time"; + version = "0.1.0.0"; + sha256 = "9232d8aa01c9a346fe158d6ad3939aef6c94526c3a7c6c59fb14656b73bc2fd1"; + libraryHaskellDepends = [ + base containers deepseq megaparsec text time validity validity-time + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/fuzzy-time"; + license = lib.licenses.mit; }) {}; "fuzzyset" = callPackage - ({ mkDerivation, base, base-unicode-symbols, data-default, lens - , stdenv, text, text-metrics, unordered-containers, vector + ({ mkDerivation, base, data-default, lib, text, text-metrics + , unordered-containers, vector }: mkDerivation { pname = "fuzzyset"; - version = "0.1.0.8"; - sha256 = "9b975a5e54d3025c25ed01963d0d8e2b0bea0435f6fc88516ccf0da59dfbd124"; + version = "0.2.1"; + sha256 = "f1bec3277bb30256f87babe2e14ddf52b2ec71883dc29e233eedb43e71f01f8e"; libraryHaskellDepends = [ - base base-unicode-symbols data-default lens text text-metrics - unordered-containers vector + base data-default text text-metrics unordered-containers vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/laserpants/fuzzyset-haskell"; description = "Fuzzy set for approximate string matching"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "gauge" = callPackage - ({ mkDerivation, base, basement, deepseq, directory, process - , stdenv, vector + ({ mkDerivation, base, basement, deepseq, directory, lib, process + , vector }: mkDerivation { pname = "gauge"; - version = "0.2.4"; - sha256 = "297fa02ceeb8be23c111ecbd15bfb2203dfa22a757fce51f8ed2829d35630add"; + version = "0.2.5"; + sha256 = "d520fd677890c1bf2b1601331d003f976d85420811c3db4a72cff4d3bdb7f5a7"; libraryHaskellDepends = [ base basement deepseq directory process vector ]; @@ -12934,25 +14821,11 @@ inherit (pkgs) libfreenect;}; doCheck = false; homepage = "https://github.com/vincenthz/hs-gauge"; description = "small framework for performance measurement and analysis"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "gc" = callPackage - ({ mkDerivation, base, Cabal, cabal-doctest, stdenv }: - mkDerivation { - pname = "gc"; - version = "0.0.2"; - sha256 = "39cc5ac887319aeb184ee0d6ddb5b5a34e3f3d38c3fdf3ecc60bdf31a53dc30c"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; - libraryHaskellDepends = [ base ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/ekmett/gc/"; - description = "Poor Richard's Memory Manager"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "gd" = callPackage ({ mkDerivation, base, bytestring, expat, fontconfig, freetype, gd - , libjpeg, libpng, stdenv, zlib + , lib, libjpeg, libpng, zlib }: mkDerivation { pname = "gd"; @@ -12965,29 +14838,29 @@ inherit (pkgs) libfreenect;}; doHaddock = false; doCheck = false; description = "A Haskell binding to a subset of the GD graphics library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) expat; inherit (pkgs) fontconfig; inherit (pkgs) freetype; inherit (pkgs) gd; inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; "gdp" = callPackage - ({ mkDerivation, base, lawful, stdenv }: + ({ mkDerivation, base, lawful, lib }: mkDerivation { pname = "gdp"; - version = "0.0.0.2"; - sha256 = "214fff5ae2e4952cb8f15e7209be125e760b6d97fac4cd99b2e0592f790a1abf"; + version = "0.0.3.0"; + sha256 = "a0f70f3eb52d0c666ef2c6a68130d1e8db21c545fc9a7cd3a839dd538a347d5e"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base lawful ]; executableHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/githubuser/gdp#readme"; + homepage = "https://github.com/matt-noonan/gdp#readme"; description = "Reason about invariants and preconditions with ghosts of departed proofs"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "general-games" = callPackage - ({ mkDerivation, base, monad-loops, MonadRandom, random - , random-shuffle, stdenv + ({ mkDerivation, base, lib, monad-loops, MonadRandom, random + , random-shuffle }: mkDerivation { pname = "general-games"; @@ -13000,10 +14873,29 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/cgorski/general-games"; description = "Library supporting simulation of a number of games"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "generic-aeson" = callPackage + ({ mkDerivation, aeson, attoparsec, base, generic-deriving, lib + , mtl, tagged, text, unordered-containers, vector + }: + mkDerivation { + pname = "generic-aeson"; + version = "0.2.0.12"; + sha256 = "23b3dfbf26364d68f776f2922128f1955cf88ac6df81fba8f350b4976813799d"; + revision = "1"; + editedCabalFile = "0nd40p8iqr6bk7py9rblpis2s8i4p5wgg6kfp607mpp4y17xq1dr"; + libraryHaskellDepends = [ + aeson attoparsec base generic-deriving mtl tagged text + unordered-containers vector + ]; + doHaddock = false; + doCheck = false; + description = "Derivation of Aeson instances using GHC generics"; + license = lib.licenses.bsd3; }) {}; "generic-arbitrary" = callPackage - ({ mkDerivation, base, QuickCheck, stdenv }: + ({ mkDerivation, base, lib, QuickCheck }: mkDerivation { pname = "generic-arbitrary"; version = "0.1.0"; @@ -13012,35 +14904,63 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Generic implementation for QuickCheck's Arbitrary"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "generic-constraints" = callPackage + ({ mkDerivation, base, lib, template-haskell, th-abstraction }: + mkDerivation { + pname = "generic-constraints"; + version = "1.1.1.1"; + sha256 = "199c1374323914cd3e335404b2a1ab83127ed01bde489610fed81c046320a3c5"; + libraryHaskellDepends = [ base template-haskell th-abstraction ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/yairchu/generic-constraints"; + description = "Constraints via Generic"; + license = lib.licenses.bsd3; }) {}; "generic-data" = callPackage - ({ mkDerivation, base, base-orphans, contravariant - , show-combinators, stdenv + ({ mkDerivation, ap-normalize, base, base-orphans, Cabal + , cabal-doctest, contravariant, ghc-boot-th, lib, show-combinators }: mkDerivation { pname = "generic-data"; - version = "0.3.0.0"; - sha256 = "4c82444def5db474389ba66e47370dd1cd8c194d951bd40344ab3a5e77faa358"; + version = "0.9.2.0"; + sha256 = "8d08f36db9ea9867c82989ffb5baa10bc5a2f72596a92d9d6cecd5194476fc03"; + setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ - base base-orphans contravariant show-combinators + ap-normalize base base-orphans contravariant ghc-boot-th + show-combinators ]; doHaddock = false; doCheck = false; homepage = "https://github.com/Lysxia/generic-data#readme"; - description = "Utilities for GHC.Generics"; - license = stdenv.lib.licenses.mit; + description = "Deriving instances with GHC.Generics and related utilities"; + license = lib.licenses.mit; + }) {}; + "generic-data-surgery" = callPackage + ({ mkDerivation, base, first-class-families, generic-data, lib }: + mkDerivation { + pname = "generic-data-surgery"; + version = "0.3.0.0"; + sha256 = "3a26382cf585ce2a24c7fdccfdcd9282bcf8b0b2f4eac983d04b8107c2abe9b5"; + libraryHaskellDepends = [ base first-class-families generic-data ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/Lysxia/generic-data-surgery#readme"; + description = "Surgery for generic data types"; + license = lib.licenses.mit; }) {}; "generic-deriving" = callPackage - ({ mkDerivation, base, containers, ghc-prim, stdenv - , template-haskell, th-abstraction + ({ mkDerivation, base, containers, ghc-prim, lib, template-haskell + , th-abstraction }: mkDerivation { pname = "generic-deriving"; - version = "1.12.2"; - sha256 = "5688b85ff1e3484e3f6073a52f99624a41c8b01ddaab9fcec20afa242f33edc4"; + version = "1.14"; + sha256 = "d0abd5e423960b66867c6149c20b221b1351e3805d1bf787fc4efa3e7bb7cb02"; revision = "1"; - editedCabalFile = "0gr20ypr6s0183wmrhmia0zvpbn4dmfyr3wksrkrqj4i8nhj42fz"; + editedCabalFile = "0g17hk01sxv5lmrlnmwqhkk73y3dy3xhy7l9myyg5qnw7hm7iin9"; libraryHaskellDepends = [ base containers ghc-prim template-haskell th-abstraction ]; @@ -13048,113 +14968,172 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/dreixel/generic-deriving"; description = "Generic programming library for generalised deriving"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "generic-functor" = callPackage + ({ mkDerivation, ap-normalize, base, lib }: + mkDerivation { + pname = "generic-functor"; + version = "0.2.0.0"; + sha256 = "5bf2af816209a14040cd83e5dfb60e0edfd352fd9d15fef08b33dd888ed5327f"; + revision = "1"; + editedCabalFile = "1hgiwf6dajj4sp0a5px1c8yhm7abikmgn175m4cs22w5a72pi3dv"; + libraryHaskellDepends = [ ap-normalize base ]; + doHaddock = false; + doCheck = false; + homepage = "https://gitlab.com/lysxia/generic-functor"; + description = "Deriving generalized functors with GHC.Generics"; + license = lib.licenses.mit; }) {}; "generic-lens" = callPackage - ({ mkDerivation, base, profunctors, stdenv, tagged }: + ({ mkDerivation, base, generic-lens-core, lib, profunctors, text }: mkDerivation { pname = "generic-lens"; - version = "1.1.0.0"; - sha256 = "ecf2946dbf7c84cb80febdd6c0574668ba7213644662cc1157f392f9767936bb"; - libraryHaskellDepends = [ base profunctors tagged ]; + version = "2.1.0.0"; + sha256 = "cd4df37fc209108b6fd16ccb5b63d06e4f4588231c03b29d8862b4f7575eaae3"; + libraryHaskellDepends = [ + base generic-lens-core profunctors text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/kcsongor/generic-lens"; + description = "Generically derive traversals, lenses and prisms"; + license = lib.licenses.bsd3; + }) {}; + "generic-lens-core" = callPackage + ({ mkDerivation, base, indexed-profunctors, lib, text }: + mkDerivation { + pname = "generic-lens-core"; + version = "2.1.0.0"; + sha256 = "6584476b6974f887ba3e2bff26bc73121d16836ed92cfcea22421d776c164749"; + libraryHaskellDepends = [ base indexed-profunctors text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/kcsongor/generic-lens"; description = "Generically derive traversals, lenses and prisms"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "generic-monoid" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "generic-monoid"; + version = "0.1.0.1"; + sha256 = "cfd072ad70af41c1b94ac24e42e2635f37ed2a54e8f4be871be78b18b66b2adf"; + revision = "1"; + editedCabalFile = "17dfarnbv6si8rgajb3jqsbc4k1nxmvga2h1lhmpnq43n2fdkqkq"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + description = "Derive monoid instances for product types"; + license = lib.licenses.bsd3; + }) {}; + "generic-optics" = callPackage + ({ mkDerivation, base, generic-lens-core, lib, optics-core, text }: + mkDerivation { + pname = "generic-optics"; + version = "2.1.0.0"; + sha256 = "4550bb9dab629101113c99773cb0bb3e4796590502f8cc824d5cc5aed86d5f13"; + libraryHaskellDepends = [ + base generic-lens-core optics-core text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/kcsongor/generic-lens"; + description = "Generically derive traversals, lenses and prisms"; + license = lib.licenses.bsd3; }) {}; "generic-random" = callPackage - ({ mkDerivation, base, QuickCheck, stdenv }: + ({ mkDerivation, base, lib, QuickCheck }: mkDerivation { pname = "generic-random"; - version = "1.2.0.0"; - sha256 = "9b1e00d2f06b582695a34cfdb2d8b62b32f64152c6ed43f5c2d776e6e9aa148c"; - revision = "1"; - editedCabalFile = "1d0hx41r7yq2a86ydnfh2fv540ah8cz05l071s2z4wxcjw0ymyn4"; + version = "1.4.0.0"; + sha256 = "bcc973beb81e1cfc2f1c4c65c83782318e73b61f9cb59dac214cbafc5b583b8b"; libraryHaskellDepends = [ base QuickCheck ]; doHaddock = false; doCheck = false; homepage = "http://github.com/lysxia/generic-random"; - description = "Generic random generators"; - license = stdenv.lib.licenses.mit; + description = "Generic random generators for QuickCheck"; + license = lib.licenses.mit; }) {}; "generics-eot" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "generics-eot"; - version = "0.4"; - sha256 = "5abedc86df738c8ff7a8c6ca9ee97605406a1b6fadd4924fa93f7aacd2fece9b"; + version = "0.4.0.1"; + sha256 = "9be6de962c003365752b6fcb181ca9f443b68223c69c728c7991f5408d86df68"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://generics-eot.readthedocs.io/"; description = "A library for generic programming that aims to be easy to understand"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "generics-mrsop" = callPackage - ({ mkDerivation, base, containers, mtl, stdenv, template-haskell }: - mkDerivation { - pname = "generics-mrsop"; - version = "1.2.2"; - sha256 = "dbcb6e1d998a3412448a9d96d09ba3f3fcd760f54a492287048e885d2ddb9b76"; - libraryHaskellDepends = [ base containers mtl template-haskell ]; - doHaddock = false; - doCheck = false; - description = "Generic Programming with Mutually Recursive Sums of Products"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.bsd3; }) {}; "generics-sop" = callPackage - ({ mkDerivation, base, ghc-prim, sop-core, stdenv, template-haskell + ({ mkDerivation, base, ghc-prim, lib, sop-core, template-haskell + , th-abstraction }: mkDerivation { pname = "generics-sop"; - version = "0.4.0.1"; - sha256 = "dc99fa6c597b7ce256bdbdfc89fc615f26013e25256dd7e813f05b7845b61398"; + version = "0.5.1.1"; + sha256 = "81b7c38b5c2a1ae3c790b1707a0e2a2031430e33b3683f88e2daa5b59ae4c5d8"; libraryHaskellDepends = [ - base ghc-prim sop-core template-haskell + base ghc-prim sop-core template-haskell th-abstraction ]; doHaddock = false; doCheck = false; description = "Generic Programming using True Sums of Products"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "generics-sop-lens" = callPackage - ({ mkDerivation, base, generics-sop, lens, stdenv }: + ({ mkDerivation, base, generics-sop, lens, lib }: mkDerivation { pname = "generics-sop-lens"; - version = "0.1.2.1"; - sha256 = "4e49d4cc580d45e25e0abdeee12b1191ae75937af1c7ca03333979584a8a525c"; - revision = "6"; - editedCabalFile = "0j4j3kk2nsl5n5gp0vrzqdc5y9ly31b4nvhq0bpgcpzibvik7ssw"; + version = "0.2.0.1"; + sha256 = "7a86497e76d0c0585c9677b081732c2b4d9377370faf7fb54eee8b6cfe2587fa"; + revision = "1"; + editedCabalFile = "1y9v2imcrm8wyagv2d91x7zvdf358iz7460gqakhg9bgifjaylh1"; libraryHaskellDepends = [ base generics-sop lens ]; doHaddock = false; doCheck = false; homepage = "https://github.com/phadej/generics-sop-lens#readme"; description = "Lenses for types in generics-sop"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "geniplate-mirror" = callPackage + ({ mkDerivation, base, lib, mtl, template-haskell }: + mkDerivation { + pname = "geniplate-mirror"; + version = "0.7.8"; + sha256 = "4b3a64ab1f7a9994bc169a2c5e4866133d4d361b1f5c91056a4e9b52e8c184cf"; + libraryHaskellDepends = [ base mtl template-haskell ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/danr/geniplate"; + description = "Use Template Haskell to generate Uniplate-like functions"; + license = lib.licenses.bsd3; }) {}; "genvalidity" = callPackage - ({ mkDerivation, base, QuickCheck, stdenv, validity }: + ({ mkDerivation, base, lib, QuickCheck, random, validity }: mkDerivation { pname = "genvalidity"; - version = "0.7.0.0"; - sha256 = "81231459cfc02d6bc85e9c2b58f2fd25615cd5801ad1e6583460d8903dc65aae"; - libraryHaskellDepends = [ base QuickCheck validity ]; + version = "0.11.0.2"; + sha256 = "12c57bfa476146aa86304d4fd445086c6ca40615710819ebf9883d0b7a2b6d99"; + libraryHaskellDepends = [ base QuickCheck random validity ]; doHaddock = false; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "Testing utilities for the validity library"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "genvalidity-aeson" = callPackage ({ mkDerivation, aeson, base, genvalidity, genvalidity-scientific , genvalidity-text, genvalidity-unordered-containers - , genvalidity-vector, QuickCheck, stdenv, validity, validity-aeson + , genvalidity-vector, lib, QuickCheck, validity, validity-aeson }: mkDerivation { pname = "genvalidity-aeson"; - version = "0.2.0.2"; - sha256 = "d1244fea0a0a7cad4f783a72b9ff98c606131445a3f2fe9bced5194ff8a2e7b0"; + version = "0.3.0.0"; + sha256 = "5090c6fc63c1a059c98bf77f09df8578ecf9c9b43a63d0538e3f8ab1d33c1651"; libraryHaskellDepends = [ aeson base genvalidity genvalidity-scientific genvalidity-text genvalidity-unordered-containers genvalidity-vector QuickCheck @@ -13164,33 +15143,34 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "GenValidity support for aeson"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "genvalidity-bytestring" = callPackage - ({ mkDerivation, base, bytestring, genvalidity, QuickCheck, stdenv - , validity, validity-bytestring + ({ mkDerivation, base, bytestring, genvalidity, lib, QuickCheck + , random, validity, validity-bytestring }: mkDerivation { pname = "genvalidity-bytestring"; - version = "0.3.0.1"; - sha256 = "e8e71e9e6bd9841ab2fdbe6f50f819d3b2e6deef61d51a165dbb34a54a8383c9"; + version = "0.6.0.0"; + sha256 = "ad7c230e271fee65889dc3bfce3f1f5b23152b426ed168d38227f64bae642534"; libraryHaskellDepends = [ - base bytestring genvalidity QuickCheck validity validity-bytestring + base bytestring genvalidity QuickCheck random validity + validity-bytestring ]; doHaddock = false; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "GenValidity support for ByteString"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "genvalidity-containers" = callPackage - ({ mkDerivation, base, containers, genvalidity, QuickCheck, stdenv + ({ mkDerivation, base, containers, genvalidity, lib, QuickCheck , validity, validity-containers }: mkDerivation { pname = "genvalidity-containers"; - version = "0.5.1.1"; - sha256 = "cfb99413ded6bc2b11da5f78a905e731fc53b6addab751dfa4de1e10f9aaebfc"; + version = "0.9.0.0"; + sha256 = "738d5c628cdaa826f111f1419e63d979a48fa50f2a0088f191e8b80bcccc2d3d"; libraryHaskellDepends = [ base containers genvalidity QuickCheck validity validity-containers ]; @@ -13198,16 +15178,33 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "GenValidity support for containers"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "genvalidity-criterion" = callPackage + ({ mkDerivation, base, criterion, deepseq, genvalidity, lib + , QuickCheck + }: + mkDerivation { + pname = "genvalidity-criterion"; + version = "0.2.0.0"; + sha256 = "af0b5323d3d95b46cbe749b95c4229918e2f0a268a37661b645b29c5319e48e4"; + libraryHaskellDepends = [ + base criterion deepseq genvalidity QuickCheck + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/validity#readme"; + description = "Criterion benchmarks for generators"; + license = lib.licenses.mit; }) {}; "genvalidity-hspec" = callPackage ({ mkDerivation, base, genvalidity, genvalidity-property, hspec - , hspec-core, QuickCheck, stdenv, transformers, validity + , hspec-core, lib, QuickCheck, transformers, validity }: mkDerivation { pname = "genvalidity-hspec"; - version = "0.6.2.2"; - sha256 = "2e4fb7ce3a0e5ec4b2c52665b869eb4694fb1237f4ed309daa351e473542feda"; + version = "0.7.0.4"; + sha256 = "bb7e396266eb4508f32371a69f57e17f6e2664b29730b03af6f667610fe85229"; libraryHaskellDepends = [ base genvalidity genvalidity-property hspec hspec-core QuickCheck transformers validity @@ -13216,16 +15213,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "Standard spec's for GenValidity instances"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "genvalidity-hspec-aeson" = callPackage ({ mkDerivation, aeson, base, bytestring, deepseq, genvalidity - , genvalidity-hspec, hspec, QuickCheck, stdenv + , genvalidity-hspec, hspec, lib, QuickCheck }: mkDerivation { pname = "genvalidity-hspec-aeson"; - version = "0.3.0.1"; - sha256 = "a2d2e232b521f15bb4fdcf139621b9fdb6bad7de6cb888597d62a96dda50b274"; + version = "0.3.1.1"; + sha256 = "4b819bd1d95ef167fa186d3b73bc478e7daa2cafb2bc93f5a8b20c0ce5dc0bef"; libraryHaskellDepends = [ aeson base bytestring deepseq genvalidity genvalidity-hspec hspec QuickCheck @@ -13234,16 +15231,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://cs-syd.eu"; description = "Standard spec's for aeson-related instances"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "genvalidity-hspec-binary" = callPackage ({ mkDerivation, base, binary, deepseq, genvalidity - , genvalidity-hspec, hspec, QuickCheck, stdenv + , genvalidity-hspec, hspec, lib, QuickCheck }: mkDerivation { pname = "genvalidity-hspec-binary"; - version = "0.2.0.3"; - sha256 = "b99ba22694a36af01f6617463a38a35f305e55c46c52ee727302f2e1585ea9aa"; + version = "0.2.0.4"; + sha256 = "298fc601daa79b027704109fad4f6b7ac655d857963e0732c72aa10a53668f90"; libraryHaskellDepends = [ base binary deepseq genvalidity genvalidity-hspec hspec QuickCheck ]; @@ -13251,16 +15248,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "Standard spec's for binary-related Instances"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "genvalidity-hspec-cereal" = callPackage ({ mkDerivation, base, cereal, deepseq, genvalidity - , genvalidity-hspec, hspec, QuickCheck, stdenv + , genvalidity-hspec, hspec, lib, QuickCheck }: mkDerivation { pname = "genvalidity-hspec-cereal"; - version = "0.2.0.3"; - sha256 = "947ec34b6befa40f12eb16ad1d37aba97c5daf91efcbb25c564e8ae2ac887185"; + version = "0.2.0.4"; + sha256 = "ebb3a158e95dcd8c678127a9237a8a10a47845b829856d031d8a46c94ce9ce37"; libraryHaskellDepends = [ base cereal deepseq genvalidity genvalidity-hspec hspec QuickCheck ]; @@ -13268,17 +15265,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://cs-syd.eu"; description = "Standard spec's for cereal-related instances"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "genvalidity-hspec-hashable" = callPackage ({ mkDerivation, base, genvalidity, genvalidity-hspec - , genvalidity-property, hashable, hspec, QuickCheck, stdenv - , validity + , genvalidity-property, hashable, hspec, lib, QuickCheck, validity }: mkDerivation { pname = "genvalidity-hspec-hashable"; - version = "0.2.0.3"; - sha256 = "c61432a1899af3d916c7892fe16d5ed1a7fa30a4e24504a19f6bb90376546151"; + version = "0.2.0.5"; + sha256 = "3e4fa0bdbcebe04382ca94d27135e9f8628504502da199db775ef845f29e41c5"; libraryHaskellDepends = [ base genvalidity genvalidity-hspec genvalidity-property hashable hspec QuickCheck validity @@ -13287,33 +15283,86 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "Standard spec's for Hashable instances"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "genvalidity-hspec-optics" = callPackage - ({ mkDerivation, base, genvalidity, genvalidity-hspec, hspec - , microlens, QuickCheck, stdenv + ({ mkDerivation, base, genvalidity, genvalidity-hspec, hspec, lib + , microlens, QuickCheck }: mkDerivation { pname = "genvalidity-hspec-optics"; - version = "0.1.1.1"; - sha256 = "0a92cb7d1f98dc17634434f715473cc19596864146eee6256eaf86576c943788"; + version = "0.1.1.2"; + sha256 = "4801063637e36d57a03cfa6daa9c5cc6539ed0afeb9348e76d26c63fb0d109d6"; libraryHaskellDepends = [ base genvalidity genvalidity-hspec hspec microlens QuickCheck ]; doHaddock = false; doCheck = false; homepage = "http://cs-syd.eu"; - description = "Standard spec's for optics"; - license = stdenv.lib.licenses.mit; + description = "Standard spec's for lens"; + license = lib.licenses.mit; + }) {}; + "genvalidity-hspec-persistent" = callPackage + ({ mkDerivation, base, genvalidity, genvalidity-hspec, hspec, lib + , persistent, QuickCheck, text + }: + mkDerivation { + pname = "genvalidity-hspec-persistent"; + version = "0.0.0.1"; + sha256 = "a0cabb83ee7a18045655469a972add66f6e4fc81ba499dd47cab0b19a1e59f87"; + libraryHaskellDepends = [ + base genvalidity genvalidity-hspec hspec persistent QuickCheck text + ]; + doHaddock = false; + doCheck = false; + homepage = "http://cs-syd.eu"; + description = "Standard spec's for persistent-related instances"; + license = lib.licenses.mit; + }) {}; + "genvalidity-mergeful" = callPackage + ({ mkDerivation, base, containers, genvalidity + , genvalidity-containers, genvalidity-time, lib, mergeful + , QuickCheck + }: + mkDerivation { + pname = "genvalidity-mergeful"; + version = "0.2.0.0"; + sha256 = "18b1f338aa35566edd94db711d43e0989584d6a451dfbd66d6adc89e85d2f457"; + libraryHaskellDepends = [ + base containers genvalidity genvalidity-containers genvalidity-time + mergeful QuickCheck + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/mergeful#readme"; + license = lib.licenses.mit; + }) {}; + "genvalidity-mergeless" = callPackage + ({ mkDerivation, base, containers, genvalidity + , genvalidity-containers, genvalidity-time, lib, mergeless + , QuickCheck + }: + mkDerivation { + pname = "genvalidity-mergeless"; + version = "0.2.0.0"; + sha256 = "f048dfb0d032d39132e66fb518c8963d857faf94e67035ddcaac1f18ed0be70a"; + libraryHaskellDepends = [ + base containers genvalidity genvalidity-containers genvalidity-time + mergeless QuickCheck + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/mergeless#readme"; + license = lib.licenses.mit; }) {}; "genvalidity-path" = callPackage - ({ mkDerivation, base, genvalidity, path, QuickCheck, stdenv + ({ mkDerivation, base, genvalidity, lib, path, QuickCheck , validity-path }: mkDerivation { pname = "genvalidity-path"; - version = "0.3.0.2"; - sha256 = "00fc6d2f4d54cda700ad4af04efea62db002cab4fbb3ca8da4d20b1a03a340ba"; + version = "0.3.0.4"; + sha256 = "748482082e93cc93b3ab7fd33970ef43247be0805f63144ee11983cf7b2a606b"; libraryHaskellDepends = [ base genvalidity path QuickCheck validity-path ]; @@ -13321,33 +15370,52 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "GenValidity support for Path"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "genvalidity-persistent" = callPackage + ({ mkDerivation, base, containers, genvalidity + , genvalidity-containers, lib, persistent, QuickCheck + , validity-containers, validity-persistent + }: + mkDerivation { + pname = "genvalidity-persistent"; + version = "0.0.0.0"; + sha256 = "27381701f1f212691c1728507b38b6ab2bf4735a6d3b95cbc89ec2a0dce6f605"; + libraryHaskellDepends = [ + base containers genvalidity genvalidity-containers persistent + QuickCheck validity-containers validity-persistent + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/validity#readme"; + description = "GenValidity support for Persistent"; + license = lib.licenses.mit; }) {}; "genvalidity-property" = callPackage - ({ mkDerivation, base, genvalidity, hspec, QuickCheck, stdenv - , validity + ({ mkDerivation, base, genvalidity, hspec, lib, pretty-show + , QuickCheck, validity }: mkDerivation { pname = "genvalidity-property"; - version = "0.3.0.0"; - sha256 = "3aea3cc0833ee2ecdffe2da24e33770ef4e82fd0bfe5e66792d76357f1ac970d"; + version = "0.5.0.1"; + sha256 = "ffa8322bcb9608a1a1cb5cc04099a19f3ecfb507923dc799bf3b9c433e617f33"; libraryHaskellDepends = [ - base genvalidity hspec QuickCheck validity + base genvalidity hspec pretty-show QuickCheck validity ]; doHaddock = false; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "Standard properties for functions on `Validity` types"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "genvalidity-scientific" = callPackage - ({ mkDerivation, base, genvalidity, QuickCheck, scientific, stdenv + ({ mkDerivation, base, genvalidity, lib, QuickCheck, scientific , validity, validity-scientific }: mkDerivation { pname = "genvalidity-scientific"; - version = "0.2.1.0"; - sha256 = "af11d48c53455eb250e68c6cb4f6e8159ddc16fb635879fc2973d57d8bd5903d"; + version = "0.2.1.1"; + sha256 = "a9b76332cf0620df26de3ca690330be290cd17b244f94555a9c7a7531f558cea"; libraryHaskellDepends = [ base genvalidity QuickCheck scientific validity validity-scientific ]; @@ -13355,68 +15423,174 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "GenValidity support for Scientific"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "genvalidity-text" = callPackage - ({ mkDerivation, array, base, genvalidity, QuickCheck, stdenv, text - , validity, validity-text + "genvalidity-sydtest" = callPackage + ({ mkDerivation, base, genvalidity, lib, pretty-show, QuickCheck + , sydtest, validity }: mkDerivation { - pname = "genvalidity-text"; - version = "0.5.1.0"; - sha256 = "ef3d7ebe85cf5ce10675f350dd80dfdb3c3f700e109170d0c4929afdbfe8ee48"; + pname = "genvalidity-sydtest"; + version = "0.0.0.0"; + sha256 = "40310e2c2b582f02cce00c0b685b0403fb1d1dbb6e8025dce33fd8d86583f9c9"; libraryHaskellDepends = [ - array base genvalidity QuickCheck text validity validity-text + base genvalidity pretty-show QuickCheck sydtest validity ]; doHaddock = false; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; - description = "GenValidity support for Text"; - license = stdenv.lib.licenses.mit; + description = "Standard properties for functions on `Validity` types for the sydtest framework"; + license = lib.licenses.mit; }) {}; - "genvalidity-time" = callPackage - ({ mkDerivation, base, genvalidity, QuickCheck, stdenv, time - , validity-time + "genvalidity-sydtest-aeson" = callPackage + ({ mkDerivation, aeson, base, bytestring, deepseq, genvalidity + , genvalidity-sydtest, lib, QuickCheck, sydtest }: mkDerivation { - pname = "genvalidity-time"; - version = "0.2.1.1"; - sha256 = "c555c206edddbd70355b295ccf9ff053463c137735c4aebcc340091f6d6b7874"; + pname = "genvalidity-sydtest-aeson"; + version = "0.0.0.0"; + sha256 = "7f61b3960bd3a57c3f9365f1c2b91fbafb2d5a2496dc6e43f2884203968df1d2"; libraryHaskellDepends = [ - base genvalidity QuickCheck time validity-time + aeson base bytestring deepseq genvalidity genvalidity-sydtest + QuickCheck sydtest ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/NorfairKing/validity#readme"; - description = "GenValidity support for time"; - license = stdenv.lib.licenses.mit; + homepage = "http://cs-syd.eu"; + description = "Standard spec's for aeson-related instances in sydtest"; + license = lib.licenses.mit; }) {}; - "genvalidity-unordered-containers" = callPackage - ({ mkDerivation, base, genvalidity, hashable, QuickCheck, stdenv - , unordered-containers, validity, validity-unordered-containers + "genvalidity-sydtest-hashable" = callPackage + ({ mkDerivation, base, genvalidity, genvalidity-sydtest, hashable + , lib, QuickCheck, sydtest, validity }: mkDerivation { - pname = "genvalidity-unordered-containers"; - version = "0.2.0.4"; - sha256 = "78502e46cc717aba80ee9c8f6778b30c7e4e583361b65b3a43f4ad1a4be57b66"; + pname = "genvalidity-sydtest-hashable"; + version = "0.0.0.0"; + sha256 = "d580d8f5103febdc818dad25e65970aebd5cfa66a18140becc9e59aa92d12346"; libraryHaskellDepends = [ - base genvalidity hashable QuickCheck unordered-containers validity - validity-unordered-containers + base genvalidity genvalidity-sydtest hashable QuickCheck sydtest + validity + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/validity#readme"; + description = "Standard spec's for Hashable instances for sydtest"; + license = lib.licenses.mit; + }) {}; + "genvalidity-sydtest-lens" = callPackage + ({ mkDerivation, base, genvalidity, genvalidity-sydtest, lib + , microlens, QuickCheck, sydtest + }: + mkDerivation { + pname = "genvalidity-sydtest-lens"; + version = "0.0.0.0"; + sha256 = "727b7e42dba391c46a1bdd5887d1c1c231e9f22023c2d51e347980a32e581cb9"; + libraryHaskellDepends = [ + base genvalidity genvalidity-sydtest microlens QuickCheck sydtest + ]; + doHaddock = false; + doCheck = false; + homepage = "http://cs-syd.eu"; + description = "Standard spec's for lens for sydtest"; + license = lib.licenses.mit; + }) {}; + "genvalidity-sydtest-persistent" = callPackage + ({ mkDerivation, base, genvalidity, genvalidity-sydtest, lib + , persistent, QuickCheck, sydtest, text + }: + mkDerivation { + pname = "genvalidity-sydtest-persistent"; + version = "0.0.0.1"; + sha256 = "95f1f7ac344ececf42e78a5b0f13e4842c77c9bef71ec91721eb5646d121c71f"; + libraryHaskellDepends = [ + base genvalidity genvalidity-sydtest persistent QuickCheck sydtest + text + ]; + doHaddock = false; + doCheck = false; + homepage = "http://cs-syd.eu"; + description = "Standard spec's for persistent-related instances for sydtest"; + license = lib.licenses.mit; + }) {}; + "genvalidity-text" = callPackage + ({ mkDerivation, array, base, genvalidity, lib, QuickCheck, random + , text, validity, validity-text + }: + mkDerivation { + pname = "genvalidity-text"; + version = "0.7.0.2"; + sha256 = "2cc93192529d5d15fce3ade12d3bc68a24c85029bfefa2e5fe528de71c464f5c"; + libraryHaskellDepends = [ + array base genvalidity QuickCheck random text validity + validity-text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/validity#readme"; + description = "GenValidity support for Text"; + license = lib.licenses.mit; + }) {}; + "genvalidity-time" = callPackage + ({ mkDerivation, base, genvalidity, lib, QuickCheck, time + , validity-time + }: + mkDerivation { + pname = "genvalidity-time"; + version = "0.3.0.0"; + sha256 = "dc6e95b4b9e7a6b771d7726faaec63ddc0bb737540361170b874872af9d349fd"; + libraryHaskellDepends = [ + base genvalidity QuickCheck time validity-time + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/validity#readme"; + description = "GenValidity support for time"; + license = lib.licenses.mit; + }) {}; + "genvalidity-typed-uuid" = callPackage + ({ mkDerivation, base, genvalidity, genvalidity-uuid, lib + , QuickCheck, typed-uuid + }: + mkDerivation { + pname = "genvalidity-typed-uuid"; + version = "0.0.0.2"; + sha256 = "20101cfa414b1ef167c448c9a45155a13bfe3ab871a989df0de10a5b43f0029a"; + libraryHaskellDepends = [ + base genvalidity genvalidity-uuid QuickCheck typed-uuid + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/typed-uuid#readme"; + description = "Generators for Phantom-Typed version of UUID"; + license = lib.licenses.mit; + }) {}; + "genvalidity-unordered-containers" = callPackage + ({ mkDerivation, base, genvalidity, hashable, lib, QuickCheck + , unordered-containers, validity, validity-unordered-containers + }: + mkDerivation { + pname = "genvalidity-unordered-containers"; + version = "0.3.0.1"; + sha256 = "c23e49c467a63de1470527d636f981f533e2054b5b951ba0498c90648a90c885"; + libraryHaskellDepends = [ + base genvalidity hashable QuickCheck unordered-containers validity + validity-unordered-containers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "GenValidity support for unordered-containers"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "genvalidity-uuid" = callPackage - ({ mkDerivation, base, genvalidity, QuickCheck, stdenv, uuid - , validity, validity-uuid + ({ mkDerivation, base, genvalidity, lib, QuickCheck, uuid, validity + , validity-uuid }: mkDerivation { pname = "genvalidity-uuid"; - version = "0.1.0.2"; - sha256 = "d1354bdfc0a75a1f228cfed22cd0edb0cc13a925e4b2514a634d56eb5b53f412"; + version = "0.1.0.4"; + sha256 = "59d8c70467439e3917e8d42c9995de1741369944383bea2495ba62b671b2340a"; libraryHaskellDepends = [ base genvalidity QuickCheck uuid validity validity-uuid ]; @@ -13424,16 +15598,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "GenValidity support for UUID"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "genvalidity-vector" = callPackage - ({ mkDerivation, base, genvalidity, QuickCheck, stdenv, validity + ({ mkDerivation, base, genvalidity, lib, QuickCheck, validity , validity-vector, vector }: mkDerivation { pname = "genvalidity-vector"; - version = "0.2.0.3"; - sha256 = "b3c42019fea54c0da0b0947b01cad510679b3b6c2dc55a43326806f9a02e3c98"; + version = "0.3.0.1"; + sha256 = "20ef74aae55af8c8e2d675d447aef132e8723b4297f0d3cbf0bf048e44d77578"; libraryHaskellDepends = [ base genvalidity QuickCheck validity validity-vector vector ]; @@ -13441,34 +15615,34 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "GenValidity support for vector"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "geojson" = callPackage - ({ mkDerivation, aeson, base, containers, deepseq, lens, scientific - , semigroups, stdenv, text, transformers, validation + ({ mkDerivation, aeson, base, containers, deepseq, lens, lib + , scientific, semigroups, text, transformers, validation, vector }: mkDerivation { pname = "geojson"; - version = "3.0.4"; - sha256 = "85b30c38948bbca401b53117989aa432de94cb3096fecf51b78f237f164bd336"; + version = "4.0.2"; + sha256 = "c634eb9879b78474a979a5eab0233a5d5a92e242262564665f0619d82e794b33"; libraryHaskellDepends = [ aeson base containers deepseq lens scientific semigroups text - transformers validation + transformers validation vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/indicatrix/hs-geojson"; + homepage = "https://github.com/zellige/hs-geojson"; description = "A thin GeoJSON Layer above the aeson library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "getopt-generics" = callPackage - ({ mkDerivation, base, base-compat, base-orphans, generics-sop - , stdenv, tagged + ({ mkDerivation, base, base-compat, base-orphans, generics-sop, lib + , tagged }: mkDerivation { pname = "getopt-generics"; - version = "0.13.0.3"; - sha256 = "ab05824897afa59304fd653685b5d9580cc91b1d6783d30234a03dbf9dee0288"; + version = "0.13.0.4"; + sha256 = "f9458ffc13a8767ca8026a2c9dfc294ce2b5ca94148d5286e368bc1c2c9b5fe7"; libraryHaskellDepends = [ base base-compat base-orphans generics-sop tagged ]; @@ -13476,11 +15650,43 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/soenkehahn/getopt-generics#readme"; description = "Create command line interfaces with ease"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "ghc-byteorder" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "ghc-byteorder"; + version = "4.11.0.0.10"; + sha256 = "86e50a89798181db4f44ec3848fc52940c73098e88549a351ceb54fefc691fb6"; + revision = "1"; + editedCabalFile = "1qwx6569079a8viq2plkpc1wlqdz8syys6hvx68m051a7zvdwzyl"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + description = "\"GHC.ByteOrder\" API Compatibility Layer"; + license = lib.licenses.bsd3; + }) {}; + "ghc-check" = callPackage + ({ mkDerivation, base, containers, directory, filepath, ghc + , ghc-paths, lib, process, safe-exceptions, template-haskell + , th-compat, transformers + }: + mkDerivation { + pname = "ghc-check"; + version = "0.5.0.5"; + sha256 = "5153a9a1312613dda2fa735d7e58b3ab9792b143d09122792322267172da8556"; + libraryHaskellDepends = [ + base containers directory filepath ghc ghc-paths process + safe-exceptions template-haskell th-compat transformers + ]; + doHaddock = false; + doCheck = false; + description = "detect mismatches between compile-time and run-time versions of the ghc api"; + license = lib.licenses.bsd3; }) {}; "ghc-core" = callPackage - ({ mkDerivation, base, colorize-haskell, directory, filepath - , pcre-light, process, stdenv + ({ mkDerivation, base, colorize-haskell, directory, filepath, lib + , pcre-light, process }: mkDerivation { pname = "ghc-core"; @@ -13495,16 +15701,35 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/shachaf/ghc-core"; description = "Display GHC's core and assembly output in a pager"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "ghc-events" = callPackage + ({ mkDerivation, array, base, binary, bytestring, containers, lib + , text, vector + }: + mkDerivation { + pname = "ghc-events"; + version = "0.17.0"; + sha256 = "8cc5b380cdf821b396c237cde6dcf0713d3d355733a9a8fac231a42113d52c15"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + array base binary bytestring containers text vector + ]; + executableHaskellDepends = [ base containers ]; + doHaddock = false; + doCheck = false; + description = "Library and tool for parsing .eventlog files from GHC"; + license = lib.licenses.bsd3; }) {}; "ghc-exactprint" = callPackage ({ mkDerivation, base, bytestring, containers, directory, filepath - , free, ghc, ghc-boot, ghc-paths, mtl, stdenv, syb + , free, ghc, ghc-boot, ghc-paths, lib, mtl, syb }: mkDerivation { pname = "ghc-exactprint"; - version = "0.5.8.2"; - sha256 = "961dde178df96c123d12a362f64f7ef43228176fd3a1b876a8fecc75df8694a3"; + version = "0.6.4"; + sha256 = "fc3e5a5b01b92a8b8cd790d71fe73f24922110ac1d0a50c5bfa40993d457cb28"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -13514,31 +15739,105 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "ExactPrint for GHC"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "ghc-lib" = callPackage + ({ mkDerivation, alex, array, base, binary, bytestring, containers + , deepseq, directory, filepath, ghc-lib-parser, ghc-prim, happy + , hpc, lib, pretty, process, rts, time, transformers, unix + }: + mkDerivation { + pname = "ghc-lib"; + version = "8.10.5.20210606"; + sha256 = "5ac62266ddccd462de8fb3cd2188f8c49d14e1a47a82a7830aed0e4dc895822e"; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + array base binary bytestring containers deepseq directory filepath + ghc-lib-parser ghc-prim hpc pretty process rts time transformers + unix + ]; + libraryToolDepends = [ alex happy ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/digital-asset/ghc-lib"; + description = "The GHC API, decoupled from GHC versions"; + license = lib.licenses.bsd3; + }) {}; + "ghc-lib-parser" = callPackage + ({ mkDerivation, alex, array, base, binary, bytestring, containers + , deepseq, directory, filepath, ghc-prim, happy, hpc, lib, pretty + , process, time, transformers, unix + }: + mkDerivation { + pname = "ghc-lib-parser"; + version = "8.10.5.20210606"; + sha256 = "8ad82f79254e62b8d577137b6b9506b151ffdb62be012e4d5c8fe33d13c11a5f"; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + array base binary bytestring containers deepseq directory filepath + ghc-prim hpc pretty process time transformers unix + ]; + libraryToolDepends = [ alex happy ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/digital-asset/ghc-lib"; + description = "The GHC API, decoupled from GHC versions"; + license = lib.licenses.bsd3; + }) {}; + "ghc-lib-parser-ex" = callPackage + ({ mkDerivation, base, bytestring, containers, ghc, ghc-boot + , ghc-boot-th, lib, uniplate + }: + mkDerivation { + pname = "ghc-lib-parser-ex"; + version = "8.10.0.21"; + sha256 = "779b69bbd0796d52169415b344434fa57ccfb1548b369cb42ba3c6daf0b1d97a"; + libraryHaskellDepends = [ + base bytestring containers ghc ghc-boot ghc-boot-th uniplate + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/shayne-fletcher/ghc-lib-parser-ex#readme"; + description = "Algorithms on GHC parse trees"; + license = lib.licenses.bsd3; + }) {}; + "ghc-parser" = callPackage + ({ mkDerivation, base, cpphs, ghc, happy, lib }: + mkDerivation { + pname = "ghc-parser"; + version = "0.2.3.0"; + sha256 = "96be38d7a94e6e6272d7359a25cdca41477dcc5c04980c1bb9137fc18d1da9ea"; + libraryHaskellDepends = [ base ghc ]; + libraryToolDepends = [ cpphs happy ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/gibiansky/IHaskell"; + description = "Haskell source parser from GHC"; + license = lib.licenses.mit; }) {}; "ghc-paths" = callPackage - ({ mkDerivation, base, Cabal, directory, stdenv }: + ({ mkDerivation, base, Cabal, directory, lib }: mkDerivation { pname = "ghc-paths"; - version = "0.1.0.9"; - sha256 = "afa68fb86123004c37c1dc354286af2d87a9dcfb12ddcb80e8bd0cd55bc87945"; - revision = "4"; - editedCabalFile = "1fp0jyvi6prqsv0dxn010c7q4mmiwlcy1xk6ppd4d539adxxy67d"; + version = "0.1.0.12"; + sha256 = "6ecbe676d073cb07989c61ce4c5709c4e67cbefdd2d55a4095f9388b6fe2c484"; + revision = "2"; + editedCabalFile = "07f81larq1ddxq2m2vyq05sdhfmz0whf2c3i5cdq57pkhijxppxg"; setupHaskellDepends = [ base Cabal directory ]; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; description = "Knowledge of GHC's installation directories"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "ghc-prof" = callPackage - ({ mkDerivation, attoparsec, base, containers, scientific, stdenv + ({ mkDerivation, attoparsec, base, containers, lib, scientific , text, time }: mkDerivation { pname = "ghc-prof"; - version = "1.4.1.5"; - sha256 = "e42d1acd9947c1396adcf1ae3a0627144884af5cf13176fb09cce0e9bcfbfe32"; + version = "1.4.1.8"; + sha256 = "571802a861856ff969c1ba61a8e620f6ef64bdbccff4e2762bb931a3008d660a"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -13548,113 +15847,158 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/maoe/ghc-prof"; description = "Library for parsing GHC time and allocation profiling reports"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "ghc-source-gen" = callPackage + ({ mkDerivation, base, ghc, lib }: + mkDerivation { + pname = "ghc-source-gen"; + version = "0.4.1.0"; + sha256 = "9ea009d00640d818d589a33220af7a89c6c261024940d8964db2e6bbd0352d27"; + libraryHaskellDepends = [ base ghc ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/google/ghc-source-gen#readme"; + description = "Constructs Haskell syntax trees for the GHC API"; + license = lib.licenses.bsd3; }) {}; "ghc-syntax-highlighter" = callPackage - ({ mkDerivation, base, ghc, stdenv, text }: + ({ mkDerivation, base, ghc-lib-parser, lib, text }: mkDerivation { pname = "ghc-syntax-highlighter"; - version = "0.0.3.0"; - sha256 = "a137f484740f4eee967fbc8d8366e053e52e073b948ffb3001b4e1227adeec1c"; + version = "0.0.6.0"; + sha256 = "4a2ab2a8a4a6c8536bf2aba0823bfd7fdb41ebae7a47423975690c4f0827b5b7"; enableSeparateDataOutput = true; - libraryHaskellDepends = [ base ghc text ]; + libraryHaskellDepends = [ base ghc-lib-parser text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mrkkrp/ghc-syntax-highlighter"; description = "Syntax highlighter for Haskell using lexer of GHC itself"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "ghc-tcplugins-extra" = callPackage - ({ mkDerivation, base, ghc, stdenv }: + ({ mkDerivation, base, ghc, lib }: mkDerivation { pname = "ghc-tcplugins-extra"; - version = "0.3"; - sha256 = "30acfd21d590809c16d990512fc8fcb98361ec540a76438233bd8aa23e82374c"; - revision = "1"; - editedCabalFile = "0x2d4bp5lhyfrqjshmgbirdn2ihc057a8a6khqmz91jj9zlhf7vb"; + version = "0.4.2"; + sha256 = "08cc264d179d55d2b41578f4ae37945a8243583360b9e568ae3da2f519c3adbd"; libraryHaskellDepends = [ base ghc ]; doHaddock = false; doCheck = false; homepage = "http://github.com/clash-lang/ghc-tcplugins-extra"; description = "Utilities for writing GHC type-checker plugins"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; + }) {}; + "ghc-trace-events" = callPackage + ({ mkDerivation, base, bytestring, lib, text }: + mkDerivation { + pname = "ghc-trace-events"; + version = "0.1.2.3"; + sha256 = "0d1f794a021f035cff2393ba42db5d54fce5fdfa76bd2f3aba7d334b3f8ca286"; + libraryHaskellDepends = [ base bytestring text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/maoe/ghc-trace-events"; + description = "Faster traceEvent and traceMarker, and binary object logging for eventlog"; + license = lib.licenses.bsd3; }) {}; "ghc-typelits-extra" = callPackage - ({ mkDerivation, base, ghc, ghc-prim, ghc-tcplugins-extra - , ghc-typelits-knownnat, ghc-typelits-natnormalise, integer-gmp - , stdenv, transformers + ({ mkDerivation, base, containers, ghc, ghc-prim + , ghc-tcplugins-extra, ghc-typelits-knownnat + , ghc-typelits-natnormalise, integer-gmp, lib, transformers }: mkDerivation { pname = "ghc-typelits-extra"; - version = "0.3"; - sha256 = "47de9b6abbee64586c819616597c3768bea61b7aedb7f1c6d3231a163b6413ce"; + version = "0.4.3"; + sha256 = "286cdd62ea48e84f3c8f0b0602f388dc97baa7ccb9743dbf602034610106e419"; libraryHaskellDepends = [ - base ghc ghc-prim ghc-tcplugins-extra ghc-typelits-knownnat - ghc-typelits-natnormalise integer-gmp transformers + base containers ghc ghc-prim ghc-tcplugins-extra + ghc-typelits-knownnat ghc-typelits-natnormalise integer-gmp + transformers ]; doHaddock = false; doCheck = false; homepage = "http://www.clash-lang.org/"; description = "Additional type-level operations on GHC.TypeLits.Nat"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; }) {}; "ghc-typelits-knownnat" = callPackage - ({ mkDerivation, base, ghc, ghc-tcplugins-extra - , ghc-typelits-natnormalise, stdenv, template-haskell, transformers + ({ mkDerivation, base, ghc, ghc-prim, ghc-tcplugins-extra + , ghc-typelits-natnormalise, lib, template-haskell, transformers }: mkDerivation { pname = "ghc-typelits-knownnat"; - version = "0.6"; - sha256 = "4b529b27b226cc3df47d95cb8f0a145ed0c25486dec4f99be8dcd700ddc7f237"; + version = "0.7.6"; + sha256 = "3bb5efad97aeb0152d8b21056a3f43b9158d6941ff124300898217e120f0a482"; libraryHaskellDepends = [ - base ghc ghc-tcplugins-extra ghc-typelits-natnormalise + base ghc ghc-prim ghc-tcplugins-extra ghc-typelits-natnormalise template-haskell transformers ]; doHaddock = false; doCheck = false; homepage = "http://clash-lang.org/"; description = "Derive KnownNat constraints from other KnownNat constraints"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; }) {}; "ghc-typelits-natnormalise" = callPackage - ({ mkDerivation, base, ghc, ghc-tcplugins-extra, integer-gmp - , stdenv, transformers + ({ mkDerivation, base, containers, ghc, ghc-tcplugins-extra + , integer-gmp, lib, transformers }: mkDerivation { pname = "ghc-typelits-natnormalise"; - version = "0.6.2"; - sha256 = "801ceb41442dfa992fad04c64f2989d1d701bcfe0874a55aa8d250e63c1a4311"; + version = "0.7.6"; + sha256 = "7da56bc189f5e5e74ecb48c3ef4ac5cd5df08213658989a237af54547804a725"; libraryHaskellDepends = [ - base ghc ghc-tcplugins-extra integer-gmp transformers + base containers ghc ghc-tcplugins-extra integer-gmp transformers ]; doHaddock = false; doCheck = false; homepage = "http://www.clash-lang.org/"; description = "GHC typechecker plugin for types of kind GHC.TypeLits.Nat"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; + }) {}; + "ghc-typelits-presburger" = callPackage + ({ mkDerivation, base, containers, ghc, ghc-tcplugins-extra, lib + , mtl, pretty, reflection, syb, transformers + }: + mkDerivation { + pname = "ghc-typelits-presburger"; + version = "0.6.0.0"; + sha256 = "9d0592485e803604f85b81a8b22f59e4759483d745f42408b293da6bfbb95d22"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base containers ghc ghc-tcplugins-extra mtl pretty reflection syb + transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/konn/ghc-typelits-presburger#readme"; + description = "Presburger Arithmetic Solver for GHC Type-level natural numbers"; + license = lib.licenses.bsd3; }) {}; "ghci-hexcalc" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, binary, lib }: mkDerivation { pname = "ghci-hexcalc"; - version = "0.1.0.1"; - sha256 = "429f96f698e7edc26f8b74ce4abdb9c8ee31e64ac18309a203b032363e2790d7"; - libraryHaskellDepends = [ base ]; + version = "0.1.1.0"; + sha256 = "701ee465d6f1d4b815782954fb68bd058b257b38773b07e89f2ee01c38ea53ce"; + libraryHaskellDepends = [ base binary ]; doHaddock = false; doCheck = false; homepage = "https://github.com/takenobu-hs/ghci-hexcalc"; description = "GHCi as a Hex Calculator interactive"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "ghcid" = callPackage ({ mkDerivation, ansi-terminal, base, cmdargs, containers - , directory, extra, filepath, fsnotify, process, stdenv - , terminal-size, time, unix + , directory, extra, filepath, fsnotify, lib, process, terminal-size + , time, unix }: mkDerivation { pname = "ghcid"; - version = "0.7.1"; - sha256 = "a73719b5d03c24726b60d1cd4cd7379d7e50690c9b738b760149c450763bc31a"; + version = "0.8.7"; + sha256 = "78c9ec4884d7d0b7e301df49b102c9839d0c8a5c7a10689f29d94ae5e60d0c7b"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -13668,10 +16012,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/ndmitchell/ghcid#readme"; description = "GHCi based bare bones IDE"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "ghcjs-codemirror" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "ghcjs-codemirror"; version = "0.0.0.2"; @@ -13682,10 +16026,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/ghcjs/CodeMirror"; description = "Installs CodeMirror JavaScript files"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "ghost-buster" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "ghost-buster"; version = "0.1.1.0"; @@ -13695,18 +16039,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/Lazersmoke/ghost-buster#readme"; description = "Existential type utilites"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "gi-atk" = callPackage ({ mkDerivation, atk, base, bytestring, Cabal, containers, gi-glib , gi-gobject, haskell-gi, haskell-gi-base, haskell-gi-overloading - , stdenv, text, transformers + , lib, text, transformers }: mkDerivation { pname = "gi-atk"; - version = "2.0.15"; - sha256 = "89753b4517e77ea956dcfd1294b4b98032c6e50df912e28c9a796d2b825fbfee"; - setupHaskellDepends = [ base Cabal haskell-gi ]; + version = "2.0.23"; + sha256 = "aeeaed3cc42cc858198b1bf47aee372beb0254423ded008fd0918cd131a3fc17"; + setupHaskellDepends = [ base Cabal gi-glib gi-gobject haskell-gi ]; libraryHaskellDepends = [ base bytestring containers gi-glib gi-gobject haskell-gi haskell-gi-base haskell-gi-overloading text transformers @@ -13716,17 +16060,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/haskell-gi/haskell-gi"; description = "Atk bindings"; - license = stdenv.lib.licenses.lgpl21; + license = lib.licenses.lgpl21Only; }) {inherit (pkgs) atk;}; "gi-cairo" = callPackage ({ mkDerivation, base, bytestring, Cabal, cairo, containers - , haskell-gi, haskell-gi-base, haskell-gi-overloading, stdenv, text + , haskell-gi, haskell-gi-base, haskell-gi-overloading, lib, text , transformers }: mkDerivation { pname = "gi-cairo"; - version = "1.0.17"; - sha256 = "5dbda70a038a93cb07130597407de9cde1436603beca3f2a0a6b43953c55a7ab"; + version = "1.0.25"; + sha256 = "84ede13d6f4f6bc61040550e17832b128902fa744d087a0c57ccc9d591476e79"; setupHaskellDepends = [ base Cabal haskell-gi ]; libraryHaskellDepends = [ base bytestring containers haskell-gi haskell-gi-base @@ -13741,19 +16085,69 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; ''; homepage = "https://github.com/haskell-gi/haskell-gi"; description = "Cairo bindings"; - license = stdenv.lib.licenses.lgpl21; + license = lib.licenses.lgpl21Only; }) {inherit (pkgs) cairo;}; + "gi-dbusmenu" = callPackage + ({ mkDerivation, base, bytestring, Cabal, containers, gi-glib + , gi-gobject, haskell-gi, haskell-gi-base, haskell-gi-overloading + , lib, libdbusmenu, text, transformers + }: + mkDerivation { + pname = "gi-dbusmenu"; + version = "0.4.9"; + sha256 = "23e0af7dbeca04518a1023fc80d825506b305f1c2d724c15b36248ce4eec4bd8"; + setupHaskellDepends = [ base Cabal gi-glib gi-gobject haskell-gi ]; + libraryHaskellDepends = [ + base bytestring containers gi-glib gi-gobject haskell-gi + haskell-gi-base haskell-gi-overloading text transformers + ]; + libraryPkgconfigDepends = [ libdbusmenu ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell-gi/haskell-gi"; + description = "Dbusmenu bindings"; + license = lib.licenses.lgpl21Only; + }) {inherit (pkgs) libdbusmenu;}; + "gi-dbusmenugtk3" = callPackage + ({ mkDerivation, base, bytestring, Cabal, containers, gi-atk + , gi-dbusmenu, gi-gdk, gi-gdkpixbuf, gi-glib, gi-gobject, gi-gtk + , gtk3, haskell-gi, haskell-gi-base, haskell-gi-overloading, lib + , libdbusmenu-gtk3, text, transformers + }: + mkDerivation { + pname = "gi-dbusmenugtk3"; + version = "0.4.10"; + sha256 = "ff7cf8dc5fea48572199dd5438a1eac8c6d1c417e435d882b5c6a218a9d807c3"; + setupHaskellDepends = [ + base Cabal gi-atk gi-dbusmenu gi-gdk gi-gdkpixbuf gi-glib + gi-gobject gi-gtk haskell-gi + ]; + libraryHaskellDepends = [ + base bytestring containers gi-atk gi-dbusmenu gi-gdk gi-gdkpixbuf + gi-glib gi-gobject gi-gtk haskell-gi haskell-gi-base + haskell-gi-overloading text transformers + ]; + libraryPkgconfigDepends = [ gtk3 libdbusmenu-gtk3 ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell-gi/haskell-gi"; + description = "DbusmenuGtk bindings"; + license = lib.licenses.lgpl21Only; + }) {inherit (pkgs) gtk3; inherit (pkgs) libdbusmenu-gtk3;}; "gi-gdk" = callPackage ({ mkDerivation, base, bytestring, Cabal, containers, gi-cairo , gi-gdkpixbuf, gi-gio, gi-glib, gi-gobject, gi-pango, gtk3 - , haskell-gi, haskell-gi-base, haskell-gi-overloading, stdenv, text + , haskell-gi, haskell-gi-base, haskell-gi-overloading, lib, text , transformers }: mkDerivation { pname = "gi-gdk"; - version = "3.0.16"; - sha256 = "7eb0aa493d268cd040c7ff70ad09d7bf7787e0e7619617ba220b88eafe68e34a"; - setupHaskellDepends = [ base Cabal haskell-gi ]; + version = "3.0.24"; + sha256 = "5dbae2a0a5a6bd07314dc902a4cb747c4fc7f694880b30e05f76c87fb6f6549f"; + setupHaskellDepends = [ + base Cabal gi-cairo gi-gdkpixbuf gi-gio gi-glib gi-gobject gi-pango + haskell-gi + ]; libraryHaskellDepends = [ base bytestring containers gi-cairo gi-gdkpixbuf gi-gio gi-glib gi-gobject gi-pango haskell-gi haskell-gi-base @@ -13764,39 +16158,65 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/haskell-gi/haskell-gi"; description = "Gdk bindings"; - license = stdenv.lib.licenses.lgpl21; - }) {gtk3 = pkgs.gnome3.gtk;}; + license = lib.licenses.lgpl21Only; + }) {inherit (pkgs) gtk3;}; "gi-gdkpixbuf" = callPackage - ({ mkDerivation, base, bytestring, Cabal, containers, gdk_pixbuf - , gi-gio, gi-glib, gi-gobject, haskell-gi, haskell-gi-base - , haskell-gi-overloading, stdenv, text, transformers + ({ mkDerivation, base, bytestring, Cabal, containers, gdk-pixbuf + , gi-gio, gi-glib, gi-gmodule, gi-gobject, haskell-gi + , haskell-gi-base, haskell-gi-overloading, lib, text, transformers }: mkDerivation { pname = "gi-gdkpixbuf"; - version = "2.0.18"; - sha256 = "f232978dde69f4b2a2459ffb5280c33c2a8a079b3a1ce2f34bd9477dc0be3ead"; - setupHaskellDepends = [ base Cabal haskell-gi ]; + version = "2.0.26"; + sha256 = "48a70b9caace29fa3287f95ae647235a618325c4a2f0d43206f6afe0b2bf21bc"; + setupHaskellDepends = [ + base Cabal gi-gio gi-glib gi-gmodule gi-gobject haskell-gi + ]; libraryHaskellDepends = [ - base bytestring containers gi-gio gi-glib gi-gobject haskell-gi - haskell-gi-base haskell-gi-overloading text transformers + base bytestring containers gi-gio gi-glib gi-gmodule gi-gobject + haskell-gi haskell-gi-base haskell-gi-overloading text transformers ]; - libraryPkgconfigDepends = [ gdk_pixbuf ]; + libraryPkgconfigDepends = [ gdk-pixbuf ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-gi/haskell-gi"; description = "GdkPixbuf bindings"; - license = stdenv.lib.licenses.lgpl21; - }) {inherit (pkgs) gdk_pixbuf;}; + license = lib.licenses.lgpl21Only; + }) {inherit (pkgs) gdk-pixbuf;}; + "gi-gdkx11" = callPackage + ({ mkDerivation, base, bytestring, Cabal, containers, gi-cairo + , gi-gdk, gi-gio, gi-gobject, gi-xlib, gtk3, haskell-gi + , haskell-gi-base, haskell-gi-overloading, lib, text, transformers + }: + mkDerivation { + pname = "gi-gdkx11"; + version = "3.0.11"; + sha256 = "a22b45fad90cb5c1ee62cad3dc83373a40435d20e7a16d1f547a67d3af3b241f"; + setupHaskellDepends = [ + base Cabal gi-cairo gi-gdk gi-gio gi-gobject gi-xlib haskell-gi + ]; + libraryHaskellDepends = [ + base bytestring containers gi-cairo gi-gdk gi-gio gi-gobject + gi-xlib haskell-gi haskell-gi-base haskell-gi-overloading text + transformers + ]; + libraryPkgconfigDepends = [ gtk3 ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell-gi/haskell-gi"; + description = "GdkX11 bindings"; + license = lib.licenses.lgpl21Only; + }) {inherit (pkgs) gtk3;}; "gi-gio" = callPackage ({ mkDerivation, base, bytestring, Cabal, containers, gi-glib , gi-gobject, glib, haskell-gi, haskell-gi-base - , haskell-gi-overloading, stdenv, text, transformers + , haskell-gi-overloading, lib, text, transformers }: mkDerivation { pname = "gi-gio"; - version = "2.0.18"; - sha256 = "13ebcd9c5d804de97db1f0ce7de520a73ba2eed950cbf5be84950fe33a8ef440"; - setupHaskellDepends = [ base Cabal haskell-gi ]; + version = "2.0.28"; + sha256 = "50b442c75a642dab5e715959f5e56dbcb728d9f2f6b1f51531aea6396364662d"; + setupHaskellDepends = [ base Cabal gi-glib gi-gobject haskell-gi ]; libraryHaskellDepends = [ base bytestring containers gi-glib gi-gobject haskell-gi haskell-gi-base haskell-gi-overloading text transformers @@ -13806,17 +16226,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/haskell-gi/haskell-gi"; description = "Gio bindings"; - license = stdenv.lib.licenses.lgpl21; + license = lib.licenses.lgpl21Only; }) {inherit (pkgs) glib;}; "gi-glib" = callPackage ({ mkDerivation, base, bytestring, Cabal, containers, glib - , haskell-gi, haskell-gi-base, haskell-gi-overloading, stdenv, text + , haskell-gi, haskell-gi-base, haskell-gi-overloading, lib, text , transformers }: mkDerivation { pname = "gi-glib"; - version = "2.0.17"; - sha256 = "9d7abe0a9d66689c5102629edb43a2336d1bb8dc805f0cbe214e5a4e799eab67"; + version = "2.0.25"; + sha256 = "a7bdf2d49776e7ca5ee18a881911a812dbd5d4a4942fc00c2e84fa1b2f097176"; setupHaskellDepends = [ base Cabal haskell-gi ]; libraryHaskellDepends = [ base bytestring containers haskell-gi haskell-gi-base @@ -13827,18 +16247,39 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/haskell-gi/haskell-gi"; description = "GLib bindings"; - license = stdenv.lib.licenses.lgpl21; + license = lib.licenses.lgpl21Only; }) {inherit (pkgs) glib;}; + "gi-gmodule" = callPackage + ({ mkDerivation, base, bytestring, Cabal, containers, gi-glib + , gmodule, haskell-gi, haskell-gi-base, haskell-gi-overloading, lib + , text, transformers + }: + mkDerivation { + pname = "gi-gmodule"; + version = "2.0.1"; + sha256 = "775df90be1a47a7d9d9eeb83a71df3e8c482bcf9a2cce42928828aa4d77da09b"; + setupHaskellDepends = [ base Cabal gi-glib haskell-gi ]; + libraryHaskellDepends = [ + base bytestring containers gi-glib haskell-gi haskell-gi-base + haskell-gi-overloading text transformers + ]; + libraryPkgconfigDepends = [ gmodule ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell-gi/haskell-gi"; + description = "GModule bindings"; + license = lib.licenses.lgpl21Only; + }) {inherit (pkgs) gmodule;}; "gi-gobject" = callPackage ({ mkDerivation, base, bytestring, Cabal, containers, gi-glib, glib - , haskell-gi, haskell-gi-base, haskell-gi-overloading, stdenv, text + , haskell-gi, haskell-gi-base, haskell-gi-overloading, lib, text , transformers }: mkDerivation { pname = "gi-gobject"; - version = "2.0.16"; - sha256 = "c57844d5b9566834ece584bfbbdff1c3ef2de5aa67c711c406fe92d4b927f6ad"; - setupHaskellDepends = [ base Cabal haskell-gi ]; + version = "2.0.26"; + sha256 = "ffce0e12132c3197b480df1614b39ea5e63cc5ba30e51f54fd41547b1bb4adcd"; + setupHaskellDepends = [ base Cabal gi-glib haskell-gi ]; libraryHaskellDepends = [ base bytestring containers gi-glib haskell-gi haskell-gi-base haskell-gi-overloading text transformers @@ -13848,19 +16289,43 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/haskell-gi/haskell-gi"; description = "GObject bindings"; - license = stdenv.lib.licenses.lgpl21; + license = lib.licenses.lgpl21Only; }) {inherit (pkgs) glib;}; + "gi-graphene" = callPackage + ({ mkDerivation, base, bytestring, Cabal, containers, gi-glib + , gi-gobject, graphene-gobject, haskell-gi, haskell-gi-base + , haskell-gi-overloading, lib, text, transformers + }: + mkDerivation { + pname = "gi-graphene"; + version = "1.0.3"; + sha256 = "6c002d8dd1bd81a30c2fe913fa7bb50118603df9ad87228c5c184f348628501b"; + setupHaskellDepends = [ base Cabal gi-glib gi-gobject haskell-gi ]; + libraryHaskellDepends = [ + base bytestring containers gi-glib gi-gobject haskell-gi + haskell-gi-base haskell-gi-overloading text transformers + ]; + libraryPkgconfigDepends = [ graphene-gobject ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell-gi/haskell-gi"; + description = "Graphene bindings"; + license = lib.licenses.lgpl21Only; + }) {inherit (pkgs) graphene-gobject;}; "gi-gtk" = callPackage ({ mkDerivation, base, bytestring, Cabal, containers, gi-atk , gi-cairo, gi-gdk, gi-gdkpixbuf, gi-gio, gi-glib, gi-gobject , gi-pango, gtk3, haskell-gi, haskell-gi-base - , haskell-gi-overloading, stdenv, text, transformers + , haskell-gi-overloading, lib, text, transformers }: mkDerivation { pname = "gi-gtk"; - version = "3.0.27"; - sha256 = "79061e4d4f428b6c67056250d57555e8fa11ee83234fff0f52105d6a0ace1dc5"; - setupHaskellDepends = [ base Cabal haskell-gi ]; + version = "3.0.37"; + sha256 = "13a8735b18670f795ad5fc8108231cb43398803e1e201f20cf96dd4c133a4fdf"; + setupHaskellDepends = [ + base Cabal gi-atk gi-cairo gi-gdk gi-gdkpixbuf gi-gio gi-glib + gi-gobject gi-pango haskell-gi + ]; libraryHaskellDepends = [ base bytestring containers gi-atk gi-cairo gi-gdk gi-gdkpixbuf gi-gio gi-glib gi-gobject gi-pango haskell-gi haskell-gi-base @@ -13871,84 +16336,63 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/haskell-gi/haskell-gi"; description = "Gtk bindings"; - license = stdenv.lib.licenses.lgpl21; - }) {gtk3 = pkgs.gnome3.gtk;}; + license = lib.licenses.lgpl21Only; + }) {inherit (pkgs) gtk3;}; "gi-gtk-hs" = callPackage ({ mkDerivation, base, base-compat, containers, gi-gdk - , gi-gdkpixbuf, gi-glib, gi-gobject, gi-gtk, haskell-gi-base, mtl - , stdenv, text, transformers + , gi-gdkpixbuf, gi-glib, gi-gobject, gi-gtk, haskell-gi-base, lib + , mtl, text, transformers }: mkDerivation { pname = "gi-gtk-hs"; - version = "0.3.6.3"; - sha256 = "5e894629b84bb79bb8b91e2d006965e351d24665c1dd37f354a77ce5acd6d976"; + version = "0.3.10"; + sha256 = "dc99dc05a3e978a11e0dcd9b4b4a4268e82c30f0aee662b4c407ef4dd7b47003"; libraryHaskellDepends = [ base base-compat containers gi-gdk gi-gdkpixbuf gi-glib gi-gobject gi-gtk haskell-gi-base mtl text transformers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/haskell-gi/gi-gtk-hs"; + homepage = "https://github.com/haskell-gi/haskell-gi"; description = "A wrapper for gi-gtk, adding a few more idiomatic API parts on top"; - license = stdenv.lib.licenses.lgpl21; + license = lib.licenses.lgpl21Only; }) {}; - "gi-gtksource" = callPackage - ({ mkDerivation, base, bytestring, Cabal, containers, gi-atk - , gi-cairo, gi-gdk, gi-gdkpixbuf, gi-gio, gi-glib, gi-gobject - , gi-gtk, gi-pango, gtksourceview3, haskell-gi, haskell-gi-base - , haskell-gi-overloading, stdenv, text, transformers + "gi-harfbuzz" = callPackage + ({ mkDerivation, base, bytestring, Cabal, containers, gi-glib + , gi-gobject, harfbuzz, harfbuzz-gobject, haskell-gi + , haskell-gi-base, haskell-gi-overloading, lib, text, transformers }: mkDerivation { - pname = "gi-gtksource"; - version = "3.0.16"; - sha256 = "97b91b9f48b9e0c65a3936beb6e814ac5a55ab20aefbd9a167313982bd5da53a"; - setupHaskellDepends = [ base Cabal haskell-gi ]; + pname = "gi-harfbuzz"; + version = "0.0.4"; + sha256 = "95d31980602858272480eea8c21f3e1242381dd3dd2b0ef3e9a55812d27f6d40"; + setupHaskellDepends = [ base Cabal gi-glib gi-gobject haskell-gi ]; libraryHaskellDepends = [ - base bytestring containers gi-atk gi-cairo gi-gdk gi-gdkpixbuf - gi-gio gi-glib gi-gobject gi-gtk gi-pango haskell-gi + base bytestring containers gi-glib gi-gobject haskell-gi haskell-gi-base haskell-gi-overloading text transformers ]; - libraryPkgconfigDepends = [ gtksourceview3 ]; + libraryPkgconfigDepends = [ harfbuzz harfbuzz-gobject ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-gi/haskell-gi"; - description = "GtkSource bindings"; - license = stdenv.lib.licenses.lgpl21; - }) {gtksourceview3 = pkgs.gnome3.gtksourceview;}; - "gi-javascriptcore" = callPackage - ({ mkDerivation, base, bytestring, Cabal, containers, gi-glib - , gi-gobject, haskell-gi, haskell-gi-base, haskell-gi-overloading - , stdenv, text, transformers, webkitgtk - }: - mkDerivation { - pname = "gi-javascriptcore"; - version = "4.0.16"; - sha256 = "5f30d7da8cca149b0234de871f18e4ff96288c928f678c649a620a7275c2304e"; - setupHaskellDepends = [ base Cabal haskell-gi ]; - libraryHaskellDepends = [ - base bytestring containers gi-glib gi-gobject haskell-gi - haskell-gi-base haskell-gi-overloading text transformers - ]; - libraryPkgconfigDepends = [ webkitgtk ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/haskell-gi/haskell-gi"; - description = "JavaScriptCore bindings"; - license = stdenv.lib.licenses.lgpl21; - }) {inherit (pkgs) webkitgtk;}; + description = "HarfBuzz bindings"; + license = lib.licenses.lgpl21Only; + }) {inherit (pkgs) harfbuzz; inherit (pkgs) harfbuzz-gobject;}; "gi-pango" = callPackage ({ mkDerivation, base, bytestring, Cabal, cairo, containers - , gi-glib, gi-gobject, haskell-gi, haskell-gi-base - , haskell-gi-overloading, pango, stdenv, text, transformers + , gi-glib, gi-gobject, gi-harfbuzz, haskell-gi, haskell-gi-base + , haskell-gi-overloading, lib, pango, text, transformers }: mkDerivation { pname = "gi-pango"; - version = "1.0.16"; - sha256 = "a7bcc68413d7f7479e9b746eacf08b0c29a93b7c8af17005d96607ce090e78f4"; - setupHaskellDepends = [ base Cabal haskell-gi ]; + version = "1.0.24"; + sha256 = "70366fbba9b258c1b79a0b7e637f2935f6342cafb106aeb6133f13d6470e7f63"; + setupHaskellDepends = [ + base Cabal gi-glib gi-gobject gi-harfbuzz haskell-gi + ]; libraryHaskellDepends = [ - base bytestring containers gi-glib gi-gobject haskell-gi - haskell-gi-base haskell-gi-overloading text transformers + base bytestring containers gi-glib gi-gobject gi-harfbuzz + haskell-gi haskell-gi-base haskell-gi-overloading text transformers ]; libraryPkgconfigDepends = [ cairo pango ]; doHaddock = false; @@ -13959,115 +16403,136 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; ''; homepage = "https://github.com/haskell-gi/haskell-gi"; description = "Pango bindings"; - license = stdenv.lib.licenses.lgpl21; + license = lib.licenses.lgpl21Only; }) {inherit (pkgs) cairo; inherit (pkgs) pango;}; - "gi-vte" = callPackage - ({ mkDerivation, base, bytestring, Cabal, containers, gi-atk - , gi-gdk, gi-gio, gi-glib, gi-gobject, gi-gtk, gi-pango, haskell-gi - , haskell-gi-base, haskell-gi-overloading, stdenv, text - , transformers, vte_291 + "gi-xlib" = callPackage + ({ mkDerivation, base, bytestring, Cabal, containers, haskell-gi + , haskell-gi-base, haskell-gi-overloading, lib, text, transformers + , xlibsWrapper }: mkDerivation { - pname = "gi-vte"; - version = "2.91.19"; - sha256 = "9eb476c66295f9786df59bcf429d16a94462846dd3486a048a07ca93658bd0c2"; + pname = "gi-xlib"; + version = "2.0.10"; + sha256 = "0849f734d39279541165fcdd3939334947e091c425f6787e2ecb845ac1bbd3c0"; setupHaskellDepends = [ base Cabal haskell-gi ]; libraryHaskellDepends = [ - base bytestring containers gi-atk gi-gdk gi-gio gi-glib gi-gobject - gi-gtk gi-pango haskell-gi haskell-gi-base haskell-gi-overloading - text transformers + base bytestring containers haskell-gi haskell-gi-base + haskell-gi-overloading text transformers ]; - libraryPkgconfigDepends = [ vte_291 ]; + libraryPkgconfigDepends = [ xlibsWrapper ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-gi/haskell-gi"; - description = "Vte bindings"; - license = stdenv.lib.licenses.lgpl21; - }) {vte_291 = pkgs.gnome3.vte;}; - "gingersnap" = callPackage - ({ mkDerivation, aeson, base, bytestring, deepseq, http-types - , postgresql-simple, resource-pool, snap-core, stdenv, text - , transformers, unordered-containers + description = "xlib bindings"; + license = lib.licenses.lgpl21Only; + }) {inherit (pkgs) xlibsWrapper;}; + "ginger" = callPackage + ({ mkDerivation, aeson, aeson-pretty, base, bytestring + , data-default, filepath, http-types, lib, mtl + , optparse-applicative, parsec, process, regex-tdfa, safe + , scientific, text, time, transformers, unordered-containers + , utf8-string, vector, yaml }: mkDerivation { - pname = "gingersnap"; - version = "0.3.1.0"; - sha256 = "01509dbfc31e865128d2ef13efc56502f9a716f7b30f0890a0616612aed08c82"; + pname = "ginger"; + version = "0.10.1.0"; + sha256 = "1dc6fe25e9180933d9b9205af6d1dcd32bf2bd71c9d07a415be0d91cb254e914"; + isLibrary = true; + isExecutable = true; + enableSeparateDataOutput = true; libraryHaskellDepends = [ - aeson base bytestring deepseq http-types postgresql-simple - resource-pool snap-core text transformers unordered-containers + aeson aeson-pretty base bytestring data-default filepath http-types + mtl parsec regex-tdfa safe scientific text time transformers + unordered-containers utf8-string vector + ]; + executableHaskellDepends = [ + aeson base bytestring data-default optparse-applicative process + text transformers unordered-containers utf8-string yaml ]; doHaddock = false; doCheck = false; - description = "Consistent and safe JSON APIs with snap-core and (by default) postgresql-simple"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://ginger.tobiasdammers.nl/"; + description = "An implementation of the Jinja2 template language in Haskell"; + license = lib.licenses.mit; }) {}; - "giphy-api" = callPackage - ({ mkDerivation, aeson, base, containers, http-api-data - , http-client, http-client-tls, microlens, microlens-th, mtl - , network-uri, servant, servant-client, stdenv, text, transformers + "gingersnap" = callPackage + ({ mkDerivation, aeson, base, bytestring, deepseq, http-types, lib + , postgresql-simple, resource-pool, snap-core, text, transformers + , unordered-containers }: mkDerivation { - pname = "giphy-api"; - version = "0.6.0.1"; - sha256 = "8ddfb5005bc26553850366c527c0a1a93e6b1efaf4334f195a4f5ab647408604"; - isLibrary = true; - isExecutable = true; + pname = "gingersnap"; + version = "0.3.1.0"; + sha256 = "01509dbfc31e865128d2ef13efc56502f9a716f7b30f0890a0616612aed08c82"; libraryHaskellDepends = [ - aeson base containers http-api-data http-client http-client-tls - microlens microlens-th mtl network-uri servant servant-client text - transformers + aeson base bytestring deepseq http-types postgresql-simple + resource-pool snap-core text transformers unordered-containers ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/passy/giphy-api#readme"; - description = "Giphy HTTP API wrapper and CLI search tool"; - license = stdenv.lib.licenses.bsd3; + description = "Consistent and safe JSON APIs with snap-core and (by default) postgresql-simple"; + license = lib.licenses.bsd3; }) {}; "githash" = callPackage - ({ mkDerivation, base, bytestring, directory, filepath, process - , stdenv, template-haskell + ({ mkDerivation, base, bytestring, directory, filepath, lib + , process, template-haskell, th-compat }: mkDerivation { pname = "githash"; - version = "0.1.3.1"; - sha256 = "ea58689a525e4953aaf91415d9a70b593fae88c7858e37f761bc836ce1fafc6e"; + version = "0.1.6.1"; + sha256 = "7101799da3e25dd4c2fef5683999b72d940333632566b85f4967f741c513223d"; libraryHaskellDepends = [ base bytestring directory filepath process template-haskell + th-compat ]; doHaddock = false; doCheck = false; homepage = "https://github.com/snoyberg/githash#readme"; description = "Compile git revision info into Haskell projects"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "github-release" = callPackage - ({ mkDerivation, aeson, base, bytestring, http-client - , http-client-tls, http-types, mime-types, optparse-generic, stdenv - , text, unordered-containers, uri-templater + ({ mkDerivation, aeson, base, burrito, bytestring, http-client + , http-client-tls, http-types, lib, mime-types, optparse-generic + , text, unordered-containers }: mkDerivation { pname = "github-release"; - version = "1.2.3"; - sha256 = "1e50df80c6cd2e1b4e007648c5e0833489cc57d41daf0262e65fd4e59f404b92"; + version = "1.3.7"; + sha256 = "f0b3642769ed93ebedc16998fd1c98e296372c37363b4ea8d15cd441ae4abf91"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - aeson base bytestring http-client http-client-tls http-types - mime-types optparse-generic text unordered-containers uri-templater - ]; - executableHaskellDepends = [ - aeson base bytestring http-client http-client-tls http-types - mime-types optparse-generic text unordered-containers uri-templater + aeson base burrito bytestring http-client http-client-tls + http-types mime-types optparse-generic text unordered-containers ]; + executableHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/tfausak/github-release#readme"; description = "Upload files to GitHub releases"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "github-rest" = callPackage + ({ mkDerivation, aeson, base, bytestring, http-client + , http-client-tls, http-types, jwt, lib, mtl, scientific, text + , time, transformers, unliftio, unliftio-core + }: + mkDerivation { + pname = "github-rest"; + version = "1.0.3"; + sha256 = "2b4bb3174d4be9fa93c0db93b4d70e91b5bc3736af677bd4327be74d458f9c2a"; + libraryHaskellDepends = [ + aeson base bytestring http-client http-client-tls http-types jwt + mtl scientific text time transformers unliftio unliftio-core + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/LeapYear/github-rest#readme"; + description = "Query the GitHub REST API programmatically"; + license = lib.licenses.bsd3; }) {}; "github-types" = callPackage - ({ mkDerivation, aeson, base, stdenv, text, time }: + ({ mkDerivation, aeson, base, lib, text, time }: mkDerivation { pname = "github-types"; version = "0.2.1"; @@ -14077,17 +16542,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; description = "Type definitions for objects used by the GitHub v3 API"; license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; + hydraPlatforms = lib.platforms.none; }) {}; "github-webhooks" = callPackage ({ mkDerivation, aeson, base, base16-bytestring, bytestring - , cryptonite, deepseq, deepseq-generics, memory, stdenv, text, time + , cryptonite, deepseq, deepseq-generics, lib, memory, text, time , vector }: mkDerivation { pname = "github-webhooks"; - version = "0.10.0"; - sha256 = "084a8aa9cc71f89a47a0c8cdb1d0f9eac79fb7d4360ed224efd8443f0c7271df"; + version = "0.15.0"; + sha256 = "bf71127d51366b06d310846bf9d4a35516a628af824879758d371576e0daaa32"; libraryHaskellDepends = [ aeson base base16-bytestring bytestring cryptonite deepseq deepseq-generics memory text time vector @@ -14096,11 +16561,31 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/onrock-eng/github-webhooks#readme"; description = "Aeson instances for GitHub Webhook payloads"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "gitlab-haskell" = callPackage + ({ mkDerivation, aeson, base, bytestring, connection, http-conduit + , http-types, lib, temporary, text, time, transformers, unix + , unliftio, unliftio-core + }: + mkDerivation { + pname = "gitlab-haskell"; + version = "0.2.5"; + sha256 = "7d20ef80adc33843ec9c6052e2444f0ab8be2ea524bceb65a7b76e0a055db48d"; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + aeson base bytestring connection http-conduit http-types temporary + text time transformers unix unliftio unliftio-core + ]; + doHaddock = false; + doCheck = false; + homepage = "https://gitlab.com/robstewart57/gitlab-haskell"; + description = "A Haskell library for the GitLab web API"; + license = lib.licenses.bsd3; }) {}; "gitrev" = callPackage - ({ mkDerivation, base, base-compat, directory, filepath, process - , stdenv, template-haskell + ({ mkDerivation, base, base-compat, directory, filepath, lib + , process, template-haskell }: mkDerivation { pname = "gitrev"; @@ -14113,21 +16598,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/acfoltzer/gitrev"; description = "Compile git revision info into Haskell projects"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "gl" = callPackage - ({ mkDerivation, base, Cabal, containers, directory, filepath - , fixed, half, hxt, libGL, stdenv, transformers + ({ mkDerivation, base, containers, fixed, half, lib, libGL + , transformers }: mkDerivation { pname = "gl"; - version = "0.8.0"; - sha256 = "aa4d2838157c86da920bda651458a4266fccc7c291ea93a69558ab02540e1439"; - revision = "2"; - editedCabalFile = "0zbpf559ajlcwnylpbm6dbi4m3g3s08fciqfp5am3i2vrmw0wpi9"; - setupHaskellDepends = [ - base Cabal containers directory filepath hxt transformers - ]; + version = "0.9"; + sha256 = "318ef0aab5239d5253c387709dd935c43a0d614f9bb1e186db4a7a96d88b61cd"; + revision = "1"; + editedCabalFile = "19qyb9m2fy9qyirmhhayg51scas42n3i2rx7jcw6v3ra8c8r9rwr"; libraryHaskellDepends = [ base containers fixed half transformers ]; @@ -14135,16 +16617,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Complete OpenGL raw bindings"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) libGL;}; "glabrous" = callPackage ({ mkDerivation, aeson, aeson-pretty, attoparsec, base, bytestring - , cereal, cereal-text, either, stdenv, text, unordered-containers + , cereal, cereal-text, either, lib, text, unordered-containers }: mkDerivation { pname = "glabrous"; - version = "1.0.0"; - sha256 = "7364ad72a415659f2ad3b37f703d5c94225b96f8aba0f5338f56675a8e390003"; + version = "2.0.4"; + sha256 = "f3fab027a55bf9923ded051c8896ad35d59b343c471740090994526913d0ee67"; libraryHaskellDepends = [ aeson aeson-pretty attoparsec base bytestring cereal cereal-text either text unordered-containers @@ -14153,49 +16635,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/MichelBoucey/glabrous"; description = "A template DSL library"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "glaze" = callPackage - ({ mkDerivation, base, lens, stdenv }: - mkDerivation { - pname = "glaze"; - version = "0.3.0.1"; - sha256 = "bbb184408bcf24e8c4f89a960cf7a69ab0c51e98bf84c5fa9901aae1702e22a1"; - libraryHaskellDepends = [ base lens ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/louispan/glaze#readme"; - description = "Framework for rendering things with metadata/headers and values"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "glazier" = callPackage - ({ mkDerivation, alternators, base, data-diverse, data-diverse-lens - , dlist, lens, mtl, stdenv, transformers, unliftio, unliftio-core - }: - mkDerivation { - pname = "glazier"; - version = "1.0.0.0"; - sha256 = "e9c56250e48b99bfe6280c58d1458c5d35203bf3676705355a4d0bd89c7b71a4"; - libraryHaskellDepends = [ - alternators base data-diverse data-diverse-lens dlist lens mtl - transformers unliftio unliftio-core - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/louispan/glazier#readme"; - description = "Extensible effects using ContT, State and variants"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "gloss" = callPackage ({ mkDerivation, base, bmp, bytestring, containers, ghc-prim - , gloss-rendering, GLUT, OpenGL, stdenv + , gloss-rendering, GLUT, lib, OpenGL }: mkDerivation { pname = "gloss"; - version = "1.13.0.1"; - sha256 = "381c0fecd9532c38bf3d0faf18a1be8d5394c8b103dd223cbd6f5a313add29b8"; - revision = "1"; - editedCabalFile = "1nyg324icnlky647zq4c21sqxv2bgnwnzgh2hz5d5ys6ba69j59h"; + version = "1.13.2.1"; + sha256 = "f6168c796f525753a68eb6e6bff9038bab9a21bc2fad92d05f47f02fa6bd4d51"; libraryHaskellDepends = [ base bmp bytestring containers ghc-prim gloss-rendering GLUT OpenGL ]; @@ -14203,88 +16652,50 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://gloss.ouroborus.net"; description = "Painless 2D vector graphics, animations and simulations"; - license = stdenv.lib.licenses.mit; - }) {}; - "gloss-algorithms" = callPackage - ({ mkDerivation, base, containers, ghc-prim, gloss, stdenv }: - mkDerivation { - pname = "gloss-algorithms"; - version = "1.13.0.1"; - sha256 = "25391db76e21e70c912d818a5f28f1b647a801034b3960540264b1e8b766786d"; - revision = "1"; - editedCabalFile = "140zmk3br0nn98mjc6ri36nk8yl93n4v69zybzv2vc41yxgvnac5"; - libraryHaskellDepends = [ base containers ghc-prim gloss ]; - doHaddock = false; - doCheck = false; - homepage = "http://gloss.ouroborus.net"; - description = "Data structures and algorithms for working with 2D graphics"; - license = stdenv.lib.licenses.mit; - }) {}; - "gloss-examples" = callPackage - ({ mkDerivation, base, bmp, bytestring, containers, ghc-prim, gloss - , gloss-algorithms, gloss-raster, random, repa, repa-algorithms - , repa-io, stdenv, vector - }: - mkDerivation { - pname = "gloss-examples"; - version = "1.13.0.2"; - sha256 = "ab216c95cf26879154db0d7ee36def7a2d9b2cd6aaae4278e2b55621a51c54bc"; - isLibrary = false; - isExecutable = true; - executableHaskellDepends = [ - base bmp bytestring containers ghc-prim gloss gloss-algorithms - gloss-raster random repa repa-algorithms repa-io vector - ]; - doHaddock = false; - doCheck = false; - homepage = "http://gloss.ouroborus.net"; - description = "Examples using the gloss library"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "gloss-raster" = callPackage - ({ mkDerivation, base, containers, ghc-prim, gloss, gloss-rendering - , repa, stdenv + "gloss-rendering" = callPackage + ({ mkDerivation, base, bmp, bytestring, containers, GLUT, lib + , OpenGL }: mkDerivation { - pname = "gloss-raster"; - version = "1.13.0.2"; - sha256 = "895c678b7c7951937c9a881c3367952352bd62a1150b0c2f093a5817580a94cc"; + pname = "gloss-rendering"; + version = "1.13.1.1"; + sha256 = "3db5001edf345ac2232d012d6f57df031674509fca18383e43ca37f7ffa97fde"; + revision = "1"; + editedCabalFile = "10x83cpxp6yrmamjg4kjm3pzlhh6zj2rdw686py0vcx0jrjy3qg7"; libraryHaskellDepends = [ - base containers ghc-prim gloss gloss-rendering repa + base bmp bytestring containers GLUT OpenGL ]; doHaddock = false; doCheck = false; - homepage = "http://gloss.ouroborus.net"; - description = "Parallel rendering of raster images"; - license = stdenv.lib.licenses.mit; + description = "Gloss picture data types and rendering functions"; + license = lib.licenses.mit; }) {}; - "gloss-rendering" = callPackage - ({ mkDerivation, base, bmp, bytestring, containers, GLUT, OpenGL - , stdenv + "gluturtle" = callPackage + ({ mkDerivation, base, convertible, GLUT, lib, stm, yjsvg, yjtools }: mkDerivation { - pname = "gloss-rendering"; - version = "1.13.0.2"; - sha256 = "003b992a84bbaee82c7fc3f3e7904afbfddffe02b86630712419d83eb18c7f47"; - revision = "1"; - editedCabalFile = "0r57zc8ryxgjb4ydcdlmq19hl3nj6gjm3z85wrmdkn0wrx16mqih"; + pname = "gluturtle"; + version = "0.0.58.1"; + sha256 = "178658ce4f76ac0a855ca9123cdc8bda0ecc5531356551c00ba6de98dcbd934b"; libraryHaskellDepends = [ - base bmp bytestring containers GLUT OpenGL + base convertible GLUT stm yjsvg yjtools ]; doHaddock = false; doCheck = false; - description = "Gloss picture data types and rendering functions"; - license = stdenv.lib.licenses.mit; + description = "turtle like LOGO with glut"; + license = lib.licenses.bsd3; }) {}; "gnuplot" = callPackage ({ mkDerivation, array, base, containers, data-accessor - , data-accessor-transformers, deepseq, filepath, process - , semigroups, stdenv, temporary, time, transformers, utility-ht + , data-accessor-transformers, deepseq, filepath, lib, process + , semigroups, temporary, time, transformers, utility-ht }: mkDerivation { pname = "gnuplot"; - version = "0.5.5.3"; - sha256 = "4f742082835978919db75abc570e6cd924d63c6bdd951e1280f97d5d98540504"; + version = "0.5.6.1"; + sha256 = "cb32149b2ad92c134094f2f79ee0cee88e4de995a6e4729347597a6d2949d8e5"; isLibrary = true; isExecutable = true; enableSeparateDataOutput = true; @@ -14297,34 +16708,33 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Gnuplot"; description = "2D and 3D plots using gnuplot"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "goggles" = callPackage - ({ mkDerivation, aeson, attoparsec, base, base64-bytestring, binary - , bytestring, containers, cryptonite, exceptions, filepath - , http-client, http-client-tls, http-types, memory, mtl, pem, req - , scientific, stdenv, stm, text, time, transformers, unix-time - , x509, x509-store + "goldplate" = callPackage + ({ mkDerivation, aeson, aeson-pretty, async, base, bytestring, Diff + , directory, filepath, Glob, lib, optparse-applicative, process + , regex-pcre-builtin, text, unordered-containers }: mkDerivation { - pname = "goggles"; - version = "0.3.2"; - sha256 = "a64d25c6506b172ec6f3b8a55f7934c23ccedc66c1acfb62432063dff743e93c"; - libraryHaskellDepends = [ - aeson attoparsec base base64-bytestring binary bytestring - containers cryptonite exceptions filepath http-client - http-client-tls http-types memory mtl pem req scientific stm text - time transformers unix-time x509 x509-store + pname = "goldplate"; + version = "0.2.0"; + sha256 = "41d5b7f8d3573d28d87d9b7b14542088e422eb41b23d87c0ced39b63024a56b8"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ + aeson aeson-pretty async base bytestring Diff directory filepath + Glob optparse-applicative process regex-pcre-builtin text + unordered-containers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/ocramz/goggles"; - description = "Extensible interface to Web APIs"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/fugue/goldplate"; + description = "A lightweight golden test runner"; + license = lib.licenses.asl20; }) {}; "google-isbn" = callPackage ({ mkDerivation, aeson, base, bytestring, conduit, conduit-extra - , http-conduit, stdenv, text + , http-conduit, lib, text }: mkDerivation { pname = "google-isbn"; @@ -14336,27 +16746,53 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; homepage = "https://github.com/apeyroux/google-isbn#readme"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "google-oauth2-jwt" = callPackage - ({ mkDerivation, base, base64-bytestring, bytestring, HsOpenSSL - , RSA, stdenv, text, unix-time + "gopher-proxy" = callPackage + ({ mkDerivation, attoparsec, base, bytestring, directory, errors + , http-types, lib, lucid, mime-types, network, optparse-applicative + , text, wai, warp }: mkDerivation { - pname = "google-oauth2-jwt"; - version = "0.3.1"; - sha256 = "71d7704aad64fbd2398d8b0dcb6f39311a8e710385fc80ee2b665bd6b43b2f88"; + pname = "gopher-proxy"; + version = "0.1.1.2"; + sha256 = "f01108862c464c415e2569b6e3624cd7863736e5d0c468c2d9763fc5b67b27ca"; + isLibrary = false; + isExecutable = true; + enableSeparateDataOutput = true; + executableHaskellDepends = [ + attoparsec base bytestring directory errors http-types lucid + mime-types network optparse-applicative text wai warp + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/sternenseemann/gopher-proxy"; + description = "proxy gopher over http"; + license = lib.licenses.gpl3Only; + }) {}; + "gothic" = callPackage + ({ mkDerivation, aeson, base, binary, bytestring, connection + , exceptions, hashable, http-client, http-client-tls, http-conduit + , http-types, lens, lens-aeson, lib, scientific, text, unix + , unordered-containers, vector + }: + mkDerivation { + pname = "gothic"; + version = "0.1.6"; + sha256 = "9a1018c247fc6b124a17dbedd2cdbc0a539249f436313dfd960dd8771f61305c"; libraryHaskellDepends = [ - base base64-bytestring bytestring HsOpenSSL RSA text unix-time + aeson base binary bytestring connection exceptions hashable + http-client http-client-tls http-conduit http-types lens lens-aeson + scientific text unix unordered-containers vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/MichelBoucey/google-oauth2-jwt"; - description = "Get a signed JWT for Google Service Accounts"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/MichelBoucey/gothic"; + description = "A Haskell Vault KVv2 secret engine client"; + license = lib.licenses.bsd3; }) {}; "gpolyline" = callPackage - ({ mkDerivation, base, split, stdenv }: + ({ mkDerivation, base, lib, split }: mkDerivation { pname = "gpolyline"; version = "0.1.0.1"; @@ -14366,11 +16802,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/fegu/gpolyline"; description = "Pure module for encoding/decoding Google Polyline"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "graph-core" = callPackage - ({ mkDerivation, base, containers, deepseq, hashable, mtl, safe - , stdenv, unordered-containers, vector + ({ mkDerivation, base, containers, deepseq, hashable, lib, mtl + , safe, unordered-containers, vector }: mkDerivation { pname = "graph-core"; @@ -14384,23 +16820,72 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/factisresearch/graph-core"; description = "Fast, memory efficient and persistent graph implementation"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "graph-wrapper" = callPackage - ({ mkDerivation, array, base, containers, stdenv }: + ({ mkDerivation, array, base, containers, lib }: mkDerivation { pname = "graph-wrapper"; - version = "0.2.5.2"; - sha256 = "98a42ef1eee9a5012b0bb2a91f645dd8487df6cfdcfcab5e387a8abf42768dcd"; + version = "0.2.6.0"; + sha256 = "b89ed6f47a6d44b9466d090eabddc9d9ec4b2d7e4b52a61b26d0cf19dac95ba6"; libraryHaskellDepends = [ array base containers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/soenkehahn/graph-wrapper"; description = "A wrapper around the standard Data.Graph with a less awkward interface"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "graphite" = callPackage + ({ mkDerivation, base, bytestring, cassava, containers, deepseq + , graphviz, hashable, lib, process, QuickCheck, random, semigroups + , text, unordered-containers, vector + }: + mkDerivation { + pname = "graphite"; + version = "0.10.0.1"; + sha256 = "7a8366a9113c5071f5c4863a6bf10462c4274281f5523fc80f2e5539de6d0aab"; + libraryHaskellDepends = [ + base bytestring cassava containers deepseq graphviz hashable + process QuickCheck random semigroups text unordered-containers + vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/alx741/graphite#readme"; + description = "Graphs and networks library"; + license = lib.licenses.bsd3; + }) {}; + "graphql-client" = callPackage + ({ mkDerivation, aeson, aeson-schemas, base, bytestring, file-embed + , http-client, http-client-tls, http-types, lib, mtl + , optparse-applicative, path, path-io, template-haskell, text + , transformers, typed-process, unliftio-core + }: + mkDerivation { + pname = "graphql-client"; + version = "1.1.1"; + sha256 = "64bdb71192e654bed239e74719ae6d7abd25f37772e687c3de485fc4d28a00b4"; + revision = "3"; + editedCabalFile = "0pnkq0wxjmfk67ji6wr7b42lsr2gp026cx91ryq146gh4c9gwacv"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson aeson-schemas base http-client http-client-tls http-types mtl + template-haskell text transformers unliftio-core + ]; + executableHaskellDepends = [ + aeson aeson-schemas base bytestring file-embed http-client + http-client-tls http-types mtl optparse-applicative path path-io + template-haskell text transformers typed-process unliftio-core + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/LeapYear/graphql-client#readme"; + description = "A client for Haskell programs to query a GraphQL API"; + license = lib.licenses.bsd3; }) {}; "graphs" = callPackage - ({ mkDerivation, array, base, containers, stdenv, transformers + ({ mkDerivation, array, base, containers, lib, transformers , transformers-compat, void }: mkDerivation { @@ -14416,70 +16901,92 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/graphs"; description = "A simple monadic graph library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "gravatar" = callPackage - ({ mkDerivation, base, bytestring, data-default, HTTP, pureMD5 - , stdenv, text + "graphula" = callPackage + ({ mkDerivation, base, containers, directory, generics-eot, HUnit + , lib, mtl, persistent, QuickCheck, random, semigroups, temporary + , text, transformers, unliftio, unliftio-core }: mkDerivation { - pname = "gravatar"; - version = "0.8.0"; - sha256 = "6f6000acaea47f3fc8711f5a2a62d5fbe96f5bb698fcb997f9f07ffe3102f4d7"; + pname = "graphula"; + version = "2.0.0.5"; + sha256 = "470d730caee75b166425ccf406d7eee500c3d173738545e2a177243f58b957aa"; libraryHaskellDepends = [ - base bytestring data-default HTTP pureMD5 text + base containers directory generics-eot HUnit mtl persistent + QuickCheck random semigroups temporary text transformers unliftio + unliftio-core ]; doHaddock = false; doCheck = false; - description = "Generate Gravatar image URLs"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/freckle/graphula#readme"; + description = "A declarative library for describing dependencies between data"; + license = lib.licenses.mit; }) {}; - "graylog" = callPackage - ({ mkDerivation, aeson, aeson-casing, base, bytestring, network - , random, scientific, stdenv, text, time, vector + "graphviz" = callPackage + ({ mkDerivation, base, bytestring, colour, containers, directory + , dlist, fgl, filepath, lib, mtl, polyparse, process, temporary + , text, wl-pprint-text }: mkDerivation { - pname = "graylog"; - version = "0.1.0.1"; - sha256 = "2d8173e61da8d02c39cb95e6ccea8a167c792f682a496aed5fe4edfd0e6a0082"; + pname = "graphviz"; + version = "2999.20.1.0"; + sha256 = "5ae428c3cda1eee205c9960504f490afa683a756ebbd1c710210a291d6eb1f50"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - aeson aeson-casing base bytestring network random scientific text - time vector + base bytestring colour containers directory dlist fgl filepath mtl + polyparse process temporary text wl-pprint-text ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/AndrewRademacher/haskell-graylog"; - description = "Support for graylog output"; - license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; + homepage = "https://github.com/ivan-m/graphviz"; + description = "Bindings to Graphviz for graph visualisation"; + license = lib.licenses.bsd3; + }) {}; + "gravatar" = callPackage + ({ mkDerivation, base, bytestring, data-default, HTTP, lib, pureMD5 + , text + }: + mkDerivation { + pname = "gravatar"; + version = "0.8.0"; + sha256 = "6f6000acaea47f3fc8711f5a2a62d5fbe96f5bb698fcb997f9f07ffe3102f4d7"; + libraryHaskellDepends = [ + base bytestring data-default HTTP pureMD5 text + ]; + doHaddock = false; + doCheck = false; + description = "Generate Gravatar image URLs"; + license = lib.licenses.mit; }) {}; "greskell" = callPackage - ({ mkDerivation, aeson, base, exceptions, greskell-core, semigroups - , stdenv, text, transformers, unordered-containers, vector + ({ mkDerivation, aeson, base, exceptions, greskell-core, hashable + , lib, semigroups, text, transformers, unordered-containers, vector }: mkDerivation { pname = "greskell"; - version = "0.2.3.0"; - sha256 = "a851a131d4ebb8b5beda62b58a2268670a7dff8370d6cc795ce092615d642560"; + version = "1.2.0.1"; + sha256 = "ba56deeb8297b952c960653cc7adbf016aae047fed5585a7b58d030a2d871a8e"; configureFlags = [ "-f-hint-test" ]; libraryHaskellDepends = [ - aeson base exceptions greskell-core semigroups text transformers - unordered-containers vector + aeson base exceptions greskell-core hashable semigroups text + transformers unordered-containers vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/debug-ito/greskell/"; description = "Haskell binding for Gremlin graph query language"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "greskell-core" = callPackage - ({ mkDerivation, aeson, base, containers, hashable, scientific - , semigroups, stdenv, text, unordered-containers, uuid, vector + ({ mkDerivation, aeson, base, containers, hashable, lib, scientific + , semigroups, text, unordered-containers, uuid, vector }: mkDerivation { pname = "greskell-core"; - version = "0.1.2.4"; - sha256 = "201d3f76a503948114f387f0c63d88e1170ed26305b2c2a8b799a47d37dc4f85"; + version = "0.1.3.6"; + sha256 = "73942c91033f5e5123f498a6ab6adc9682c6c099613733d92a814590758acdd5"; libraryHaskellDepends = [ aeson base containers hashable scientific semigroups text unordered-containers uuid vector @@ -14488,17 +16995,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/debug-ito/greskell/"; description = "Haskell binding for Gremlin graph query language - core data types and tools"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "greskell-websocket" = callPackage ({ mkDerivation, aeson, async, base, base64-bytestring, bytestring - , greskell-core, hashtables, safe-exceptions, stdenv, stm, text + , greskell-core, hashtables, lib, safe-exceptions, stm, text , unordered-containers, uuid, vector, websockets }: mkDerivation { pname = "greskell-websocket"; - version = "0.1.1.2"; - sha256 = "9062b34fec1855b0262a0cf529dcc3ebf5bb20738712195420d832dd46e2cde7"; + version = "0.1.2.5"; + sha256 = "c0aea52dbe791bc27325513e52a2274673b76d9021fb10db4275092949767979"; libraryHaskellDepends = [ aeson async base base64-bytestring bytestring greskell-core hashtables safe-exceptions stm text unordered-containers uuid @@ -14508,10 +17015,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/debug-ito/greskell/"; description = "Haskell client for Gremlin Server using WebSocket serializer"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "groom" = callPackage - ({ mkDerivation, base, haskell-src-exts, stdenv }: + ({ mkDerivation, base, haskell-src-exts, lib }: mkDerivation { pname = "groom"; version = "0.1.2.1"; @@ -14523,229 +17030,148 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Pretty printing for well-behaved Show instances"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "groundhog" = callPackage - ({ mkDerivation, aeson, attoparsec, base, base64-bytestring - , blaze-builder, bytestring, containers, monad-control, mtl - , resourcet, safe-exceptions, scientific, stdenv, text, time - , transformers, transformers-base, transformers-compat - }: - mkDerivation { - pname = "groundhog"; - version = "0.10.0"; - sha256 = "38fb65889878a50fd16e2ad8a04f0a9e2c774794086fbe156361d797b1a893f1"; - libraryHaskellDepends = [ - aeson attoparsec base base64-bytestring blaze-builder bytestring - containers monad-control mtl resourcet safe-exceptions scientific - text time transformers transformers-base transformers-compat - ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/lykahb/groundhog"; - description = "Type-safe datatype-database mapping library"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "groundhog-mysql" = callPackage - ({ mkDerivation, base, bytestring, containers, groundhog - , monad-control, monad-logger, mysql, mysql-simple, resource-pool - , resourcet, stdenv, text, time, transformers - }: - mkDerivation { - pname = "groundhog-mysql"; - version = "0.10"; - sha256 = "ddf26a56078d815c77b0d36230183fe8ab804c5dc12ed09c2332ae06a88ebec5"; - libraryHaskellDepends = [ - base bytestring containers groundhog monad-control monad-logger - mysql mysql-simple resource-pool resourcet text time transformers - ]; - doHaddock = false; - doCheck = false; - description = "MySQL backend for the groundhog library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "groundhog-postgresql" = callPackage - ({ mkDerivation, aeson, attoparsec, base, blaze-builder, bytestring - , containers, groundhog, monad-control, postgresql-libpq - , postgresql-simple, resource-pool, resourcet, stdenv, text, time - , transformers, vector + "group-by-date" = callPackage + ({ mkDerivation, base, explicit-exception, filemanip, lib, pathtype + , shell-utility, time, transformers, unix-compat, utility-ht }: mkDerivation { - pname = "groundhog-postgresql"; - version = "0.10"; - sha256 = "8916f26dfe8b3a8523792ce44899fa7ee984c002100c10850819159551dc2fb6"; - libraryHaskellDepends = [ - aeson attoparsec base blaze-builder bytestring containers groundhog - monad-control postgresql-libpq postgresql-simple resource-pool - resourcet text time transformers vector + pname = "group-by-date"; + version = "0.1.0.4"; + sha256 = "4a27d9a48fa4f80dc17c265c13b1f9b3a9821f0962e15cfc7cbf883fc3b4abcc"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ + base explicit-exception filemanip pathtype shell-utility time + transformers unix-compat utility-ht ]; doHaddock = false; doCheck = false; - description = "PostgreSQL backend for the groundhog library"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://hub.darcs.net/thielema/group-by-date/"; + description = "Shell command for grouping files by dates into folders"; + license = lib.licenses.bsd3; }) {}; - "groundhog-sqlite" = callPackage - ({ mkDerivation, base, bytestring, containers, direct-sqlite - , groundhog, monad-control, resource-pool, resourcet, stdenv, text - , transformers, unordered-containers - }: + "groups" = callPackage + ({ mkDerivation, base, lib }: mkDerivation { - pname = "groundhog-sqlite"; - version = "0.10.0"; - sha256 = "fdf0377924ac6214ced50a5670b2d4811801c1a20e480b22090a705582d6defc"; - libraryHaskellDepends = [ - base bytestring containers direct-sqlite groundhog monad-control - resource-pool resourcet text transformers unordered-containers - ]; + pname = "groups"; + version = "0.5.3"; + sha256 = "ce1e52a8be7effbd1f995eadf0ed34fa45c412656d372db8a38f9c955e43ac38"; + libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - description = "Sqlite3 backend for the groundhog library"; - license = stdenv.lib.licenses.bsd3; + description = "Groups"; + license = lib.licenses.bsd3; }) {}; - "groups" = callPackage - ({ mkDerivation, base, stdenv }: + "gtk-strut" = callPackage + ({ mkDerivation, base, gi-gdk, gi-gtk, lib, text, transformers }: mkDerivation { - pname = "groups"; - version = "0.4.1.0"; - sha256 = "dd4588b71dfff42b9a30cb40304912742b95db964b20f51951aff0eee7f3f33d"; - libraryHaskellDepends = [ base ]; + pname = "gtk-strut"; + version = "0.1.3.0"; + sha256 = "81936e26af4de93be8e11ae287e7617d14aa01a08c781f40735f29bb7fe0e3a6"; + libraryHaskellDepends = [ base gi-gdk gi-gtk text transformers ]; doHaddock = false; doCheck = false; - description = "Haskell 98 groups"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/IvanMalison/gtk-strut#readme"; + description = "Libary for creating strut windows with gi-gtk"; + license = lib.licenses.bsd3; }) {}; "guarded-allocation" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "guarded-allocation"; - version = "0.0"; - sha256 = "5257dbe3088099ee19874d0657513b5662dcd207eff8d8fc426deedc92fb48ba"; + version = "0.0.1"; + sha256 = "0cac10d1790817bdbc44ffe4ee8fcb649e350bb831987ee80739393917784695"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "http://hub.darcs.net/thielema/guarded-allocation/"; description = "Memory allocation with added stress tests and integrity checks"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "gym-http-api" = callPackage - ({ mkDerivation, aeson, base, exceptions, http-client, servant - , servant-client, servant-lucid, stdenv, text, unordered-containers - }: - mkDerivation { - pname = "gym-http-api"; - version = "0.1.0.1"; - sha256 = "2c3fd9b261cd7bc3a004d41f582cd6c629956c78f7236eb91d615ca0c9b0c910"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - aeson base servant servant-client servant-lucid text - unordered-containers - ]; - executableHaskellDepends = [ - base exceptions http-client servant-client - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/stites/gym-http-api#readme"; - description = "REST client to the gym-http-api project"; - license = stdenv.lib.licenses.mit; - }) {}; - "h2c" = callPackage - ({ mkDerivation, base, bytestring, mtl, resourcet, stdenv }: - mkDerivation { - pname = "h2c"; - version = "1.0.0"; - sha256 = "4be2c9d54084175777624770640850aba33d7e4a31e2dc8096c122f737965499"; - libraryHaskellDepends = [ base bytestring mtl resourcet ]; - doHaddock = false; - doCheck = false; - homepage = "https://bitbucket.org/fmapE/h2c"; - description = "Bindings to Linux I2C with support for repeated-start transactions"; - license = stdenv.lib.licenses.mit; - }) {}; - "hOpenPGP" = callPackage - ({ mkDerivation, aeson, asn1-encoding, attoparsec, base - , base16-bytestring, base64-bytestring, bifunctors, binary - , binary-conduit, bytestring, bzlib, conduit, conduit-extra - , containers, crypto-cipher-types, cryptonite, errors, hashable - , incremental-parser, ixset-typed, lens, memory, monad-loops - , nettle, network-uri, newtype, openpgp-asciiarmor, prettyprinter - , resourcet, semigroups, split, stdenv, text, time - , time-locale-compat, transformers, unliftio-core - , unordered-containers, zlib + "hOpenPGP" = callPackage + ({ mkDerivation, aeson, asn1-encoding, attoparsec, base + , base16-bytestring, bifunctors, binary, binary-conduit, bytestring + , bz2, conduit, conduit-extra, containers, crypto-cipher-types + , cryptonite, errors, hashable, incremental-parser, ixset-typed + , lens, lib, memory, monad-loops, nettle, network-uri + , openpgp-asciiarmor, prettyprinter, resourcet, split, text, time + , time-locale-compat, transformers, unliftio-core + , unordered-containers, zlib }: mkDerivation { pname = "hOpenPGP"; - version = "2.7.4.1"; - sha256 = "1aa868310f2c1fe4a768034e8114fe7d5d91479b5f34850c27890537f3419539"; - libraryHaskellDepends = [ - aeson asn1-encoding attoparsec base base16-bytestring - base64-bytestring bifunctors binary binary-conduit bytestring bzlib - conduit conduit-extra containers crypto-cipher-types cryptonite - errors hashable incremental-parser ixset-typed lens memory - monad-loops nettle network-uri newtype openpgp-asciiarmor - prettyprinter resourcet semigroups split text time - time-locale-compat transformers unliftio-core unordered-containers - zlib + version = "2.9.5"; + sha256 = "ddeac93d92323408b264538aef39146bc04b9be0f405ae2bcf481d5fcfa4fbf3"; + libraryHaskellDepends = [ + aeson asn1-encoding attoparsec base base16-bytestring bifunctors + binary binary-conduit bytestring bz2 conduit conduit-extra + containers crypto-cipher-types cryptonite errors hashable + incremental-parser ixset-typed lens memory monad-loops nettle + network-uri openpgp-asciiarmor prettyprinter resourcet split text + time time-locale-compat transformers unliftio-core + unordered-containers zlib ]; doHaddock = false; doCheck = false; homepage = "https://salsa.debian.org/clint/hOpenPGP"; description = "native Haskell implementation of OpenPGP (RFC4880)"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hackage-db" = callPackage ({ mkDerivation, aeson, base, bytestring, Cabal, containers - , directory, filepath, stdenv, tar, time, utf8-string + , directory, exceptions, filepath, lib, tar, time, utf8-string }: mkDerivation { pname = "hackage-db"; - version = "2.0.1"; - sha256 = "f0aac1af6d8d29b7fc2ffd43efaf5a7a5b00f2ead8dacff180bc3714c591ef8d"; + version = "2.1.1"; + sha256 = "6134162fa60efe5ff1d7bbf03afc2403791c4aff031fac9b8429003f168ec19b"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - aeson base bytestring Cabal containers directory filepath tar time - utf8-string + aeson base bytestring Cabal containers directory exceptions + filepath tar time utf8-string ]; doHaddock = false; doCheck = false; homepage = "https://github.com/peti/hackage-db#readme"; - description = "Access Hackage's package database via Data.Map"; - license = stdenv.lib.licenses.bsd3; + description = "Access cabal-install's Hackage database via Data.Map"; + license = lib.licenses.bsd3; }) {}; "hackage-security" = callPackage ({ mkDerivation, base, base16-bytestring, base64-bytestring , bytestring, Cabal, containers, cryptohash-sha256, directory - , ed25519, filepath, ghc-prim, mtl, network, network-uri, parsec - , pretty, stdenv, tar, template-haskell, time, transformers, zlib + , ed25519, filepath, ghc-prim, lib, lukko, mtl, network + , network-uri, parsec, pretty, tar, template-haskell, time + , transformers, zlib }: mkDerivation { pname = "hackage-security"; - version = "0.5.3.0"; - sha256 = "db986e17e9265aa9e40901690815b890b97d53159eb24d0a6cafaa7c18577c21"; - revision = "3"; - editedCabalFile = "07h13j203wafvimfhswpjl2a43iaavy9579hm16z5m565m7f8hwy"; + version = "0.6.0.1"; + sha256 = "9162b473af5a21c1ff32a50b972b9acf51f4c901604a22cf08a2dccac2f82f17"; + revision = "5"; + editedCabalFile = "0vr2fcgp3pjjnp0sy7mvbabqh92215alw62f70pjys9i4z1ks977"; libraryHaskellDepends = [ base base16-bytestring base64-bytestring bytestring Cabal containers cryptohash-sha256 directory ed25519 filepath ghc-prim - mtl network network-uri parsec pretty tar template-haskell time - transformers zlib + lukko mtl network network-uri parsec pretty tar template-haskell + time transformers zlib ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell/hackage-security"; description = "Hackage security library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "haddock-library" = callPackage - ({ mkDerivation, base, bytestring, containers, parsec, stdenv, text + ({ mkDerivation, base, bytestring, containers, lib, parsec, text , transformers }: mkDerivation { pname = "haddock-library"; - version = "1.7.0"; - sha256 = "e7c2794a7eb352824f098cafa07bc0506f2c3633808bfbf4c64aef0ba664d011"; + version = "1.10.0"; + sha256 = "f806c7d5a07d63166101332664c345278f88a5781a640ec3ef215c8fb0015395"; libraryHaskellDepends = [ base bytestring containers parsec text transformers ]; @@ -14753,72 +17179,98 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.haskell.org/haddock/"; description = "Library exposing some functionality of Haddock"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd2; + }) {}; + "hadoop-streaming" = callPackage + ({ mkDerivation, base, bytestring, conduit, extra, lib, text }: + mkDerivation { + pname = "hadoop-streaming"; + version = "0.2.0.3"; + sha256 = "5e33cf6b45b7bb8445485c697ab62e71122b26b9fcbae8dfb6b7461aaf4e93fe"; + libraryHaskellDepends = [ base bytestring conduit extra text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/zliu41/hadoop-streaming"; + description = "A simple Hadoop streaming library"; + license = lib.licenses.bsd3; }) {}; - "hailgun" = callPackage - ({ mkDerivation, aeson, base, bytestring, email-validate - , exceptions, filepath, http-client, http-client-tls, http-types - , stdenv, tagsoup, text, time, transformers + "hakyll-convert" = callPackage + ({ mkDerivation, base, bytestring, cmdargs, containers + , data-default, directory, feed, filepath, lib, text, time + , xml-conduit, xml-types }: mkDerivation { - pname = "hailgun"; - version = "0.4.1.8"; - sha256 = "9dcc7367afec6605045246d4959f27a29a54bbdbcec543e6f5ae59b048e2dcc3"; + pname = "hakyll-convert"; + version = "0.3.0.4"; + sha256 = "694c330bfb43624d9c32ade41d2cb7b12ba2839d27617d47d118e85d0bc8d825"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - aeson base bytestring email-validate exceptions filepath - http-client http-client-tls http-types tagsoup text time - transformers + base bytestring containers data-default directory feed filepath + text time xml-conduit xml-types + ]; + executableHaskellDepends = [ + base cmdargs filepath text xml-types + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/Minoru/hakyll-convert#readme"; + description = "Convert from other blog engines to Hakyll"; + license = lib.licenses.bsd3; + }) {}; + "hal" = callPackage + ({ mkDerivation, aeson, base, base64-bytestring, bytestring + , case-insensitive, conduit, conduit-extra, containers, envy + , exceptions, hashable, http-client, http-types, lib, mtl, text + , time, unordered-containers + }: + mkDerivation { + pname = "hal"; + version = "0.4.8"; + sha256 = "5e6cdf692c668076f9bcb6625d5fbe68cfbd7b132951bf0600bb441b90cb77c8"; + revision = "1"; + editedCabalFile = "0jz54lz3wd05b2vabwlid31pyhvjrwbdr35nbqb9kdf13jfdgahr"; + libraryHaskellDepends = [ + aeson base base64-bytestring bytestring case-insensitive conduit + conduit-extra containers envy exceptions hashable http-client + http-types mtl text time unordered-containers ]; doHaddock = false; doCheck = false; - homepage = "https://bitbucket.org/robertmassaioli/hailgun"; - description = "Mailgun REST api interface for Haskell"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/Nike-inc/hal#readme"; + description = "A runtime environment for Haskell applications running on AWS Lambda"; + license = lib.licenses.bsd3; }) {}; "half" = callPackage - ({ mkDerivation, base, deepseq, stdenv, template-haskell }: + ({ mkDerivation, base, binary, deepseq, lib, template-haskell }: mkDerivation { pname = "half"; - version = "0.3"; - sha256 = "06b26fb062a55fa8f5df1cc2fddc47e5303f09977279f05f62d1950a51b72093"; - libraryHaskellDepends = [ base deepseq template-haskell ]; + version = "0.3.1"; + sha256 = "e2afc32724e11bf5c695d797b9169d9d9b2dc62a530aed31284c8187af1615d1"; + libraryHaskellDepends = [ base binary deepseq template-haskell ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/half"; description = "Half-precision floating-point"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "hamilton" = callPackage - ({ mkDerivation, ad, ansi-wl-pprint, base, containers - , finite-typelits, ghc-typelits-knownnat, hmatrix, hmatrix-gsl - , hmatrix-vector-sized, optparse-applicative, stdenv - , typelits-witnesses, vector, vector-sized, vty - }: + "hall-symbols" = callPackage + ({ mkDerivation, base, lib, matrix, parsec }: mkDerivation { - pname = "hamilton"; - version = "0.1.0.3"; - sha256 = "3c7623217c8e49cabc6620835e53609e7b7339f39a1523da2467076252addb1b"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - ad base hmatrix hmatrix-gsl hmatrix-vector-sized typelits-witnesses - vector-sized - ]; - executableHaskellDepends = [ - ansi-wl-pprint base containers finite-typelits - ghc-typelits-knownnat hmatrix optparse-applicative vector - vector-sized vty - ]; + pname = "hall-symbols"; + version = "0.1.0.6"; + sha256 = "8ab7ebbd081b1e41314cc56f8901b4c42070f532bbc41f408e36535e39e4c0bd"; + libraryHaskellDepends = [ base matrix parsec ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/mstksg/hamilton#readme"; - description = "Physics on generalized coordinate systems using Hamiltonian Mechanics and AD"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/narumij/hall-symbols#readme"; + description = "Symmetry operations generater of Hall Symbols"; + license = lib.licenses.bsd3; }) {}; "hamtsolo" = callPackage ({ mkDerivation, async, attoparsec, attoparsec-binary, base, binary , bytestring, conduit, conduit-combinators, conduit-extra - , exceptions, gitrev, optparse-applicative, resourcet, stdenv + , exceptions, gitrev, lib, optparse-applicative, resourcet , stm-conduit, unix }: mkDerivation { @@ -14836,23 +17288,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/tfc/hamtsolo#readme"; description = "Intel AMT serial-over-lan (SOL) client"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hapistrano" = callPackage - ({ mkDerivation, aeson, async, base, filepath, formatting, gitrev - , mtl, optparse-applicative, path, path-io, process, stdenv, stm - , time, transformers, typed-process, yaml + ({ mkDerivation, aeson, ansi-terminal, async, base, filepath + , formatting, gitrev, lib, mtl, optparse-applicative, path, path-io + , process, stm, time, transformers, typed-process, yaml }: mkDerivation { pname = "hapistrano"; - version = "0.3.9.0"; - sha256 = "7eac3f9c870445693ec2c4b1ed9cbb91b18bc96e54a71cd9dfdaca8b05566485"; + version = "0.4.2.0"; + sha256 = "90cfe686ab69289b697f7222c24117560d4ba7b46896232a660aca2b2c5043b8"; isLibrary = true; isExecutable = true; enableSeparateDataOutput = true; libraryHaskellDepends = [ - aeson base filepath formatting gitrev mtl path process stm time - transformers typed-process + aeson ansi-terminal base filepath gitrev mtl path process stm time + transformers typed-process yaml ]; executableHaskellDepends = [ aeson async base formatting gitrev optparse-applicative path @@ -14862,38 +17314,99 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/stackbuilders/hapistrano"; description = "A deployment library for Haskell applications"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "happstack-server" = callPackage + ({ mkDerivation, base, base64-bytestring, blaze-html, bytestring + , containers, directory, exceptions, extensible-exceptions + , filepath, hslogger, html, lib, monad-control, mtl, network + , network-uri, old-locale, parsec, process, semigroups, sendfile + , syb, system-filepath, text, threads, time, transformers + , transformers-base, transformers-compat, unix, utf8-string, xhtml + , zlib + }: + mkDerivation { + pname = "happstack-server"; + version = "7.7.1.1"; + sha256 = "36711c7d02901e774c6916b7f5b5246e62802a1902b76ae31d35d19fb7cd8559"; + libraryHaskellDepends = [ + base base64-bytestring blaze-html bytestring containers directory + exceptions extensible-exceptions filepath hslogger html + monad-control mtl network network-uri old-locale parsec process + semigroups sendfile syb system-filepath text threads time + transformers transformers-base transformers-compat unix utf8-string + xhtml zlib + ]; + doHaddock = false; + doCheck = false; + homepage = "http://happstack.com"; + description = "Web related tools and services"; + license = lib.licenses.bsd3; }) {}; "happy" = callPackage - ({ mkDerivation, array, base, Cabal, containers, directory - , filepath, mtl, stdenv - }: + ({ mkDerivation, array, base, containers, lib, mtl }: mkDerivation { pname = "happy"; - version = "1.19.9"; - sha256 = "3e81a3e813acca3aae52721c412cde18b7b7c71ecbacfaeaa5c2f4b35abf1d8d"; - revision = "3"; - editedCabalFile = "0kwlh964nyqvfbm02np8vpc28gbhsby0r65jhz1918rm0wip9izq"; + version = "1.20.0"; + sha256 = "3b1d3a8f93a2723b554d9f07b2cd136be1a7b2fcab1855b12b7aab5cbac8868c"; isLibrary = false; isExecutable = true; - setupHaskellDepends = [ base Cabal directory filepath ]; + enableSeparateDataOutput = true; executableHaskellDepends = [ array base containers mtl ]; doHaddock = false; doCheck = false; homepage = "https://www.haskell.org/happy/"; description = "Happy is a parser generator for Haskell"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; + }) {}; + "happy-meta" = callPackage + ({ mkDerivation, array, base, containers, fail, happy + , haskell-src-meta, lib, mtl, template-haskell + }: + mkDerivation { + pname = "happy-meta"; + version = "0.2.0.11"; + sha256 = "23894127ae789ae6aa37f7da174eb8df535021f0aff13fa0e3477917ba2bfbed"; + revision = "1"; + editedCabalFile = "1dspifamwsn6lcj2mxjyrbdsfjqfb4p6m0s1c9dkiv08cfkk02p6"; + libraryHaskellDepends = [ + array base containers fail haskell-src-meta mtl template-haskell + ]; + libraryToolDepends = [ happy ]; + doHaddock = false; + doCheck = false; + description = "Quasi-quoter for Happy parsers"; + license = lib.licenses.bsd3; + }) {}; + "hasbolt" = callPackage + ({ mkDerivation, base, binary, bytestring, connection, containers + , data-binary-ieee754, data-default, deepseq, deepseq-generics, lib + , mtl, network, text + }: + mkDerivation { + pname = "hasbolt"; + version = "0.1.6.1"; + sha256 = "00896fb8ba449dffc570965bcd94de53026848615240ab0608e3927f048f76ea"; + libraryHaskellDepends = [ + base binary bytestring connection containers data-binary-ieee754 + data-default deepseq deepseq-generics mtl network text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/zmactep/hasbolt#readme"; + description = "Haskell driver for Neo4j 3+ (BOLT protocol)"; + license = lib.licenses.bsd3; }) {}; "hashable" = callPackage ({ mkDerivation, base, bytestring, deepseq, ghc-prim, integer-gmp - , stdenv, text + , lib, text }: mkDerivation { pname = "hashable"; - version = "1.2.7.0"; - sha256 = "ecb5efc0586023f5a0dc861100621c1dbb4cbb2f0516829a16ebac39f0432abf"; - revision = "1"; - editedCabalFile = "197063dpl0wn67dp7a06yc2hxp81n24ykk7klbjx0fndm5n87dh3"; + version = "1.3.0.0"; + sha256 = "822e5413fbccca6ae884d3aba4066422c8b5d58d23d18b9ecb5c03273bb19ab4"; + revision = "2"; + editedCabalFile = "16va8hx4ynw0n5s2warhs13ilj7hrs5fcdn140h1fiix480as36n"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -14903,22 +17416,24 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/tibbe/hashable"; description = "A class for types that can be converted to a hash value"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hashable-time" = callPackage - ({ mkDerivation, base, hashable, stdenv, time }: + ({ mkDerivation, base, hashable, lib, time, time-compat }: mkDerivation { pname = "hashable-time"; - version = "0.2.0.2"; - sha256 = "fa61f7fbd493b5a54f2aeb10e0c1c4144111ecf34e74080d12c5738ce925fee0"; - libraryHaskellDepends = [ base hashable time ]; + version = "0.2.1"; + sha256 = "b07bd12b8c8e7ab03957b0def13a2b61590dabf19be6d21f0c98affb147e82ff"; + revision = "1"; + editedCabalFile = "151gxiprdlj3masa95vvrxal9nwa72n3p1y15xyj4hp7mvvl4s2l"; + libraryHaskellDepends = [ base hashable time time-compat ]; doHaddock = false; doCheck = false; description = "Hashable instances for Data.Time"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hashids" = callPackage - ({ mkDerivation, base, bytestring, containers, split, stdenv }: + ({ mkDerivation, base, bytestring, containers, lib, split }: mkDerivation { pname = "hashids"; version = "1.0.2.4"; @@ -14928,10 +17443,30 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://hashids.org/"; description = "Hashids generates short, unique, non-sequential ids from numbers"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "hashing" = callPackage + ({ mkDerivation, array, base, bytestring, lib, mtl, QuickCheck }: + mkDerivation { + pname = "hashing"; + version = "0.1.0.1"; + sha256 = "e5a4a19c6cd6f0a0adda381db76d608d23f8d303e68f1d744735433f91f49410"; + revision = "2"; + editedCabalFile = "1rwl68jiivw7f2f5cg73sr3dawlbmklnwyiwivrcsihrg4b1z1lq"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ array base bytestring ]; + executableHaskellDepends = [ + array base bytestring mtl QuickCheck + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/wangbj/hashing"; + description = "A pure haskell library implements several hash algorithms"; + license = lib.licenses.mit; }) {}; "hashmap" = callPackage - ({ mkDerivation, base, containers, deepseq, hashable, stdenv }: + ({ mkDerivation, base, containers, deepseq, hashable, lib }: mkDerivation { pname = "hashmap"; version = "1.3.3"; @@ -14941,16 +17476,15 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/foxik/hashmap"; description = "Persistent containers Map and Set based on hashing"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hashtables" = callPackage - ({ mkDerivation, base, ghc-prim, hashable, primitive, stdenv - , vector + ({ mkDerivation, base, ghc-prim, hashable, lib, primitive, vector }: mkDerivation { pname = "hashtables"; - version = "1.2.3.1"; - sha256 = "8fd1c7c77c267eae6af01f1d9ca427754fb092cfffc8041cd50764a9144b3cbe"; + version = "1.2.4.1"; + sha256 = "0ac3bf86030eeb1dd0f3d0cd1967cb610ee9564251622371fda560bc4e7def6d"; libraryHaskellDepends = [ base ghc-prim hashable primitive vector ]; @@ -14958,66 +17492,98 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/gregorycollins/hashtables"; description = "Mutable hash tables in the ST monad"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "haskeline" = callPackage - ({ mkDerivation, base, bytestring, containers, directory, filepath - , process, stdenv, stm, terminfo, transformers, unix + ({ mkDerivation, base, bytestring, containers, directory + , exceptions, filepath, lib, process, stm, terminfo, transformers + , unix }: mkDerivation { pname = "haskeline"; - version = "0.7.4.3"; - sha256 = "046d0930bc2dbc57a7cd9ddb5d1e92c7fdb71c6b91b2bbf673f5406843d6b679"; + version = "0.8.1.2"; + sha256 = "d766794c9c471173ad8cd5ebd49b679e269306198f742ecfc03a73a45011b92b"; configureFlags = [ "-fterminfo" ]; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - base bytestring containers directory filepath process stm terminfo - transformers unix + base bytestring containers directory exceptions filepath process + stm terminfo transformers unix ]; + executableHaskellDepends = [ base containers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/judah/haskeline"; description = "A command-line interface for user input, written in Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "haskell-awk" = callPackage + ({ mkDerivation, base, bytestring, Cabal, cabal-doctest, containers + , directory, extra, filelock, filepath, ghc, haskell-src-exts, hint + , lib, list-t, mtl, process, stringsearch, template-haskell + , transformers + }: + mkDerivation { + pname = "haskell-awk"; + version = "1.2.0.1"; + sha256 = "34f1ccd129ff901b6b4a94af0a897ef883efb80a9905c49c01f329bcfed690e4"; + isLibrary = true; + isExecutable = true; + setupHaskellDepends = [ base Cabal cabal-doctest ]; + libraryHaskellDepends = [ + base bytestring containers ghc list-t stringsearch + ]; + executableHaskellDepends = [ + base bytestring containers directory extra filelock filepath ghc + haskell-src-exts hint list-t mtl process template-haskell + transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/gelisam/hawk#readme"; + description = "Transform text from the command-line using Haskell expressions"; + license = lib.licenses.asl20; }) {}; "haskell-gi" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, Cabal, containers - , directory, filepath, glib, gobjectIntrospection, haskell-gi-base - , mtl, pretty-show, process, regex-tdfa, safe, stdenv, text - , transformers, xdg-basedir, xml-conduit + ({ mkDerivation, ansi-terminal, attoparsec, base, bytestring, Cabal + , cabal-doctest, containers, directory, filepath, glib + , gobject-introspection, haskell-gi-base, lib, mtl, pretty-show + , process, regex-tdfa, safe, text, transformers, xdg-basedir + , xml-conduit }: mkDerivation { pname = "haskell-gi"; - version = "0.21.5"; - sha256 = "12d116c6effae4da3f97afaad46faab6766f4a58be2c8fb434f8e0feea4a71e7"; + version = "0.25.0"; + sha256 = "c8c65b4d9a27fc3547421f876a2efd8c031d0e198b9d227d755c26b9425cbeaf"; + setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ - attoparsec base bytestring Cabal containers directory filepath - haskell-gi-base mtl pretty-show process regex-tdfa safe text - transformers xdg-basedir xml-conduit + ansi-terminal attoparsec base bytestring Cabal containers directory + filepath haskell-gi-base mtl pretty-show process regex-tdfa safe + text transformers xdg-basedir xml-conduit ]; - libraryPkgconfigDepends = [ glib gobjectIntrospection ]; + libraryPkgconfigDepends = [ glib gobject-introspection ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-gi/haskell-gi"; description = "Generate Haskell bindings for GObject Introspection capable libraries"; - license = stdenv.lib.licenses.lgpl21; - }) {inherit (pkgs) glib; inherit (pkgs) gobjectIntrospection;}; + license = lib.licenses.lgpl21Only; + }) {inherit (pkgs) glib; inherit (pkgs) gobject-introspection;}; "haskell-gi-base" = callPackage - ({ mkDerivation, base, bytestring, containers, glib, stdenv, text - }: + ({ mkDerivation, base, bytestring, containers, glib, lib, text }: mkDerivation { pname = "haskell-gi-base"; - version = "0.21.5"; - sha256 = "f04d372ce57821f84524d7191b769ee2ae7f14dd1db5c306cadd771625e5b6df"; + version = "0.25.0"; + sha256 = "1e57c4e132c67995f3a299493fd69e5d7b801323374452e44e232783ab320e90"; libraryHaskellDepends = [ base bytestring containers text ]; libraryPkgconfigDepends = [ glib ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/haskell-gi/haskell-gi-base"; + homepage = "https://github.com/haskell-gi/haskell-gi"; description = "Foundation for libraries generated by haskell-gi"; - license = stdenv.lib.licenses.lgpl21; + license = lib.licenses.lgpl21Only; }) {inherit (pkgs) glib;}; "haskell-gi-overloading" = callPackage - ({ mkDerivation, stdenv }: + ({ mkDerivation, lib }: mkDerivation { pname = "haskell-gi-overloading"; version = "1.0"; @@ -15026,77 +17592,94 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/haskell-gi/haskell-gi"; description = "Overloading support for haskell-gi"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "haskell-import-graph" = callPackage + ({ mkDerivation, base, classy-prelude, ghc, graphviz, lib, process + , text, transformers + }: + mkDerivation { + pname = "haskell-import-graph"; + version = "1.0.4"; + sha256 = "a036cde19d89ba30f9810bff5e5bdfb35eeaa3df6fa234303da76385d22c4c9d"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base classy-prelude ghc graphviz process text transformers + ]; + executableHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ncaq/haskell-import-graph#readme"; + description = "create haskell import graph for graphviz"; + license = lib.licenses.mit; }) {}; "haskell-lexer" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "haskell-lexer"; - version = "1.0.2"; - sha256 = "d8cdf3122ee384ec440269108fd85ccf207a413015ceeffb2e9bf4313a6addf3"; + version = "1.1"; + sha256 = "313a15cc643322c8badd148867ce25ca1ffc191df9e7eeec5b10bc08c4b563d5"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/yav/haskell-lexer"; description = "A fully compliant Haskell 98 lexer"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "haskell-lsp" = callPackage - ({ mkDerivation, aeson, base, bytestring, containers, data-default - , directory, filepath, hashable, haskell-lsp-types, hslogger, lens - , mtl, network-uri, parsec, sorted-list, stdenv, stm, text, time - , transformers, unordered-containers, vector, yi-rope + ({ mkDerivation, aeson, async, attoparsec, base, bytestring + , containers, data-default, directory, filepath, hashable + , haskell-lsp-types, hslogger, lens, lib, mtl, network-uri + , rope-utf16-splay, sorted-list, stm, temporary, text, time + , unordered-containers }: mkDerivation { pname = "haskell-lsp"; - version = "0.8.0.1"; - sha256 = "18f1fd93ef7191dfe5feca9d58fbff9aeee60db226238a9082bb976d6ec779d3"; + version = "0.24.0.0"; + sha256 = "2fde650a1f7405c663cb3ca4224bae5be63c387d83d3e8c8c60086e47942823f"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - aeson base bytestring containers data-default directory filepath - hashable haskell-lsp-types hslogger lens mtl network-uri parsec - sorted-list stm text time unordered-containers yi-rope - ]; - executableHaskellDepends = [ - aeson base bytestring containers data-default directory filepath - hslogger lens mtl network-uri parsec stm text time transformers - unordered-containers vector yi-rope + aeson async attoparsec base bytestring containers data-default + directory filepath hashable haskell-lsp-types hslogger lens mtl + network-uri rope-utf16-splay sorted-list stm temporary text time + unordered-containers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/alanz/haskell-lsp"; description = "Haskell library for the Microsoft Language Server Protocol"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "haskell-lsp-types" = callPackage - ({ mkDerivation, aeson, base, bytestring, data-default, filepath - , hashable, lens, network-uri, scientific, stdenv, text - , unordered-containers + ({ mkDerivation, aeson, base, binary, bytestring, data-default + , deepseq, filepath, hashable, lens, lib, network-uri, scientific + , text, unordered-containers }: mkDerivation { pname = "haskell-lsp-types"; - version = "0.8.0.1"; - sha256 = "c8a3fec8c38ebe7da931e14e9b0381acde33882d2a46ced5ece5fe9fb133f033"; + version = "0.24.0.0"; + sha256 = "764d51c6b0e52bbafe042f10ad69fdaddcc31007d78a6fada6be24ddc513f3dc"; libraryHaskellDepends = [ - aeson base bytestring data-default filepath hashable lens - network-uri scientific text unordered-containers + aeson base binary bytestring data-default deepseq filepath hashable + lens network-uri scientific text unordered-containers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/alanz/haskell-lsp"; description = "Haskell library for the Microsoft Language Server Protocol, data types"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "haskell-names" = callPackage ({ mkDerivation, aeson, base, bytestring, containers - , data-lens-light, filepath, haskell-src-exts, mtl, stdenv + , data-lens-light, filepath, haskell-src-exts, lib, mtl , transformers, traverse-with-class, uniplate }: mkDerivation { pname = "haskell-names"; - version = "0.9.4"; - sha256 = "1e3d9a393b677981cf7e77d54306b041983abe6ba371148095a754ed7b2e6e35"; + version = "0.9.9"; + sha256 = "151e9925f437b85a87e3131582ee804c05741e08c679610433e4b1ff213f103f"; enableSeparateDataOutput = true; libraryHaskellDepends = [ aeson base bytestring containers data-lens-light filepath @@ -15106,60 +17689,45 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://documentup.com/haskell-suite/haskell-names"; description = "Name resolution library for Haskell"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "haskell-spacegoo" = callPackage - ({ mkDerivation, aeson, base, bytestring, conduit, conduit-extra - , mtl, pretty, pretty-show, stdenv, text, vector, vector-space - }: - mkDerivation { - pname = "haskell-spacegoo"; - version = "0.2.0.1"; - sha256 = "1eb3faa9a7f6a5870337eeb0bb3ad915f58987dfe4643fe95c91cbb2738ddd3c"; - libraryHaskellDepends = [ - aeson base bytestring conduit conduit-extra mtl pretty pretty-show - text vector vector-space - ]; - doHaddock = false; - doCheck = false; - description = "Client API for Rocket Scissor Spacegoo"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.bsd3; }) {}; "haskell-src" = callPackage - ({ mkDerivation, array, base, happy, pretty, stdenv, syb }: + ({ mkDerivation, array, base, happy, lib, pretty, syb }: mkDerivation { pname = "haskell-src"; - version = "1.0.3.0"; - sha256 = "b4b4941e8883da32c3f2b93f3ecdd5cff82ff9304cb91e89850b19095c908dbc"; + version = "1.0.3.1"; + sha256 = "869cc710004c2161470d8a788dab96d2cff054fa106c301be6689109f57e5132"; + revision = "3"; + editedCabalFile = "0hjridmgm95lrb9qs972zicipsqcfwpr35gwkzxncpgwcm0vn0b6"; libraryHaskellDepends = [ array base pretty syb ]; libraryToolDepends = [ happy ]; doHaddock = false; doCheck = false; description = "Support for manipulating Haskell source code"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "haskell-src-exts" = callPackage - ({ mkDerivation, array, base, ghc-prim, happy, pretty, stdenv }: + ({ mkDerivation, array, base, ghc-prim, happy, lib, pretty }: mkDerivation { pname = "haskell-src-exts"; - version = "1.20.3"; - sha256 = "433e68a731fb6a1435e86d3eb3b2878db9c5d51dc1f7499d85bbf5ac3ed1e4a8"; + version = "1.23.1"; + sha256 = "67853047169fff7d3e5d87acef214ee185a6ab8c6a104ed9c59e389574cf6c05"; libraryHaskellDepends = [ array base ghc-prim pretty ]; libraryToolDepends = [ happy ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-suite/haskell-src-exts"; description = "Manipulating Haskell source: abstract syntax, lexer, parser, and pretty-printer"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "haskell-src-exts-util" = callPackage ({ mkDerivation, base, containers, data-default, haskell-src-exts - , semigroups, stdenv, transformers, uniplate + , lib, semigroups, transformers, uniplate }: mkDerivation { pname = "haskell-src-exts-util"; - version = "0.2.4"; - sha256 = "beb8af3a29322c72a9c9ac9988953c5aacc8f3b882780dd4f03f621d15126ef5"; + version = "0.2.5"; + sha256 = "c802f9ec4e05668e3eeb2cbb0a827f342854211315f9bb74c1e79253c589783b"; libraryHaskellDepends = [ base containers data-default haskell-src-exts semigroups transformers uniplate @@ -15168,34 +17736,32 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/pepeiborra/haskell-src-exts-util"; description = "Helper functions for working with haskell-src-exts trees"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "haskell-src-meta" = callPackage - ({ mkDerivation, base, haskell-src-exts, pretty, stdenv, syb + ({ mkDerivation, base, haskell-src-exts, lib, pretty, syb , template-haskell, th-orphans }: mkDerivation { pname = "haskell-src-meta"; - version = "0.8.0.3"; - sha256 = "8473e3555080860c2043581b398dbab67319584a568463b074a092fd4d095822"; - revision = "2"; - editedCabalFile = "0dp5v0yd0wgijzaggr22glgjswpa65hy84h8awdzd9d78g2fjz6c"; + version = "0.8.7"; + sha256 = "361ad6f1ff47c89228e3b1e7beff52a5940484480f09d847c73fdc18966bc2fb"; libraryHaskellDepends = [ base haskell-src-exts pretty syb template-haskell th-orphans ]; doHaddock = false; doCheck = false; description = "Parse source to template-haskell abstract syntax"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "haskey-btree" = callPackage ({ mkDerivation, base, binary, bytestring, containers, hashable - , mtl, semigroups, stdenv, text, transformers, vector + , lib, mtl, semigroups, text, transformers, vector }: mkDerivation { pname = "haskey-btree"; - version = "0.3.0.0"; - sha256 = "90387d9a8e2afb22f9a4ace4b8f3b1a2045b955c1283c70a614abeff2294465a"; + version = "0.3.0.1"; + sha256 = "35f54cf51b0cd66361b29e21ebcd0603ab2396028e58ab667ac709591491f387"; libraryHaskellDepends = [ base binary bytestring containers hashable mtl semigroups text transformers vector @@ -15204,64 +17770,58 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/haskell-haskey/haskey-btree"; description = "B+-tree implementation in Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "haskoin-core" = callPackage - ({ mkDerivation, aeson, array, base, base16-bytestring, bytestring - , cereal, conduit, containers, cryptonite, entropy, hashable - , memory, mtl, murmur3, network, QuickCheck, scientific - , secp256k1-haskell, split, stdenv, string-conversions, text, time - , transformers, unordered-containers, vector + "hasql" = callPackage + ({ mkDerivation, attoparsec, base, bytestring + , bytestring-strict-builder, contravariant, dlist, hashable + , hashtables, lib, mtl, postgresql-binary, postgresql-libpq + , profunctors, text, text-builder, transformers, vector }: mkDerivation { - pname = "haskoin-core"; - version = "0.8.4"; - sha256 = "5c2746a075af13a7b40fa4592ba4f3c0ee5599ee6177c1f6bcbb7b6ec45fea42"; + pname = "hasql"; + version = "1.4.5.1"; + sha256 = "f453787f66be5db9e7feedd0a7c7fc0ed13aa1c974dfdf644e81e095c4c44378"; libraryHaskellDepends = [ - aeson array base base16-bytestring bytestring cereal conduit - containers cryptonite entropy hashable memory mtl murmur3 network - QuickCheck scientific secp256k1-haskell split string-conversions - text time transformers unordered-containers vector + attoparsec base bytestring bytestring-strict-builder contravariant + dlist hashable hashtables mtl postgresql-binary postgresql-libpq + profunctors text text-builder transformers vector ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/haskoin/haskoin#readme"; - description = "Bitcoin & Bitcoin Cash library for Haskell"; - license = stdenv.lib.licenses.publicDomain; + homepage = "https://github.com/nikita-volkov/hasql"; + description = "An efficient PostgreSQL driver with a flexible mapping API"; + license = lib.licenses.mit; }) {}; - "hasql" = callPackage - ({ mkDerivation, attoparsec, base, base-prelude, bytestring - , bytestring-strict-builder, contravariant, contravariant-extras - , data-default-class, dlist, hashable, hashtables, loch-th, mtl - , placeholders, postgresql-binary, postgresql-libpq, profunctors - , stdenv, text, text-builder, transformers, vector + "hasql-notifications" = callPackage + ({ mkDerivation, base, bytestring, contravariant, hasql, hasql-pool + , lib, postgresql-libpq, text }: mkDerivation { - pname = "hasql"; - version = "1.3.0.3"; - sha256 = "519ac7c3b06dec89fcd4c881328c2b77c8f74ef34faaba2a4395417fcc257407"; - revision = "2"; - editedCabalFile = "14063k0dald0i2cqk70kdja1df587vn8vrzgw3rb62nxwycr0r9b"; + pname = "hasql-notifications"; + version = "0.2.0.0"; + sha256 = "b133e38b7a27e66385332791bb03c4a3cf4f85994412318d08cd820577db3ffe"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - attoparsec base base-prelude bytestring bytestring-strict-builder - contravariant contravariant-extras data-default-class dlist - hashable hashtables loch-th mtl placeholders postgresql-binary - postgresql-libpq profunctors text text-builder transformers vector + base bytestring contravariant hasql hasql-pool postgresql-libpq + text ]; + executableHaskellDepends = [ base hasql ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/nikita-volkov/hasql"; - description = "An efficient PostgreSQL driver and a flexible mapping API"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/diogob/hasql-notifications"; + description = "LISTEN/NOTIFY support for Hasql"; + license = lib.licenses.bsd3; }) {}; "hasql-optparse-applicative" = callPackage - ({ mkDerivation, base-prelude, hasql, hasql-pool - , optparse-applicative, stdenv + ({ mkDerivation, base-prelude, hasql, hasql-pool, lib + , optparse-applicative }: mkDerivation { pname = "hasql-optparse-applicative"; - version = "0.3.0.3"; - sha256 = "63b4c3da21434bac9a98521cdcfda7815bcebb8829feb889f4050fffd7f06334"; + version = "0.3.0.6"; + sha256 = "29e39883c6b1be4e7ce37bf384ce1846e8a7282a644adfa2a6762b74b198669a"; libraryHaskellDepends = [ base-prelude hasql hasql-pool optparse-applicative ]; @@ -15269,49 +17829,77 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/sannsyn/hasql-optparse-applicative"; description = "\"optparse-applicative\" parsers for \"hasql\""; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hasql-pool" = callPackage - ({ mkDerivation, base-prelude, hasql, resource-pool, stdenv, time - }: + ({ mkDerivation, base-prelude, hasql, lib, resource-pool, time }: mkDerivation { pname = "hasql-pool"; - version = "0.5"; - sha256 = "3a33cdfc9ae253f193afb824c9488051103b4c71316b6db39d51dce27c825d2f"; + version = "0.5.2"; + sha256 = "9ff2140407f88ca46769069d00314a85e18a7e759de5f7179f6a14854a030751"; libraryHaskellDepends = [ base-prelude hasql resource-pool time ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nikita-volkov/hasql-pool"; description = "A pool of connections for Hasql"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "hasql-queue" = callPackage + ({ mkDerivation, aeson, async, base, base64-bytestring, bytestring + , cryptohash-sha1, exceptions, hasql, here, lib, monad-control + , postgresql-libpq, postgresql-libpq-notify, random, resource-pool + , stm, text, time, tmp-postgres, transformers + }: + mkDerivation { + pname = "hasql-queue"; + version = "1.2.0.2"; + sha256 = "b5d843d2e759153e4cedd6860c34af774ef965b4bdcb2cb6080f362f92a31e35"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson base bytestring exceptions hasql here monad-control + postgresql-libpq postgresql-libpq-notify random stm text time + transformers + ]; + executableHaskellDepends = [ + aeson async base base64-bytestring bytestring cryptohash-sha1 + exceptions hasql here monad-control postgresql-libpq + postgresql-libpq-notify random resource-pool stm text time + tmp-postgres transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jfischoff/hasql-queue#readme"; + description = "A PostgreSQL backed queue"; + license = lib.licenses.bsd3; }) {}; "hasql-transaction" = callPackage - ({ mkDerivation, base, base-prelude, bytestring - , bytestring-tree-builder, contravariant, contravariant-extras - , hasql, mtl, stdenv, transformers + ({ mkDerivation, base, bytestring, bytestring-tree-builder + , contravariant, contravariant-extras, hasql, lib, mtl + , transformers }: mkDerivation { pname = "hasql-transaction"; - version = "0.7"; - sha256 = "decb3c5b08f710413ee65861c30766c53dc79d05f388fab6f8e1105e4d907fcf"; + version = "1.0.1"; + sha256 = "3a4d6902ba85734fc8047fd71c0071a1b3b271e60eefe77a9670a59da5e803a9"; libraryHaskellDepends = [ - base base-prelude bytestring bytestring-tree-builder contravariant + base bytestring bytestring-tree-builder contravariant contravariant-extras hasql mtl transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nikita-volkov/hasql-transaction"; - description = "A composable abstraction over the retryable transactions for Hasql"; - license = stdenv.lib.licenses.mit; + description = "Composable abstraction over retryable transactions for Hasql"; + license = lib.licenses.mit; }) {}; "hasty-hamiltonian" = callPackage - ({ mkDerivation, base, kan-extensions, lens, mcmc-types - , mwc-probability, pipes, primitive, stdenv, transformers + ({ mkDerivation, base, kan-extensions, lens, lib, mcmc-types + , mwc-probability, pipes, primitive, transformers }: mkDerivation { pname = "hasty-hamiltonian"; - version = "1.3.2"; - sha256 = "e6299d72e145cfabea798e2088284580fc65f01638e3562e1f01cf9df018cc9e"; + version = "1.3.4"; + sha256 = "f82be55cbb74e57b5352f997f80a34030d74be51411781b100988e205a817863"; libraryHaskellDepends = [ base kan-extensions lens mcmc-types mwc-probability pipes primitive transformers @@ -15320,66 +17908,76 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/jtobin/hasty-hamiltonian"; description = "Speedy traversal through parameter space"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "haxl" = callPackage - ({ mkDerivation, aeson, base, binary, bytestring, containers - , deepseq, exceptions, filepath, ghc-prim, hashable, pretty, stdenv - , stm, text, time, transformers, unordered-containers, vector + "haxr" = callPackage + ({ mkDerivation, array, base, base-compat, base64-bytestring + , blaze-builder, bytestring, HaXml, HsOpenSSL, http-streams + , http-types, io-streams, lib, mtl, mtl-compat, network + , network-uri, old-locale, old-time, template-haskell, text, time + , utf8-string }: mkDerivation { - pname = "haxl"; - version = "2.0.1.1"; - sha256 = "59f30d1bde6c70736071ccf3b561776d1a060af4c5a854c66664df1a47e4d6f1"; - isLibrary = true; - isExecutable = true; + pname = "haxr"; + version = "3000.11.4.1"; + sha256 = "1ef6ee518720c6f5959169fd7fde7e7641ff71f8c02c20e645a88f221853c389"; libraryHaskellDepends = [ - aeson base binary bytestring containers deepseq exceptions filepath - ghc-prim hashable pretty stm text time transformers - unordered-containers vector + array base base-compat base64-bytestring blaze-builder bytestring + HaXml HsOpenSSL http-streams http-types io-streams mtl mtl-compat + network network-uri old-locale old-time template-haskell text time + utf8-string ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/facebook/Haxl"; - description = "A Haskell library for efficient, concurrent, and concise data access"; - license = stdenv.lib.licenses.bsd3; + homepage = "http://www.haskell.org/haskellwiki/HaXR"; + description = "XML-RPC client and server library"; + license = lib.licenses.bsd3; }) {}; - "hbeanstalk" = callPackage - ({ mkDerivation, attoparsec, base, blaze-builder, bytestring - , containers, network, stdenv + "hdaemonize" = callPackage + ({ mkDerivation, base, bytestring, extensible-exceptions, filepath + , hsyslog, lib, mtl, unix }: mkDerivation { - pname = "hbeanstalk"; - version = "0.2.4"; - sha256 = "feaf97fd18fedb3e5abf337e61c98a03108d917d9f87f885c8d02b6b838aac8f"; + pname = "hdaemonize"; + version = "0.5.6"; + sha256 = "ad6f302492a9c41e99ce62ca955a959b0cdca0ff328e66f31bfec5a99f7cee24"; libraryHaskellDepends = [ - attoparsec base blaze-builder bytestring containers network + base bytestring extensible-exceptions filepath hsyslog mtl unix ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/scsibug/hbeanstalk/"; - description = "Client for the beanstalkd workqueue service"; - license = stdenv.lib.licenses.bsd3; + homepage = "http://github.com/unprolix/hdaemonize"; + description = "Library to handle the details of writing daemons for UNIX"; + license = lib.licenses.bsd3; }) {}; - "hdaemonize" = callPackage - ({ mkDerivation, base, bytestring, extensible-exceptions, filepath - , hsyslog, mtl, stdenv, unix + "headroom" = callPackage + ({ mkDerivation, aeson, base, either, extra, file-embed + , generic-data, http-client, http-types, lib, microlens + , microlens-th, modern-uri, mtl, mustache, optparse-applicative + , pcre-heavy, pcre-light, req, rio, string-interpolate + , template-haskell, time, vcs-ignore, yaml }: mkDerivation { - pname = "hdaemonize"; - version = "0.5.5"; - sha256 = "d250cb0c066ec45aa9b8e9e0df094677f9e7788b01eaf51ab5bc9bbd52fe029f"; + pname = "headroom"; + version = "0.4.2.0"; + sha256 = "40de3905173c40c473128181e619a0f01c1d6ac9e8a1495d500152a3eeb0e1e5"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - base bytestring extensible-exceptions filepath hsyslog mtl unix + aeson base either extra file-embed generic-data http-client + http-types microlens microlens-th modern-uri mtl mustache + optparse-applicative pcre-heavy pcre-light req rio + string-interpolate template-haskell time vcs-ignore yaml ]; + executableHaskellDepends = [ base optparse-applicative rio ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/greydot/hdaemonize"; - description = "Library to handle the details of writing daemons for UNIX"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/vaclavsvejcar/headroom"; + description = "License Header Manager"; + license = lib.licenses.bsd3; }) {}; "heap" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "heap"; version = "1.0.4"; @@ -15388,100 +17986,158 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Heaps in Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "heaps" = callPackage - ({ mkDerivation, base, Cabal, cabal-doctest, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "heaps"; - version = "0.3.6"; - sha256 = "181c3cd7f2be698f903dc9649e5ec9311245ad2b9fed91b61f05d0dd7b7dddb2"; - revision = "3"; - editedCabalFile = "0k6wsm1hwn3vaxdvw8p7cidxg7p8zply2ig4w4qrbpyjhl6dj9x9"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "0.4"; + sha256 = "89329df8b95ae99ef272e41e7a2d0fe2f1bb7eacfcc34bc01664414b33067cfd"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/heaps/"; description = "Asymptotically optimal Brodal/Okasaki heaps"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hebrew-time" = callPackage - ({ mkDerivation, base, stdenv, time }: + ({ mkDerivation, base, lib, time }: mkDerivation { pname = "hebrew-time"; - version = "0.1.1"; - sha256 = "c7997ee86df43d5d734df63c5e091543bb7fd75a93d530c1857067e27a8b7932"; + version = "0.1.2"; + sha256 = "4316e2ab829a7344900fe15966460bc553e3a60989a14c08ecadf00d2674462b"; libraryHaskellDepends = [ base time ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/snoyberg/hebrew-time"; + homepage = "https://github.com/snoyberg/hebrew-time#readme"; description = "Hebrew dates and prayer times"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hedgehog" = callPackage ({ mkDerivation, ansi-terminal, async, base, bytestring - , concurrent-output, containers, directory, exceptions - , lifted-async, mmorph, monad-control, mtl, pretty-show, primitive - , random, resourcet, semigroups, stdenv, stm, template-haskell - , text, th-lift, time, transformers, transformers-base, unix - , wl-pprint-annotated + , concurrent-output, containers, deepseq, directory, erf + , exceptions, lib, lifted-async, mmorph, monad-control, mtl + , pretty-show, primitive, random, resourcet, stm, template-haskell + , text, time, transformers, transformers-base, wl-pprint-annotated }: mkDerivation { pname = "hedgehog"; - version = "0.6.1"; - sha256 = "d2f94024906af37fed427fa1f03177d9a530078a2e54cfb24d7397da9807e177"; - revision = "2"; - editedCabalFile = "1l0iw2jqdvxgfysfvp1x0s2pq3kyvpapjdjkx9pi4bkxpjpkvbza"; + version = "1.0.5"; + sha256 = "263a487be22f2626bc0e719096d8c230c1bd374a91332404af7ca85e29d258e3"; libraryHaskellDepends = [ ansi-terminal async base bytestring concurrent-output containers - directory exceptions lifted-async mmorph monad-control mtl - pretty-show primitive random resourcet semigroups stm - template-haskell text th-lift time transformers transformers-base - unix wl-pprint-annotated + deepseq directory erf exceptions lifted-async mmorph monad-control + mtl pretty-show primitive random resourcet stm template-haskell + text time transformers transformers-base wl-pprint-annotated ]; doHaddock = false; doCheck = false; homepage = "https://hedgehog.qa"; - description = "Hedgehog will eat all your bugs"; - license = stdenv.lib.licenses.bsd3; + description = "Release with confidence"; + license = lib.licenses.bsd3; }) {}; "hedgehog-corpus" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "hedgehog-corpus"; - version = "0.1.0"; - sha256 = "c3569cd8316770115871acf334587350e887b046e35abc0d52a90dd0e6d719f2"; + version = "0.2.0"; + sha256 = "189669375a6425e4d80a59004e486e4096e06e7cdd33085825bba8282b9297a4"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/tmcgilchrist/hedgehog-corpus"; description = "hedgehog-corpus"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "hedis" = callPackage - ({ mkDerivation, async, base, bytestring, bytestring-lexing - , deepseq, errors, HTTP, mtl, network, network-uri, resource-pool - , scanner, stdenv, stm, text, time, tls, unordered-containers - , vector + "hedgehog-fakedata" = callPackage + ({ mkDerivation, base, fakedata, hedgehog, lib, random }: + mkDerivation { + pname = "hedgehog-fakedata"; + version = "0.0.1.4"; + sha256 = "a3376a168d28292f2da34162ba024268c4c60c22b32791917775eb7e8d9b48dd"; + libraryHaskellDepends = [ base fakedata hedgehog random ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/parsonsmatt/hedgehog-fakedata#readme"; + description = "Use 'fakedata' with 'hedgehog'"; + license = lib.licenses.bsd3; + }) {}; + "hedgehog-fn" = callPackage + ({ mkDerivation, base, contravariant, hedgehog, lib, transformers + }: + mkDerivation { + pname = "hedgehog-fn"; + version = "1.0"; + sha256 = "170bc58d2e5a5bc15bc3e8a0a3ea71b11b8aab8b3bfd923b7f9394afe569b915"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base contravariant hedgehog transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/qfpl/hedgehog-fn"; + description = "Function generation for `hedgehog`"; + license = lib.licenses.bsd3; + }) {}; + "hedgehog-quickcheck" = callPackage + ({ mkDerivation, base, hedgehog, lib, QuickCheck, transformers }: + mkDerivation { + pname = "hedgehog-quickcheck"; + version = "0.1.1"; + sha256 = "97b65db815fdfaacc7c4d06a7b9b74680b50264afa03f839c4037dcc875152fc"; + revision = "1"; + editedCabalFile = "0ddmwz3ngamij2k4paf7508dnzqn4qjpgwypbpr8d6s2y95jbvfh"; + libraryHaskellDepends = [ base hedgehog QuickCheck transformers ]; + doHaddock = false; + doCheck = false; + homepage = "https://hedgehog.qa"; + description = "Use QuickCheck generators in Hedgehog and vice versa"; + license = lib.licenses.bsd3; + }) {}; + "hedis" = callPackage + ({ mkDerivation, async, base, bytestring, bytestring-lexing + , containers, deepseq, errors, exceptions, HTTP, lib, mtl, network + , network-uri, resource-pool, scanner, stm, text, time, tls + , unordered-containers, vector }: mkDerivation { pname = "hedis"; - version = "0.10.10"; - sha256 = "1ad2452dc78065035d58f124547caa8ae927c9a470dbe85988e2ed1b19837241"; + version = "0.14.4"; + sha256 = "09261e0825786744ac2b43c698ea319a96ca04abd963f9976cd1537f471fda40"; libraryHaskellDepends = [ - async base bytestring bytestring-lexing deepseq errors HTTP mtl - network network-uri resource-pool scanner stm text time tls - unordered-containers vector + async base bytestring bytestring-lexing containers deepseq errors + exceptions HTTP mtl network network-uri resource-pool scanner stm + text time tls unordered-containers vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/informatikr/hedis"; description = "Client library for the Redis datastore: supports full command set, pipelining"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "hedn" = callPackage + ({ mkDerivation, base, containers, deepseq, deriving-compat, lib + , megaparsec, parser-combinators, prettyprinter, scientific + , template-haskell, text, time, uuid-types, vector + }: + mkDerivation { + pname = "hedn"; + version = "0.3.0.3"; + sha256 = "94df352475eabce2b9cea7d3f9e631a06197f044ca9321c3fedd274f6dd5ae2a"; + libraryHaskellDepends = [ + base containers deepseq deriving-compat megaparsec + parser-combinators prettyprinter scientific template-haskell text + time uuid-types vector + ]; + doHaddock = false; + doCheck = false; + description = "EDN parsing and encoding"; + license = lib.licenses.bsd3; }) {}; "here" = callPackage - ({ mkDerivation, base, haskell-src-meta, mtl, parsec, stdenv + ({ mkDerivation, base, haskell-src-meta, lib, mtl, parsec , template-haskell }: mkDerivation { @@ -15495,10 +18151,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/tmhedberg/here"; description = "Here docs & interpolated strings via quasiquotation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "heredoc" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { pname = "heredoc"; version = "0.2.0.0"; @@ -15508,17 +18164,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://hackage.haskell.org/package/heredoc"; description = "multi-line string / here document using QuasiQuotes"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "heterocephalus" = callPackage ({ mkDerivation, base, blaze-html, blaze-markup, containers, dlist - , mtl, parsec, shakespeare, stdenv, template-haskell, text + , lib, mtl, parsec, shakespeare, template-haskell, text , transformers }: mkDerivation { pname = "heterocephalus"; - version = "1.0.5.3"; - sha256 = "4723e03896cc91d524da36fe1b8c5b174b81120c323a3fad692f9ada4bd8794f"; + version = "1.0.5.4"; + sha256 = "8cde8f9a43ad77f6d4898c72755940d19c5ee79db9891d22950c2069e11adb19"; libraryHaskellDepends = [ base blaze-html blaze-markup containers dlist mtl parsec shakespeare template-haskell text transformers @@ -15526,23 +18182,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; homepage = "https://github.com/arowM/heterocephalus#readme"; - description = "A type-safe template engine for working with popular front end development tools"; - license = stdenv.lib.licenses.mit; - }) {}; - "hex" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: - mkDerivation { - pname = "hex"; - version = "0.1.2"; - sha256 = "12ee1243edd80570a486521565fb0c9b5e39374f21a12f050636e71d55ec61ec"; - libraryHaskellDepends = [ base bytestring ]; - doHaddock = false; - doCheck = false; - description = "Convert strings into hexadecimal and back"; - license = stdenv.lib.licenses.bsd3; + description = "A type-safe template engine for working with front end development tools"; + license = lib.licenses.mit; }) {}; "hexml" = callPackage - ({ mkDerivation, base, bytestring, extra, stdenv }: + ({ mkDerivation, base, bytestring, extra, lib }: mkDerivation { pname = "hexml"; version = "0.3.4"; @@ -15552,11 +18196,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/ndmitchell/hexml#readme"; description = "XML subset DOM parser"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hexml-lens" = callPackage ({ mkDerivation, base, bytestring, contravariant, foundation, hexml - , lens, profunctors, stdenv, text + , lens, lib, profunctors, text }: mkDerivation { pname = "hexml-lens"; @@ -15570,11 +18214,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/pepeiborra/hexml-lens#readme"; description = "Lenses for the hexml package"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hexpat" = callPackage - ({ mkDerivation, base, bytestring, containers, deepseq, expat, List - , stdenv, text, transformers, utf8-string + ({ mkDerivation, base, bytestring, containers, deepseq, expat, lib + , List, text, transformers, utf8-string }: mkDerivation { pname = "hexpat"; @@ -15589,28 +18233,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://haskell.org/haskellwiki/Hexpat/"; description = "XML parser/formatter based on expat"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) expat;}; - "hexstring" = callPackage - ({ mkDerivation, aeson, base, base16-bytestring, binary, bytestring - , stdenv, text - }: - mkDerivation { - pname = "hexstring"; - version = "0.11.1"; - sha256 = "40d8dbfe22f572ffdb73f28c448b228a75008e83cc3bf78e939add0c9d800914"; - enableSeparateDataOutput = true; - libraryHaskellDepends = [ - aeson base base16-bytestring binary bytestring text - ]; - doHaddock = false; - doCheck = false; - homepage = "http://www.leonmergen.com/opensource.html"; - description = "Fast and safe representation of a hex string"; - license = stdenv.lib.licenses.mit; - }) {}; "hformat" = callPackage - ({ mkDerivation, ansi-terminal, base, base-unicode-symbols, stdenv + ({ mkDerivation, ansi-terminal, base, base-unicode-symbols, lib , text }: mkDerivation { @@ -15624,11 +18250,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/mvoidex/hformat"; description = "Simple Haskell formatting"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hfsevents" = callPackage - ({ mkDerivation, base, bytestring, cereal, Cocoa, CoreServices, mtl - , stdenv, text + ({ mkDerivation, base, bytestring, cereal, Cocoa, CoreServices, lib + , mtl, text }: mkDerivation { pname = "hfsevents"; @@ -15641,66 +18267,151 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/luite/hfsevents"; description = "File/folder watching for OS X"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; platforms = [ "x86_64-darwin" ]; }) {inherit (pkgs.darwin.apple_sdk.frameworks) Cocoa;}; - "hgmp" = callPackage - ({ mkDerivation, base, ghc-prim, integer-gmp, stdenv }: + "hgeometry" = callPackage + ({ mkDerivation, aeson, base, bifunctors, bytestring, containers + , data-clist, deepseq, dlist, fingertree, fixed-vector, hashable + , hgeometry-combinatorial, hspec, lens, lib, linear, MonadRandom + , mtl, nonempty-vector, primitive, QuickCheck, quickcheck-instances + , random, reflection, semigroupoids, semigroups, template-haskell + , text, vector, vector-algorithms, vector-builder, vector-circular + , vinyl, witherable, yaml + }: mkDerivation { - pname = "hgmp"; - version = "0.1.1"; - sha256 = "b905720ad455ef54a167ed6c2a44dfb01f8e8f8efc6fe4f0a2a21ff22f5b3ac2"; - revision = "3"; - editedCabalFile = "0z2xbqzyrgm9apy3xl353wgwhbnc3hdb1giw2j6fyvv705fmpb62"; - libraryHaskellDepends = [ base ghc-prim integer-gmp ]; + pname = "hgeometry"; + version = "0.12.0.4"; + sha256 = "1cbea556f6864e9435606bb0e2c4e825e10d18f97c6691bd98eec322cae8c6af"; + libraryHaskellDepends = [ + aeson base bifunctors bytestring containers data-clist deepseq + dlist fingertree fixed-vector hashable hgeometry-combinatorial + hspec lens linear MonadRandom mtl nonempty-vector primitive + QuickCheck quickcheck-instances random reflection semigroupoids + semigroups template-haskell text vector vector-algorithms + vector-builder vector-circular vinyl witherable yaml + ]; + doHaddock = false; + doCheck = false; + homepage = "https://fstaals.net/software/hgeometry"; + description = "Geometric Algorithms, Data structures, and Data types"; + license = lib.licenses.bsd3; + }) {}; + "hgeometry-combinatorial" = callPackage + ({ mkDerivation, aeson, array, base, bifunctors, bytestring + , containers, contravariant, data-clist, deepseq, dlist, fingertree + , hashable, lens, lib, linear, math-functions, MonadRandom, mtl + , nonempty-vector, primitive, QuickCheck, quickcheck-instances + , random, reflection, semigroupoids, semigroups, template-haskell + , text, unordered-containers, vector, vector-builder + , vector-circular, vinyl, witherable, yaml + }: + mkDerivation { + pname = "hgeometry-combinatorial"; + version = "0.12.0.3"; + sha256 = "4951d7d42982bd83a4eee0b095f9baf68e8e9ef6db76eab0cdf0e5789179d669"; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + aeson array base bifunctors bytestring containers contravariant + data-clist deepseq dlist fingertree hashable lens linear + math-functions MonadRandom mtl nonempty-vector primitive QuickCheck + quickcheck-instances random reflection semigroupoids semigroups + template-haskell text unordered-containers vector vector-builder + vector-circular vinyl witherable yaml + ]; + doHaddock = false; + doCheck = false; + homepage = "https://fstaals.net/software/hgeometry"; + description = "Data structures, and Data types"; + license = lib.licenses.bsd3; + }) {}; + "hgrev" = callPackage + ({ mkDerivation, aeson, base, bytestring, directory, filepath, lib + , process, template-haskell + }: + mkDerivation { + pname = "hgrev"; + version = "0.2.6"; + sha256 = "6269657a8a620d49c7d5d8691e2bda5638a1f6915cd63bf2b4881b89378e36ec"; + libraryHaskellDepends = [ + aeson base bytestring directory filepath process template-haskell + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/bitnomial/hgrev"; + description = "Compile Mercurial (hg) version info into Haskell code"; + license = lib.licenses.bsd3; + }) {}; + "hi-file-parser" = callPackage + ({ mkDerivation, base, binary, bytestring, lib, mtl, rio, vector }: + mkDerivation { + pname = "hi-file-parser"; + version = "0.1.2.0"; + sha256 = "695f8a7baae616b47ec2b5105ab999bef5847a70e7eb6da31d7c3ab5e27aa3ca"; + libraryHaskellDepends = [ base binary bytestring mtl rio vector ]; doHaddock = false; doCheck = false; - homepage = "https://code.mathr.co.uk/hgmp"; - description = "Haskell interface to GMP"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/commercialhaskell/hi-file-parser#readme"; + description = "Parser for GHC's hi files"; + license = lib.licenses.bsd3; }) {}; "hidapi" = callPackage - ({ mkDerivation, base, bytestring, deepseq, deepseq-generics - , stdenv, systemd + ({ mkDerivation, base, bytestring, deepseq, deepseq-generics, lib + , systemd }: mkDerivation { pname = "hidapi"; - version = "0.1.5"; - sha256 = "3726e0bcbdbda309b919241d86629625e732fd07d78cc90ad39cb39b51cd595e"; + version = "0.1.7"; + sha256 = "ee85a3d5d65bb8e31670528c2465989f3a5e943eaae7f5fe4ff6c9d3b317f455"; libraryHaskellDepends = [ base bytestring deepseq deepseq-generics ]; librarySystemDepends = [ systemd ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/vahokif/haskell-hidapi"; + homepage = "https://github.com/chpatrick/haskell-hidapi"; description = "Haskell bindings to HIDAPI"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {inherit (pkgs) systemd;}; - "hidden-char" = callPackage - ({ mkDerivation, base, stdenv }: + "hie-bios" = callPackage + ({ mkDerivation, aeson, base, base16-bytestring, bytestring + , conduit, conduit-extra, containers, cryptohash-sha1, deepseq + , directory, extra, file-embed, filepath, ghc, hslogger, lib + , optparse-applicative, process, temporary, text, time + , transformers, unix-compat, unordered-containers, vector, yaml + }: mkDerivation { - pname = "hidden-char"; - version = "0.1.0.2"; - sha256 = "ea909372a7cc06cda7ee8e9c1a6a5c16be19fef256ad4bd2c0b39e61d940f498"; - revision = "2"; - editedCabalFile = "1d0k297hxff31k0x5xbli6l7c151d2y9wq4w0x0prgagjc0l7z5n"; - libraryHaskellDepends = [ base ]; + pname = "hie-bios"; + version = "0.7.5"; + sha256 = "883b0a26837956d134da7aa9d98aa92c92aadfdc55205d42a34061dc270e0f4d"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson base base16-bytestring bytestring conduit conduit-extra + containers cryptohash-sha1 deepseq directory extra file-embed + filepath ghc hslogger process temporary text time transformers + unix-compat unordered-containers vector yaml + ]; + executableHaskellDepends = [ + base directory filepath ghc optparse-applicative + ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/rcook/hidden-char#readme"; - description = "Provides cross-platform getHiddenChar function"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/mpickering/hie-bios"; + description = "Set up a GHC API session"; + license = lib.licenses.bsd3; }) {}; "higher-leveldb" = callPackage ({ mkDerivation, base, bytestring, cereal, data-default, exceptions - , leveldb-haskell, mtl, resourcet, stdenv, transformers + , leveldb-haskell, lib, mtl, resourcet, transformers , transformers-base, unliftio-core }: mkDerivation { pname = "higher-leveldb"; - version = "0.5.0.2"; - sha256 = "2afc228104a29aed6b208b1aeba93631e96fdf11efbe68ad036f838f95f8aff2"; + version = "0.6.0.0"; + sha256 = "c747769651732a80e7859f497eaa856796d82b2015323ba8044aa4bb4572583f"; + revision = "2"; + editedCabalFile = "1g8fnqvxjcq332wrnls272ff8grcbrc875phm77nsmjb8q4wjqz7"; libraryHaskellDepends = [ base bytestring cereal data-default exceptions leveldb-haskell mtl resourcet transformers transformers-base unliftio-core @@ -15709,11 +18420,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/jeremyjh/higher-leveldb"; description = "A rich monadic API for working with leveldb databases"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "highlighting-kate" = callPackage - ({ mkDerivation, base, blaze-html, bytestring, containers, mtl - , parsec, pcre-light, stdenv, utf8-string + ({ mkDerivation, base, blaze-html, bytestring, containers, lib, mtl + , parsec, pcre-light, utf8-string }: mkDerivation { pname = "highlighting-kate"; @@ -15733,8 +18444,7 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; license = "GPL"; }) {}; "hinfo" = callPackage - ({ mkDerivation, aeson, base, optparse-applicative, stdenv, text - , yaml + ({ mkDerivation, aeson, base, lib, optparse-applicative, text, yaml }: mkDerivation { pname = "hinfo"; @@ -15752,134 +18462,169 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/ChristopherDavenport/hinfo#readme"; description = "Command Line App With Info on your Haskell App"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hinotify" = callPackage - ({ mkDerivation, async, base, bytestring, containers, stdenv, unix - }: + ({ mkDerivation, async, base, bytestring, containers, lib, unix }: mkDerivation { pname = "hinotify"; - version = "0.4"; - sha256 = "7d182c524384aaa15eec666803643d067671e8e806f315c10758685e90a934f4"; + version = "0.4.1"; + sha256 = "1307b100aeaf35d0d0f582d4897fac9cde39505ec52c915e213118e56674f81a"; libraryHaskellDepends = [ async base bytestring containers unix ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/kolmodin/hinotify.git"; + homepage = "https://github.com/kolmodin/hinotify"; description = "Haskell binding to inotify"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hint" = callPackage ({ mkDerivation, base, directory, exceptions, filepath, ghc - , ghc-boot, ghc-paths, mtl, random, stdenv, temporary, unix + , ghc-boot, ghc-paths, lib, random, temporary, transformers, unix }: mkDerivation { pname = "hint"; - version = "0.9.0"; - sha256 = "7425af412a66d22f254608b4e9f552d65fd96c6cc5885af7b2ed0af62923f8bc"; + version = "0.9.0.4"; + sha256 = "da8ed3afc74da3c14a03a54c03a3e1cb34665c3ada16dbcb850333dde8b4b041"; libraryHaskellDepends = [ - base directory exceptions filepath ghc ghc-boot ghc-paths mtl - random temporary unix + base directory exceptions filepath ghc ghc-boot ghc-paths random + temporary transformers unix ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-hint/hint"; description = "Runtime Haskell interpreter (GHC API wrapper)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hjsmin" = callPackage - ({ mkDerivation, base, blaze-builder, bytestring, containers - , language-javascript, optparse-applicative, stdenv, text + ({ mkDerivation, base, bytestring, language-javascript, lib + , optparse-applicative, text }: mkDerivation { pname = "hjsmin"; - version = "0.2.0.2"; - sha256 = "bec153d2396962c63998eb12d0a2c7c9f7df6f774cb00e41b6cdb1f5a4905484"; + version = "0.2.0.4"; + sha256 = "81b9947714d8d2b73d0aba9e2e02af7e30c13b2cf8144df8904564d9642e57e4"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - base blaze-builder bytestring containers language-javascript text + base bytestring language-javascript text ]; executableHaskellDepends = [ - base blaze-builder bytestring containers language-javascript - optparse-applicative text + base bytestring language-javascript optparse-applicative text ]; doHaddock = false; doCheck = false; homepage = "http://github.com/erikd/hjsmin"; description = "Haskell implementation of a javascript minifier"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "hkd-default" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "hkd-default"; + version = "1.1.0.0"; + sha256 = "6f1fab330919c8b928884bb40d8e03f5545eb8e1bc20e6e6d10628649ad3c8b9"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/versioncloud/hkd-default#readme"; + description = "Apply default value for optional field of HKD"; + license = lib.licenses.bsd3; + }) {}; + "hkgr" = callPackage + ({ mkDerivation, base, bytestring, directory, extra, filepath, lib + , simple-cabal, simple-cmd-args, typed-process, xdg-basedir + }: + mkDerivation { + pname = "hkgr"; + version = "0.3"; + sha256 = "35e330016b5c99ec02babed80323afc6650bfd2a76710329d0ae4d3d9be01cf1"; + isLibrary = false; + isExecutable = true; + enableSeparateDataOutput = true; + executableHaskellDepends = [ + base bytestring directory extra filepath simple-cabal + simple-cmd-args typed-process xdg-basedir + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/juhp/hkgr"; + description = "Simple Hackage release workflow for package maintainers"; + license = lib.licenses.gpl3Only; }) {}; "hledger" = callPackage - ({ mkDerivation, ansi-terminal, base, base-compat-batteries + ({ mkDerivation, aeson, ansi-terminal, base, base-compat-batteries , bytestring, cmdargs, containers, data-default, Decimal, Diff - , directory, easytest, file-embed, filepath, hashable, haskeline - , here, hledger-lib, lucid, math-functions, megaparsec, mtl - , mtl-compat, old-time, parsec, pretty-show, process, regex-tdfa - , safe, shakespeare, split, stdenv, tabular, temporary, terminfo - , text, time, transformers, unordered-containers, utf8-string - , utility-ht, wizards + , directory, extra, filepath, hashable, haskeline, hledger-lib, lib + , lucid, math-functions, megaparsec, mtl, old-time, process + , regex-tdfa, safe, shakespeare, split, tabular, tasty, temporary + , terminfo, text, time, timeit, transformers, unordered-containers + , utf8-string, utility-ht, wizards }: mkDerivation { pname = "hledger"; - version = "1.12.1"; - sha256 = "3c94f63bd66cd9229e1e1e220a0ee80d3a8d2cfa812990e6cee0fd0c33dd3fad"; + version = "1.21"; + sha256 = "5a57b05b3b934c781a6bb443611236e92b0ba03c0c0b67a515c933b2eb74cc1d"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - ansi-terminal base base-compat-batteries bytestring cmdargs - containers data-default Decimal Diff directory easytest file-embed - filepath hashable haskeline here hledger-lib lucid math-functions - megaparsec mtl mtl-compat old-time parsec pretty-show process - regex-tdfa safe shakespeare split tabular temporary terminfo text - time transformers unordered-containers utf8-string utility-ht - wizards + aeson ansi-terminal base base-compat-batteries bytestring cmdargs + containers data-default Decimal Diff directory extra filepath + hashable haskeline hledger-lib lucid math-functions megaparsec mtl + old-time process regex-tdfa safe shakespeare split tabular tasty + temporary terminfo text time timeit transformers + unordered-containers utf8-string utility-ht wizards ]; executableHaskellDepends = [ - ansi-terminal base base-compat-batteries bytestring cmdargs - containers data-default Decimal directory easytest file-embed - filepath haskeline here hledger-lib math-functions megaparsec mtl - mtl-compat old-time parsec pretty-show process regex-tdfa safe - shakespeare split tabular temporary terminfo text time transformers - unordered-containers utf8-string utility-ht wizards + aeson ansi-terminal base base-compat-batteries bytestring cmdargs + containers data-default Decimal directory extra filepath haskeline + hledger-lib math-functions megaparsec mtl old-time process + regex-tdfa safe shakespeare split tabular tasty temporary terminfo + text time timeit transformers unordered-containers utf8-string + utility-ht wizards ]; doHaddock = false; doCheck = false; homepage = "http://hledger.org"; - description = "Command-line interface for the hledger accounting tool"; - license = stdenv.lib.licenses.gpl3; + description = "Command-line interface for the hledger accounting system"; + license = lib.licenses.gpl3Only; }) {}; - "hledger-api" = callPackage - ({ mkDerivation, aeson, base, bytestring, containers, data-default - , Decimal, docopt, either, hledger, hledger-lib, microlens - , microlens-platform, safe, servant-server, servant-swagger, stdenv - , swagger2, text, transformers, wai, wai-extra, warp + "hledger-iadd" = callPackage + ({ mkDerivation, base, brick, containers, directory, free + , hledger-lib, lib, megaparsec, microlens, microlens-th + , optparse-applicative, semigroups, text, text-zipper, time + , transformers, unordered-containers, vector, vty, xdg-basedir }: mkDerivation { - pname = "hledger-api"; - version = "1.12"; - sha256 = "5df5766fcb971b33f48f0e8762e5673be3ab92a4adc2281b7aeaa392cb53846e"; - isLibrary = false; + pname = "hledger-iadd"; + version = "1.3.14"; + sha256 = "c5472492ec443948762e4e236d91d9057ed23e8f0866c2aa32929997ae479c4d"; + isLibrary = true; isExecutable = true; + libraryHaskellDepends = [ + base brick containers directory free hledger-lib megaparsec + microlens microlens-th optparse-applicative semigroups text + text-zipper time transformers unordered-containers vector vty + xdg-basedir + ]; executableHaskellDepends = [ - aeson base bytestring containers data-default Decimal docopt either - hledger hledger-lib microlens microlens-platform safe - servant-server servant-swagger swagger2 text transformers wai - wai-extra warp + base brick directory free hledger-lib megaparsec microlens + optparse-applicative text text-zipper time transformers + unordered-containers vector vty xdg-basedir ]; doHaddock = false; doCheck = false; - homepage = "http://hledger.org"; - description = "Web API server for the hledger accounting tool"; - license = stdenv.lib.licenses.gpl3; + homepage = "https://github.com/hpdeifel/hledger-iadd#readme"; + description = "A terminal UI as drop-in replacement for hledger add"; + license = lib.licenses.bsd3; }) {}; "hledger-interest" = callPackage - ({ mkDerivation, base, Cabal, Decimal, hledger-lib, mtl, stdenv - , text, time + ({ mkDerivation, base, Cabal, Decimal, hledger-lib, lib, mtl, text + , time }: mkDerivation { pname = "hledger-interest"; - version = "1.5.3"; - sha256 = "7a7f5d437c98e42ba1f1529f2645e5df88d18962ae28b71b8c07e428fe08c1b9"; + version = "1.6.1"; + sha256 = "0cee0bef33a18bb1aca414abb93d5931e97dc293a2713c266ea2cda2f3f12745"; isLibrary = false; isExecutable = true; executableHaskellDepends = [ @@ -15887,69 +18632,145 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/peti/hledger-interest"; + homepage = "https://github.com/peti/hledger-interest"; description = "computes interest for a given account"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hledger-lib" = callPackage - ({ mkDerivation, ansi-terminal, array, base, base-compat-batteries - , blaze-markup, bytestring, call-stack, cassava, cassava-megaparsec - , cmdargs, containers, data-default, Decimal, deepseq, directory - , easytest, extra, filepath, Glob, hashtables, megaparsec, mtl - , mtl-compat, old-time, parsec, parser-combinators, pretty-show - , regex-tdfa, safe, split, stdenv, tabular, text, time - , transformers, uglymemo, utf8-string + ({ mkDerivation, aeson, aeson-pretty, ansi-terminal, array, base + , base-compat-batteries, blaze-markup, bytestring, call-stack + , cassava, cassava-megaparsec, cmdargs, containers, data-default + , Decimal, directory, extra, file-embed, filepath, Glob, hashtables + , lib, megaparsec, mtl, old-time, parser-combinators, pretty-simple + , regex-tdfa, safe, tabular, tasty, tasty-hunit, template-haskell + , text, time, timeit, transformers, uglymemo, unordered-containers + , utf8-string }: mkDerivation { pname = "hledger-lib"; - version = "1.12"; - sha256 = "7095d03bf9375fbe886467d98a3c4c34c8ea566ea9a3490a85bd31667eca68d4"; + version = "1.21"; + sha256 = "be2cd8c4259da63a6cc2c5abf625ebc8ffaab405ec3284c6f7cb6e3431d5f902"; + libraryHaskellDepends = [ + aeson aeson-pretty ansi-terminal array base base-compat-batteries + blaze-markup bytestring call-stack cassava cassava-megaparsec + cmdargs containers data-default Decimal directory extra file-embed + filepath Glob hashtables megaparsec mtl old-time parser-combinators + pretty-simple regex-tdfa safe tabular tasty tasty-hunit + template-haskell text time timeit transformers uglymemo + unordered-containers utf8-string + ]; + doHaddock = false; + doCheck = false; + homepage = "http://hledger.org"; + description = "A reusable library providing the core functionality of hledger"; + license = lib.licenses.gpl3Only; + }) {}; + "hledger-stockquotes" = callPackage + ({ mkDerivation, aeson, base, bytestring, cmdargs, containers + , directory, hledger-lib, lib, raw-strings-qq, req, safe + , safe-exceptions, scientific, split, text, time + , unordered-containers, xdg-basedir, yaml + }: + mkDerivation { + pname = "hledger-stockquotes"; + version = "0.1.2.0"; + sha256 = "7ddc0f470fa8ee5c30a26375220225adda13acf121c312739a50e56c3e369818"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - ansi-terminal array base base-compat-batteries blaze-markup - bytestring call-stack cassava cassava-megaparsec cmdargs containers - data-default Decimal deepseq directory easytest extra filepath Glob - hashtables megaparsec mtl mtl-compat old-time parsec - parser-combinators pretty-show regex-tdfa safe split tabular text - time transformers uglymemo utf8-string + aeson base bytestring containers hledger-lib req safe scientific + split text time unordered-containers + ]; + executableHaskellDepends = [ + aeson base bytestring cmdargs directory raw-strings-qq + safe-exceptions text time xdg-basedir yaml + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/prikhi/hledger-stockquotes#readme"; + description = "Generate HLedger Price Directives From Daily Stock Quotes"; + license = lib.licenses.bsd3; + }) {}; + "hledger-ui" = callPackage + ({ mkDerivation, ansi-terminal, async, base, base-compat-batteries + , brick, cmdargs, containers, data-default, directory, extra + , filepath, fsnotify, hledger, hledger-lib, lib, megaparsec + , microlens, microlens-platform, process, safe, split, text + , text-zipper, time, transformers, unix, vector, vty + }: + mkDerivation { + pname = "hledger-ui"; + version = "1.21"; + sha256 = "14f4f5de87b69b05ca6040cb444cf2e6e8dc1ccae601740cde0c79f00d322dc1"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ + ansi-terminal async base base-compat-batteries brick cmdargs + containers data-default directory extra filepath fsnotify hledger + hledger-lib megaparsec microlens microlens-platform process safe + split text text-zipper time transformers unix vector vty ]; doHaddock = false; doCheck = false; homepage = "http://hledger.org"; - description = "Core data types, parsers and functionality for the hledger accounting tools"; - license = stdenv.lib.licenses.gpl3; + description = "Curses-style terminal interface for the hledger accounting system"; + license = lib.licenses.gpl3Only; }) {}; "hledger-web" = callPackage - ({ mkDerivation, base, blaze-html, blaze-markup, bytestring + ({ mkDerivation, aeson, base, blaze-html, blaze-markup, bytestring , case-insensitive, clientsession, cmdargs, conduit, conduit-extra - , data-default, directory, filepath, hjsmin, hledger, hledger-lib - , http-client, http-conduit, json, megaparsec, mtl, semigroups - , shakespeare, stdenv, template-haskell, text, time, transformers - , wai, wai-extra, wai-handler-launch, warp, yaml, yesod, yesod-core - , yesod-form, yesod-static + , containers, data-default, Decimal, directory, extra, filepath + , hjsmin, hledger, hledger-lib, hspec, http-client, http-conduit + , http-types, lib, megaparsec, mtl, network, shakespeare + , template-haskell, text, time, transformers, unix-compat + , unordered-containers, utf8-string, wai, wai-cors, wai-extra + , wai-handler-launch, warp, yaml, yesod, yesod-core, yesod-form + , yesod-static, yesod-test }: mkDerivation { pname = "hledger-web"; - version = "1.12"; - sha256 = "6668e9922490d1b742ab285200c337681ae1b988b315c03f7bce96941bc4c392"; + version = "1.21"; + sha256 = "e2251687ed0c4dff9fea1767e3c30279df50713bdb9d4c2c1712f0eb19fe7a47"; + revision = "1"; + editedCabalFile = "1hnw10ibhbafbsfj5lzlxwjg4cjnqr5bb51n6mqbi30qqabgq78x"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - base blaze-html blaze-markup bytestring case-insensitive - clientsession cmdargs conduit conduit-extra data-default directory - filepath hjsmin hledger hledger-lib http-client http-conduit json - megaparsec mtl semigroups shakespeare template-haskell text time - transformers wai wai-extra wai-handler-launch warp yaml yesod - yesod-core yesod-form yesod-static + aeson base blaze-html blaze-markup bytestring case-insensitive + clientsession cmdargs conduit conduit-extra containers data-default + Decimal directory extra filepath hjsmin hledger hledger-lib hspec + http-client http-conduit http-types megaparsec mtl network + shakespeare template-haskell text time transformers unix-compat + unordered-containers utf8-string wai wai-cors wai-extra + wai-handler-launch warp yaml yesod yesod-core yesod-form + yesod-static yesod-test ]; executableHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "http://hledger.org"; - description = "Web interface for the hledger accounting tool"; - license = stdenv.lib.licenses.gpl3; + description = "Web-based user interface for the hledger accounting system"; + license = lib.licenses.gpl3Only; + }) {}; + "hlibcpuid" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "hlibcpuid"; + version = "0.2.0"; + sha256 = "015990c807ad4c4fe6d535ae602ad6f4e038d3c0b628a9b739598ac75aed9a59"; + isLibrary = true; + isExecutable = true; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ base ]; + executableHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/dtaskoff/hlibcpuid#readme"; + description = "Bindings to https://github.com/anrieff/libcpuid"; + license = lib.licenses.mit; }) {}; "hlibgit2" = callPackage - ({ mkDerivation, base, bindings-DSL, openssl, stdenv, zlib }: + ({ mkDerivation, base, bindings-DSL, lib, openssl, zlib }: mkDerivation { pname = "hlibgit2"; version = "0.18.0.16"; @@ -15959,15 +18780,15 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Low-level bindings to libgit2"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {inherit (pkgs) openssl;}; "hlibsass" = callPackage - ({ mkDerivation, base, Cabal, directory, libsass, stdenv }: + ({ mkDerivation, base, Cabal, directory, lib, libsass }: mkDerivation { pname = "hlibsass"; - version = "0.1.8.0"; - sha256 = "26de9a1275e0c1cae5afbe79ad3aa1a857c3bfc0b6dcc97698e9d02d41de4feb"; - configureFlags = [ "-fexternalLibsass" ]; + version = "0.1.10.1"; + sha256 = "9eb7913c3184d8573b9f801df7bad07f48c389759de3549f611037449ae1cb3d"; + configureFlags = [ "-fexternallibsass" ]; setupHaskellDepends = [ base Cabal directory ]; libraryHaskellDepends = [ base ]; librarySystemDepends = [ libsass ]; @@ -15975,67 +18796,66 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/jakubfijalkowski/hlibsass"; description = "Low-level bindings to Libsass"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {inherit (pkgs) libsass;}; "hlint" = callPackage ({ mkDerivation, aeson, ansi-terminal, base, bytestring, cmdargs - , containers, cpphs, data-default, directory, extra, filepath - , haskell-src-exts, haskell-src-exts-util, hscolour, process - , refact, stdenv, text, transformers, uniplate - , unordered-containers, vector, yaml + , containers, cpphs, data-default, directory, extra, file-embed + , filepath, filepattern, ghc, ghc-boot, ghc-boot-th + , ghc-lib-parser-ex, hscolour, lib, process, refact, text + , transformers, uniplate, unordered-containers, utf8-string, vector + , yaml }: mkDerivation { pname = "hlint"; - version = "2.1.11"; - sha256 = "4b590d27ec6da4670deea9de4f52c83048688073b3e6389a74da31d58e30665b"; + version = "3.2.7"; + sha256 = "6f9c3d9603a072e1b76d3ee125dfaa54ce356fc0ced836affa741d989bedcf7c"; isLibrary = true; isExecutable = true; enableSeparateDataOutput = true; libraryHaskellDepends = [ aeson ansi-terminal base bytestring cmdargs containers cpphs - data-default directory extra filepath haskell-src-exts - haskell-src-exts-util hscolour process refact text transformers - uniplate unordered-containers vector yaml + data-default directory extra file-embed filepath filepattern ghc + ghc-boot ghc-boot-th ghc-lib-parser-ex hscolour process refact text + transformers uniplate unordered-containers utf8-string vector yaml ]; executableHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/ndmitchell/hlint#readme"; description = "Source code suggestions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hmatrix" = callPackage - ({ mkDerivation, array, base, binary, bytestring, deepseq - , openblasCompat, random, semigroups, split, stdenv + ({ mkDerivation, array, base, binary, bytestring, deepseq, lib + , openblasCompat, primitive, random, semigroups, split , storable-complex, vector }: mkDerivation { pname = "hmatrix"; - version = "0.19.0.0"; - sha256 = "52eb2e42edc5839bfd9d2dec6c4fb29997eca737537a06df7b2d09bf6c324d82"; - revision = "1"; - editedCabalFile = "0krx0ds5mcj28y6zpg0r50lljn8681wi4c5lqcdz2c71nhixfq8h"; + version = "0.20.2"; + sha256 = "6f4dfc8e15e5501af299fa53f3b178396ae01447573ffd97eb17af89f3158614"; configureFlags = [ "-fdisable-default-paths" "-fopenblas" ]; libraryHaskellDepends = [ - array base binary bytestring deepseq random semigroups split - storable-complex vector + array base binary bytestring deepseq primitive random semigroups + split storable-complex vector ]; librarySystemDepends = [ openblasCompat ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/albertoruiz/hmatrix"; + homepage = "https://github.com/haskell-numerics/hmatrix"; description = "Numeric Linear Algebra"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) openblasCompat;}; "hmatrix-backprop" = callPackage ({ mkDerivation, backprop, base, ghc-typelits-knownnat - , ghc-typelits-natnormalise, hmatrix, hmatrix-vector-sized - , microlens, stdenv, vector, vector-sized, vinyl + , ghc-typelits-natnormalise, hmatrix, hmatrix-vector-sized, lib + , microlens, vector, vector-sized, vinyl }: mkDerivation { pname = "hmatrix-backprop"; - version = "0.1.2.5"; - sha256 = "4ebb6e5073bd6652fcac22275e47411ca1076699100bc928a692a1c7f6aed1d4"; + version = "0.1.3.0"; + sha256 = "5350f95a7bdf014f06f424f51379cc8074baa7439107ef7568c385c2aae276da"; libraryHaskellDepends = [ backprop base ghc-typelits-knownnat ghc-typelits-natnormalise hmatrix hmatrix-vector-sized microlens vector vector-sized vinyl @@ -16044,10 +18864,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mstksg/hmatrix-backprop#readme"; description = "hmatrix operations lifted for backprop"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hmatrix-gsl" = callPackage - ({ mkDerivation, array, base, gsl, hmatrix, process, random, stdenv + ({ mkDerivation, array, base, gsl, hmatrix, lib, process, random , vector }: mkDerivation { @@ -16062,16 +18882,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/albertoruiz/hmatrix"; description = "Numerical computation"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; }) {inherit (pkgs) gsl;}; "hmatrix-gsl-stats" = callPackage - ({ mkDerivation, base, binary, gsl, hmatrix, stdenv - , storable-complex, vector + ({ mkDerivation, base, binary, gsl, hmatrix, lib, storable-complex + , vector }: mkDerivation { pname = "hmatrix-gsl-stats"; - version = "0.4.1.7"; - sha256 = "4a0f8b6ea1caefebd30f1e726c94f238d96c0f873bdeb5d920367e8aca7c54bf"; + version = "0.4.1.8"; + sha256 = "b844420ce1e76e11ab04fba7e826b98449e166c6b08c78ba01b9e021752200b3"; libraryHaskellDepends = [ base binary hmatrix storable-complex vector ]; @@ -16080,10 +18900,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://code.haskell.org/hmatrix-gsl-stats"; description = "GSL Statistics interface"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) gsl;}; "hmatrix-morpheus" = callPackage - ({ mkDerivation, base, blas, hmatrix, liblapack, stdenv }: + ({ mkDerivation, base, blas, hmatrix, lib, liblapack }: mkDerivation { pname = "hmatrix-morpheus"; version = "0.1.1.2"; @@ -16094,23 +18914,46 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/aligusnet/morpheus/tree/master/hmatrix-morpheus"; description = "Low-level machine learning auxiliary functions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) blas; inherit (pkgs) liblapack;}; "hmatrix-vector-sized" = callPackage - ({ mkDerivation, base, hmatrix, stdenv, vector, vector-sized }: + ({ mkDerivation, base, hmatrix, lib, vector, vector-sized }: mkDerivation { pname = "hmatrix-vector-sized"; - version = "0.1.1.2"; - sha256 = "86981a7f412b68e42abff0d929db8ed2eab264d1bde3e4e75fa789066a0f437e"; + version = "0.1.3.0"; + sha256 = "48d6ad05b83411d7cd364ca0c91eff5cedfab3e9a3bc27bcd8b9c2ca40ff9995"; libraryHaskellDepends = [ base hmatrix vector vector-sized ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mstksg/hmatrix-vector-sized#readme"; description = "Conversions between hmatrix and vector-sized types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "hmm-lapack" = callPackage + ({ mkDerivation, base, comfort-array, containers, deepseq + , explicit-exception, fixed-length, lapack, lazy-csv, lib + , netlib-ffi, non-empty, prelude-compat, QuickCheck, random + , semigroups, tfp, transformers, utility-ht + }: + mkDerivation { + pname = "hmm-lapack"; + version = "0.4"; + sha256 = "1c0cedbd0efef71a44323e0c3ab4aa6d7dc45be36dead37b8d0e632d5d701d38"; + revision = "1"; + editedCabalFile = "10dg0s6nrvb93ksyzgappmr28av4k204kmc8lb3vc2ribqhpb177"; + libraryHaskellDepends = [ + base comfort-array containers deepseq explicit-exception + fixed-length lapack lazy-csv netlib-ffi non-empty prelude-compat + QuickCheck random semigroups tfp transformers utility-ht + ]; + doHaddock = false; + doCheck = false; + homepage = "http://hub.darcs.net/thielema/hmm-lapack"; + description = "Hidden Markov Models using LAPACK primitives"; + license = lib.licenses.bsd3; }) {}; "hmpfr" = callPackage - ({ mkDerivation, base, integer-gmp, mpfr, stdenv }: + ({ mkDerivation, base, integer-gmp, lib, mpfr }: mkDerivation { pname = "hmpfr"; version = "0.4.4"; @@ -16122,77 +18965,131 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/michalkonecny/hmpfr"; description = "Haskell binding to the MPFR library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) mpfr;}; + "hnock" = callPackage + ({ mkDerivation, base, lib, parsec, text }: + mkDerivation { + pname = "hnock"; + version = "0.4.0"; + sha256 = "ad5c377fa5c0e089953ca31a4ea65131854d157444903cb4e4df2abd2b357cb4"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base parsec text ]; + executableHaskellDepends = [ base text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jtobin/hnock"; + description = "A Nock interpreter"; + license = lib.licenses.mit; + }) {}; "hoauth2" = callPackage - ({ mkDerivation, aeson, base, bytestring, exceptions, http-conduit - , http-types, microlens, stdenv, text, unordered-containers - , uri-bytestring, uri-bytestring-aeson + ({ mkDerivation, aeson, base, binary, bytestring, exceptions + , http-conduit, http-types, lib, microlens, text + , unordered-containers, uri-bytestring, uri-bytestring-aeson }: mkDerivation { pname = "hoauth2"; - version = "1.8.3"; - sha256 = "a7fc28f8bd3c49f5c9727e00b48d0de9eb205596a064451c180d45c9a68ba0d7"; + version = "1.16.0"; + sha256 = "0659dacf6dabbd5105c60923efcf0c7ea507926691acaa71cb5ab6308276c968"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - aeson base bytestring exceptions http-conduit http-types microlens - text unordered-containers uri-bytestring uri-bytestring-aeson + aeson base binary bytestring exceptions http-conduit http-types + microlens text unordered-containers uri-bytestring + uri-bytestring-aeson ]; doHaddock = false; doCheck = false; homepage = "https://github.com/freizl/hoauth2"; description = "Haskell OAuth2 authentication client"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hoogle" = callPackage - ({ mkDerivation, aeson, base, binary, bytestring, cmdargs, conduit - , conduit-extra, connection, containers, deepseq, directory, extra - , filepath, haskell-src-exts, http-conduit, http-types, js-flot - , js-jquery, mmap, network, network-uri, old-locale, process-extras - , QuickCheck, resourcet, stdenv, storable-tuple, tar - , template-haskell, text, time, transformers, uniplate, utf8-string - , vector, wai, wai-logger, warp, warp-tls, zlib + ({ mkDerivation, aeson, base, binary, blaze-html, blaze-markup + , bytestring, cmdargs, conduit, conduit-extra, connection + , containers, deepseq, directory, extra, filepath, foundation + , hashable, haskell-src-exts, http-conduit, http-types, js-flot + , js-jquery, lib, mmap, old-locale, process-extras, QuickCheck + , resourcet, storable-tuple, tar, template-haskell, text, time + , transformers, uniplate, utf8-string, vector, wai, wai-logger + , warp, warp-tls, zlib }: mkDerivation { pname = "hoogle"; - version = "5.0.17.3"; - sha256 = "66bebaf75600fef1c5fc0613ccc55c137aaed4c8f69653cf903f4fb003b98f9c"; + version = "5.0.18.1"; + sha256 = "7c44830d072ce13f326bbcd13e01765ceaad18d59a49ba4b55b6496f12052a96"; isLibrary = true; isExecutable = true; enableSeparateDataOutput = true; libraryHaskellDepends = [ - aeson base binary bytestring cmdargs conduit conduit-extra - connection containers deepseq directory extra filepath - haskell-src-exts http-conduit http-types js-flot js-jquery mmap - network network-uri old-locale process-extras QuickCheck resourcet - storable-tuple tar template-haskell text time transformers uniplate - utf8-string vector wai wai-logger warp warp-tls zlib + aeson base binary blaze-html blaze-markup bytestring cmdargs + conduit conduit-extra connection containers deepseq directory extra + filepath foundation hashable haskell-src-exts http-conduit + http-types js-flot js-jquery mmap old-locale process-extras + QuickCheck resourcet storable-tuple tar template-haskell text time + transformers uniplate utf8-string vector wai wai-logger warp + warp-tls zlib ]; executableHaskellDepends = [ base ]; doHaddock = false; doCheck = false; testTarget = "--test-option=--no-net"; - homepage = "http://hoogle.haskell.org/"; + homepage = "https://hoogle.haskell.org/"; description = "Haskell API Search"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "hopenpgp-tools" = callPackage + ({ mkDerivation, aeson, alex, array, base, base16-bytestring + , binary, binary-conduit, bytestring, conduit, conduit-extra + , containers, cryptonite, directory, errors, fgl, graphviz, happy + , hOpenPGP, http-client, http-client-tls, http-types, ixset-typed + , lens, lib, memory, monad-loops, mtl, openpgp-asciiarmor + , optparse-applicative, prettyprinter, prettyprinter-ansi-terminal + , prettyprinter-convert-ansi-wl-pprint, resourcet, text, time + , time-locale-compat, transformers, unordered-containers, vector + , yaml + }: + mkDerivation { + pname = "hopenpgp-tools"; + version = "0.23.6"; + sha256 = "3df2f26a8e1c2be92c54b1b347474464a23d213a7982dd4afb8c88c6b6325042"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ + aeson array base base16-bytestring binary binary-conduit bytestring + conduit conduit-extra containers cryptonite directory errors fgl + graphviz hOpenPGP http-client http-client-tls http-types + ixset-typed lens memory monad-loops mtl openpgp-asciiarmor + optparse-applicative prettyprinter prettyprinter-ansi-terminal + prettyprinter-convert-ansi-wl-pprint resourcet text time + time-locale-compat transformers unordered-containers vector yaml + ]; + executableToolDepends = [ alex happy ]; + doHaddock = false; + doCheck = false; + homepage = "https://salsa.debian.org/clint/hOpenPGP-tools"; + description = "hOpenPGP-based command-line tools"; + license = lib.licenses.agpl3Plus; }) {}; "hopenssl" = callPackage - ({ mkDerivation, base, bytestring, openssl, stdenv }: + ({ mkDerivation, base, bytestring, lib, openssl }: mkDerivation { pname = "hopenssl"; version = "2.2.4"; sha256 = "9df46c328fc4c1d1566e2d1539770c9fe9d0422e09ee254721b35ee7d48a7671"; + revision = "1"; + editedCabalFile = "14bs0wjrqnnn1v8c4yznfzggvmgypm2lssgl0cr498kmp54if0lf"; libraryHaskellDepends = [ base bytestring ]; librarySystemDepends = [ openssl ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/peti/hopenssl"; + homepage = "https://github.com/peti/hopenssl"; description = "FFI Bindings to OpenSSL's EVP Digest Interface"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) openssl;}; "hopfli" = callPackage - ({ mkDerivation, base, bytestring, stdenv, zlib }: + ({ mkDerivation, base, bytestring, lib, zlib }: mkDerivation { pname = "hopfli"; version = "0.2.2.1"; @@ -16204,16 +19101,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/ananthakumaran/hopfli"; description = "Bidings to Google's Zopfli compression library"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; }) {}; "hosc" = callPackage ({ mkDerivation, base, binary, blaze-builder, bytestring - , data-binary-ieee754, network, stdenv, time, transformers + , data-binary-ieee754, lib, network, time, transformers }: mkDerivation { pname = "hosc"; - version = "0.17"; - sha256 = "66439c416246cb56c15a0f3fb0cf07b178202c7755034b648f02d4f81ba5800c"; + version = "0.18.1"; + sha256 = "720f004ef78308735572e9a579f18036803cff1cd1d4f661bc64e3ad3fdffe79"; enableSeparateDataOutput = true; libraryHaskellDepends = [ base binary blaze-builder bytestring data-binary-ieee754 network @@ -16223,10 +19120,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://rohandrape.net/t/hosc"; description = "Haskell Open Sound Control"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; }) {}; "hostname" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "hostname"; version = "1.0"; @@ -16235,10 +19132,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A very simple package providing a cross-platform means of determining the hostname"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hostname-validate" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, stdenv }: + ({ mkDerivation, attoparsec, base, bytestring, lib }: mkDerivation { pname = "hostname-validate"; version = "1.0.0"; @@ -16247,10 +19144,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Validate hostnames e.g. localhost or foo.co.uk."; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hourglass" = callPackage - ({ mkDerivation, base, deepseq, stdenv }: + ({ mkDerivation, base, deepseq, lib }: mkDerivation { pname = "hourglass"; version = "0.2.12"; @@ -16260,10 +19157,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/vincenthz/hs-hourglass"; description = "simple performant time related library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hourglass-orphans" = callPackage - ({ mkDerivation, aeson, base, hourglass, stdenv }: + ({ mkDerivation, aeson, base, hourglass, lib }: mkDerivation { pname = "hourglass-orphans"; version = "0.1.0.0"; @@ -16273,16 +19170,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/psibi/hourglass-orphans#readme"; description = "Orphan Aeson instances to hourglass"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hp2pretty" = callPackage ({ mkDerivation, array, attoparsec, base, containers, filepath - , floatshow, mtl, optparse-applicative, semigroups, stdenv, text + , floatshow, lib, mtl, optparse-applicative, semigroups, text }: mkDerivation { pname = "hp2pretty"; - version = "0.9"; - sha256 = "56fc8ba0ad862668179f5bab032c3738fa42d10abce6b59f8dd01b3a11e52b52"; + version = "0.10"; + sha256 = "226c0f3762861c29748e83a3c93388c284aba33cfef45623ca69acc8764535c7"; isLibrary = false; isExecutable = true; executableHaskellDepends = [ @@ -16293,19 +19190,19 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://mathr.co.uk/blog/hp2pretty.html"; description = "generate pretty graphs from heap profiles"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hpack" = callPackage ({ mkDerivation, aeson, base, bifunctors, bytestring, Cabal , containers, cryptonite, deepseq, directory, filepath, Glob - , http-client, http-client-tls, http-types, infer-license, pretty - , scientific, stdenv, text, transformers, unordered-containers + , http-client, http-client-tls, http-types, infer-license, lib + , pretty, scientific, text, transformers, unordered-containers , vector, yaml }: mkDerivation { pname = "hpack"; - version = "0.31.1"; - sha256 = "ac3ab2b42339f6e3d45b89e4ee9acf33550f7fac6518b8cf47a874226b5d373a"; + version = "0.34.4"; + sha256 = "7411ed9042a94e99c0a2c8e3198c13448cc4f0dbf6c0478c7aff17aa00f05ff7"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -16324,18 +19221,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/sol/hpack#readme"; description = "A modern format for Haskell packages"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hpack-dhall" = callPackage ({ mkDerivation, aeson, aeson-pretty, base, bytestring, dhall - , dhall-json, filepath, hpack, megaparsec, microlens - , optparse-applicative, prettyprinter, stdenv, text, transformers - , yaml + , dhall-json, filepath, hpack, lib, megaparsec, microlens + , optparse-applicative, prettyprinter, text, transformers, yaml }: mkDerivation { pname = "hpack-dhall"; - version = "0.5.1"; - sha256 = "739ef8c197784e91f9ad3489f93dcb7367e222732b476314cf847e166598ed65"; + version = "0.5.2"; + sha256 = "f187092f60fddda9f4f453cbbf9c536b3f3af193ebd23c2c234280cb6182b69a"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -16351,54 +19247,92 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/blockscope/hpack-dhall#readme"; description = "hpack's dhalling"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "hreader" = callPackage - ({ mkDerivation, base, exceptions, hset, mmorph, monad-control, mtl - , stdenv, tagged, transformers, transformers-base + "hpc-codecov" = callPackage + ({ mkDerivation, array, base, bytestring, directory, filepath, hpc + , lib }: mkDerivation { - pname = "hreader"; - version = "1.1.0"; - sha256 = "2a2b02c059b343ab7ff0d340b6545a003b0d563fb8a1ad2d53d6c2f4759a7d3a"; - revision = "1"; - editedCabalFile = "0kz3yzah7m4c2r9yaawhljcgb579masx3lx4mrr4lmqy39kmsvcb"; + pname = "hpc-codecov"; + version = "0.3.0.0"; + sha256 = "a22d9de3e635fe22a87324d322dbce712d9e83d8ca744d26e6cf1894aac32925"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - base exceptions hset mmorph monad-control mtl tagged transformers - transformers-base + array base bytestring directory filepath hpc + ]; + executableHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/8c6794b6/hpc-codecov#readme"; + description = "Generate codecov report from hpc data"; + license = lib.licenses.bsd3; + }) {}; + "hpc-lcov" = callPackage + ({ mkDerivation, aeson, base, containers, hpc, lib + , optparse-applicative, path, path-io, process, text + , unordered-containers, yaml + }: + mkDerivation { + pname = "hpc-lcov"; + version = "1.0.1"; + sha256 = "74476e8632ec956a0e266015fb6dce3778cbe5e04bb1164a38f56db5852f9a07"; + revision = "2"; + editedCabalFile = "1sbd4wk977hh7jvy2ingmavkqx7fzicfa70figipa7lzdq3lg0ls"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base containers hpc ]; + executableHaskellDepends = [ + aeson base containers hpc optparse-applicative path path-io process + text unordered-containers yaml ]; doHaddock = false; doCheck = false; - homepage = "https://bitbucket.org/s9gf4ult/hreader"; - description = "Generalization of MonadReader and ReaderT using hset"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/LeapYear/hpc-lcov#readme"; + description = "Convert HPC output into LCOV format"; + license = lib.licenses.bsd3; }) {}; - "hreader-lens" = callPackage - ({ mkDerivation, base, comonad, hreader, hset, lens, lens-action - , profunctors, stdenv + "hprotoc" = callPackage + ({ mkDerivation, alex, array, base, binary, bytestring, containers + , directory, filepath, haskell-src-exts, lib, mtl, parsec + , protocol-buffers, protocol-buffers-descriptor, utf8-string }: mkDerivation { - pname = "hreader-lens"; - version = "0.1.3.0"; - sha256 = "408f0a2c6ce4bc5c00746947262f43f421f0e8fb9cc29c0cd2563ee1e87502d0"; + pname = "hprotoc"; + version = "2.4.17"; + sha256 = "62381d1d35d24279edb75225fdc3a74f81b0ddee51feb5d52f6598b734c9ffe4"; + revision = "2"; + editedCabalFile = "0hxhvjk3mswx712viv7krcgiynxq4bjs71vbk2pgm2d50i5qr8mr"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - base comonad hreader hset lens lens-action profunctors + array base binary bytestring containers directory filepath + haskell-src-exts mtl parsec protocol-buffers + protocol-buffers-descriptor utf8-string + ]; + libraryToolDepends = [ alex ]; + executableHaskellDepends = [ + array base binary bytestring containers directory filepath + haskell-src-exts mtl parsec protocol-buffers + protocol-buffers-descriptor utf8-string ]; + executableToolDepends = [ alex ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/dredozubov/hreader-lens"; - description = "Optics for hreader package"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/k-bx/protocol-buffers"; + description = "Parse Google Protocol Buffer specifications"; + license = lib.licenses.bsd3; }) {}; "hruby" = callPackage - ({ mkDerivation, aeson, attoparsec, base, bytestring, Cabal - , process, ruby, scientific, stdenv, stm, text - , unordered-containers, vector + ({ mkDerivation, aeson, attoparsec, base, bytestring, Cabal, lib + , process, ruby, scientific, stm, text, unordered-containers + , vector }: mkDerivation { pname = "hruby"; - version = "0.3.6"; - sha256 = "dda3b4fb243b612915c8a5c415a95c7d68c0d860901fd01b5d0315b7ccda1519"; + version = "0.3.8.1"; + sha256 = "92d11d8bd49f8af2b7202b02900a099067f70c632a60df4e80b0fbe3b9009702"; setupHaskellDepends = [ base Cabal process ]; libraryHaskellDepends = [ aeson attoparsec base bytestring scientific stm text @@ -16408,10 +19342,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Embed a Ruby intepreter in your Haskell program !"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) ruby;}; "hs-GeoIP" = callPackage - ({ mkDerivation, base, bytestring, deepseq, GeoIP, stdenv }: + ({ mkDerivation, base, bytestring, deepseq, GeoIP, lib }: mkDerivation { pname = "hs-GeoIP"; version = "0.3"; @@ -16422,14 +19356,14 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ozataman/hs-GeoIP"; description = "Haskell bindings to the MaxMind GeoIPCity database via the C library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) GeoIP;}; "hs-bibutils" = callPackage - ({ mkDerivation, base, stdenv, syb }: + ({ mkDerivation, base, lib, syb }: mkDerivation { pname = "hs-bibutils"; - version = "6.7.0.0"; - sha256 = "c5d205294ff372306504b03c4334fd96215727087ee4ee1378a45273a8d6dee1"; + version = "6.10.0.0"; + sha256 = "76bc12763bd8c45519313a08fad3ce715ec4b9d5373146791431ae5c76f0d7f2"; libraryHaskellDepends = [ base syb ]; doHaddock = false; doCheck = false; @@ -16438,19 +19372,19 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; license = "GPL"; }) {}; "hs-functors" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + ({ mkDerivation, base, dual, lib, tagged, transformers }: mkDerivation { pname = "hs-functors"; - version = "0.1.3.0"; - sha256 = "3312807260f463dc58b26765379114c144be86a94868ab2091812127902eefc8"; - libraryHaskellDepends = [ base transformers ]; + version = "0.1.7.1"; + sha256 = "3a7635be3b1dceaa227d115c84cbfa68580a082b2f04f9e3bb05641adf532fb2"; + libraryHaskellDepends = [ base dual tagged transformers ]; doHaddock = false; doCheck = false; description = "Functors from products of Haskell and its dual to Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hs-php-session" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "hs-php-session"; version = "0.0.9.3"; @@ -16460,110 +19394,69 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/elblake/hs-php-session"; description = "PHP session and values serialization"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "hsass" = callPackage - ({ mkDerivation, base, bytestring, data-default-class, filepath - , hlibsass, monad-loops, stdenv, transformers + "hs-tags" = callPackage + ({ mkDerivation, base, Cabal, containers, directory, filepath, ghc + , lib, mtl, process, strict }: mkDerivation { - pname = "hsass"; - version = "0.8.0"; - sha256 = "afb4d904253e59c4f0e271fee24fabb97090372cb53c12d7bc8bd5db8cdcd2ae"; - libraryHaskellDepends = [ - base bytestring data-default-class filepath hlibsass monad-loops - transformers - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/jakubfijalkowski/hsass"; - description = "Integrating Sass into Haskell applications"; - license = stdenv.lib.licenses.mit; - }) {}; - "hschema" = callPackage - ({ mkDerivation, base, comonad, contravariant, free, hashable - , invariant, lens, mtl, natural-transformation, profunctors, stdenv - , text, unordered-containers, vector - }: - mkDerivation { - pname = "hschema"; - version = "0.0.1.1"; - sha256 = "3218cf757cd0ca57b47d3f63c2f599e785ee225e7d17cae0b15656ffa32785e8"; - libraryHaskellDepends = [ - base comonad contravariant free hashable invariant lens mtl - natural-transformation profunctors text unordered-containers vector - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/alonsodomin/haskell-schema#readme"; - description = "Describe schemas for your Haskell data types"; - license = stdenv.lib.licenses.lgpl3; - }) {}; - "hschema-aeson" = callPackage - ({ mkDerivation, aeson, base, comonad, contravariant, free, hschema - , hschema-prettyprinter, hschema-quickcheck, lens, mtl - , natural-transformation, prettyprinter - , prettyprinter-ansi-terminal, QuickCheck, quickcheck-instances - , scientific, stdenv, text, time, unordered-containers, vector - }: - mkDerivation { - pname = "hschema-aeson"; - version = "0.0.1.1"; - sha256 = "4c5f8b24c25ca385f16a6adbad175240b258746594083aa8213257eba35e057d"; - libraryHaskellDepends = [ - aeson base comonad contravariant free hschema hschema-prettyprinter - hschema-quickcheck lens mtl natural-transformation prettyprinter - prettyprinter-ansi-terminal QuickCheck quickcheck-instances - scientific text time unordered-containers vector + pname = "hs-tags"; + version = "0.1.5"; + sha256 = "0ee1f017295f98eabbcf7676e607c920a501ec6c29c55daf51a714913549c83f"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ + base Cabal containers directory filepath ghc mtl process strict ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/alonsodomin/haskell-schema#readme"; - description = "Describe schemas for your Haskell data types"; - license = stdenv.lib.licenses.lgpl3; + description = "Create tag files (ctags and etags) for Haskell code"; + license = lib.licenses.mit; }) {}; - "hschema-prettyprinter" = callPackage - ({ mkDerivation, base, contravariant, free, hschema, lens, mtl - , natural-transformation, prettyprinter - , prettyprinter-ansi-terminal, stdenv, text, unordered-containers - , vector + "hsass" = callPackage + ({ mkDerivation, base, bytestring, data-default-class, filepath + , hlibsass, lib, monad-loops, transformers }: mkDerivation { - pname = "hschema-prettyprinter"; - version = "0.0.1.1"; - sha256 = "eff29fe173f759b80f5a2f762f35a730aa914ffe94a250955de1f134c5c07fee"; + pname = "hsass"; + version = "0.8.0"; + sha256 = "afb4d904253e59c4f0e271fee24fabb97090372cb53c12d7bc8bd5db8cdcd2ae"; + revision = "1"; + editedCabalFile = "0d085g21zvawl2jv6ap5fyk70c9igbjiwknvk1mgdydxbm1kvyq5"; libraryHaskellDepends = [ - base contravariant free hschema lens mtl natural-transformation - prettyprinter prettyprinter-ansi-terminal text unordered-containers - vector + base bytestring data-default-class filepath hlibsass monad-loops + transformers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/alonsodomin/haskell-schema#readme"; - description = "Describe schemas for your Haskell data types"; - license = stdenv.lib.licenses.lgpl3; + homepage = "https://github.com/jakubfijalkowski/hsass"; + description = "Integrating Sass into Haskell applications"; + license = lib.licenses.mit; }) {}; - "hschema-quickcheck" = callPackage - ({ mkDerivation, base, free, hschema, lens, mtl - , natural-transformation, QuickCheck, quickcheck-instances, stdenv - , text, unordered-containers, vector + "hsc2hs" = callPackage + ({ mkDerivation, base, containers, directory, filepath, lib + , process }: mkDerivation { - pname = "hschema-quickcheck"; - version = "0.0.1.1"; - sha256 = "b94aedaacddcadd935ec1dec43568826b6c98e3933a7e22d877df96cac75a9e5"; - libraryHaskellDepends = [ - base free hschema lens mtl natural-transformation QuickCheck - quickcheck-instances text unordered-containers vector + pname = "hsc2hs"; + version = "0.68.7"; + sha256 = "fd7915e41e3ed3bc7750fee0e8add2b4f32dcac8b7c544cfdf5542293223894a"; + revision = "1"; + editedCabalFile = "0nzmlx0kdsq5231m6dbvdb5zssj1h4lkqplp8rb28z3yl5h6h3sa"; + isLibrary = false; + isExecutable = true; + enableSeparateDataOutput = true; + executableHaskellDepends = [ + base containers directory filepath process ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/alonsodomin/haskell-schema#readme"; - description = "Describe schemas for your Haskell data types"; - license = stdenv.lib.licenses.lgpl3; + description = "A preprocessor that helps with writing Haskell bindings to C code"; + license = lib.licenses.bsd3; }) {}; "hscolour" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "hscolour"; version = "1.24.4"; @@ -16579,205 +19472,139 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; description = "Colourise Haskell code"; license = "LGPL"; }) {}; - "hsdev" = callPackage - ({ mkDerivation, aeson, aeson-pretty, array, async, attoparsec - , base, bytestring, Cabal, containers, cpphs, data-default, deepseq - , direct-sqlite, directory, exceptions, filepath, fsnotify, ghc - , ghc-boot, ghc-paths, haskell-names, haskell-src-exts, hformat - , hlint, HTTP, lens, lifted-base, mmorph, monad-control - , monad-loops, mtl, network, optparse-applicative, process - , regex-pcre-builtin, scientific, simple-log, sqlite-simple, stdenv - , stm, syb, template-haskell, text, text-region, time, transformers - , transformers-base, traverse-with-class, uniplate, unix - , unordered-containers, vector - }: - mkDerivation { - pname = "hsdev"; - version = "0.3.2.3"; - sha256 = "3bb80c8afb08919e373a8fb8cf5e4baa286ac97d19845e8e2123ec7634a5610f"; - configureFlags = [ "-f-docs" ]; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - aeson aeson-pretty array async attoparsec base bytestring Cabal - containers cpphs data-default deepseq direct-sqlite directory - exceptions filepath fsnotify ghc ghc-boot ghc-paths haskell-names - haskell-src-exts hformat hlint HTTP lens lifted-base mmorph - monad-control monad-loops mtl network optparse-applicative process - regex-pcre-builtin scientific simple-log sqlite-simple stm syb - template-haskell text text-region time transformers - transformers-base traverse-with-class uniplate unix - unordered-containers vector - ]; - executableHaskellDepends = [ - aeson aeson-pretty base bytestring containers deepseq directory - exceptions filepath monad-loops mtl network optparse-applicative - process text transformers unordered-containers - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/mvoidex/hsdev"; - description = "Haskell development library"; - license = stdenv.lib.licenses.bsd3; - }) {}; "hsdns" = callPackage - ({ mkDerivation, adns, base, containers, network, stdenv }: + ({ mkDerivation, adns, base, containers, lib, network }: mkDerivation { pname = "hsdns"; - version = "1.7.1"; - sha256 = "4fcd00e85cde989652ab5c6b179610c9514180a00cd7b161ea33ebfec3b8a044"; + version = "1.8"; + sha256 = "60e2c1467d381ab183c95e29de58f9b0514309f21d728fec700a42adff73b64b"; + revision = "1"; + editedCabalFile = "09ixj0xywmbigfhqmq58dwqns8l3w6wprykafg52fx69bvhg9yph"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base containers network ]; librarySystemDepends = [ adns ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/peti/hsdns"; + homepage = "https://github.com/peti/hsdns"; description = "Asynchronous DNS Resolver"; - license = stdenv.lib.licenses.lgpl3; + license = lib.licenses.lgpl3Only; }) {inherit (pkgs) adns;}; "hsebaysdk" = callPackage - ({ mkDerivation, aeson, base, bytestring, http-client, http-types - , stdenv, text, time, transformers, unordered-containers + ({ mkDerivation, aeson, base, bytestring, http-client + , http-client-tls, http-types, lib, text, time, transformers + , unordered-containers }: mkDerivation { pname = "hsebaysdk"; - version = "0.4.0.0"; - sha256 = "0738d0df113b15bb9148ecbe02f0a34562c557d8f64b65065122925e29df8901"; + version = "0.4.1.0"; + sha256 = "6379051c8c83916bb93a7eccce23a9f76f17bd675bfa539cc25831208f313878"; libraryHaskellDepends = [ - aeson base bytestring http-client http-types text time transformers - unordered-containers + aeson base bytestring http-client http-client-tls http-types text + time transformers unordered-containers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/creichert/hsebaysdk"; description = "Haskell eBay SDK"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hsemail" = callPackage - ({ mkDerivation, base, mtl, old-time, parsec, stdenv }: + ({ mkDerivation, base, lib, parsec, time, time-compat }: mkDerivation { pname = "hsemail"; - version = "2"; - sha256 = "f5f08a879444abd1f9a8a3e620d7fc83bc632ae3ba9b545bebdf58d5f4bfa8d9"; - libraryHaskellDepends = [ base mtl old-time parsec ]; + version = "2.2.1"; + sha256 = "b5ea99b4d98c988f1ca248a5641e3ecbe22b200cfcecfd1011fdaa93af961d81"; + libraryHaskellDepends = [ base parsec time time-compat ]; doHaddock = false; doCheck = false; homepage = "https://github.com/peti/hsemail#readme"; - description = "Parsec parsers for the RFC2822 Internet Message format"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "hset" = callPackage - ({ mkDerivation, base, deepseq, stdenv, tagged, type-fun }: - mkDerivation { - pname = "hset"; - version = "2.2.0"; - sha256 = "b8747a0826aeaca2ca814e7a334f9de5a02f36ac83faea5e1c32c8f6040bf130"; - libraryHaskellDepends = [ base deepseq tagged type-fun ]; - doHaddock = false; - doCheck = false; - homepage = "https://bitbucket.org/s9gf4ult/hset"; - description = "Primitive list with elements of unique types"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "hsexif" = callPackage - ({ mkDerivation, base, binary, bytestring, containers, iconv - , stdenv, text, time - }: - mkDerivation { - pname = "hsexif"; - version = "0.6.1.6"; - sha256 = "0f7e14cdec698c4e8e17ec84971ca5a604c9e75a861806dbf7088cdfc706b55d"; - revision = "1"; - editedCabalFile = "1dgcgsmx0k5p3ibfv3n5k0c5p1is2m5zfsd2s6nc6d0pz34d4wl9"; - libraryHaskellDepends = [ - base binary bytestring containers iconv text time - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/emmanueltouzery/hsexif"; - description = "EXIF handling library in pure Haskell"; - license = stdenv.lib.licenses.bsd3; + description = "Parsec parsers for the Internet Message format (e-mail)"; + license = lib.licenses.bsd3; }) {}; "hsini" = callPackage - ({ mkDerivation, base, bytestring, containers, mtl, parsec, stdenv - }: + ({ mkDerivation, base, bytestring, containers, lib, mtl, parsec }: mkDerivation { pname = "hsini"; version = "0.5.1.2"; sha256 = "eaa6ae68c6271d5c3187054e702719b3ee7916524ffda27bb328cc9aad9ed8e4"; + revision = "1"; + editedCabalFile = "0wkvajjgs64l4wlw8s6sn3pbwx3ni41p1260chp67a16innr1qp6"; libraryHaskellDepends = [ base bytestring containers mtl parsec ]; doHaddock = false; doCheck = false; description = "ini configuration files"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hsinstall" = callPackage - ({ mkDerivation, base, Cabal, directory, filepath, heredoc, process - , safe-exceptions, stdenv + ({ mkDerivation, ansi-wl-pprint, base, Cabal, directory, filepath + , heredoc, lib, optparse-applicative, process, safe-exceptions + , transformers }: mkDerivation { pname = "hsinstall"; - version = "2.2"; - sha256 = "23a702c43e0f42ad916aedd5b53970a6e64708ffc50d1d509904ebad3d478991"; + version = "2.6"; + sha256 = "85aa6d67f88e12f5a3590889c682a6252213478c86510546b44a7b44fd97c31c"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base directory filepath ]; executableHaskellDepends = [ - base Cabal directory filepath heredoc process safe-exceptions + ansi-wl-pprint base Cabal directory filepath heredoc + optparse-applicative process safe-exceptions transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/dino-/hsinstall#readme"; description = "Install Haskell software"; - license = stdenv.lib.licenses.isc; + license = lib.licenses.isc; }) {}; "hslogger" = callPackage - ({ mkDerivation, base, containers, directory, mtl, network - , old-locale, process, stdenv, time, unix + ({ mkDerivation, base, bytestring, containers, deepseq, lib + , network, network-bsd, old-locale, time, unix }: mkDerivation { pname = "hslogger"; - version = "1.2.12"; - sha256 = "f97a4c89d0921f237999de5d44950127dbe8baa177960ccccbfb79cccfd46c7a"; - revision = "1"; - editedCabalFile = "1rk2lrg3959nbgbyd1aacvwbv865lsrnczqdmj4ivkfn0c8nkidh"; + version = "1.3.1.0"; + sha256 = "7f2364f6c0b9c5b85a257267a335816126ef2471c817a42797a5d3c57acaca5b"; + revision = "3"; + editedCabalFile = "04mda3bwr2a00f5nbkqc84d46lmqfsk3gibzg3amdh74ngb451xq"; libraryHaskellDepends = [ - base containers directory mtl network old-locale process time unix + base bytestring containers deepseq network network-bsd old-locale + time unix ]; doHaddock = false; doCheck = false; - homepage = "http://software.complete.org/hslogger"; + homepage = "https://github.com/hvr/hslogger/wiki"; description = "Versatile logging framework"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hslua" = callPackage - ({ mkDerivation, base, bytestring, containers, exceptions, fail - , lua5_3, mtl, stdenv, text + ({ mkDerivation, base, bytestring, containers, exceptions, lib + , lua5_3, mtl, text }: mkDerivation { pname = "hslua"; - version = "1.0.2"; - sha256 = "fda9b291051769a02c175f744bc2175f5ff49732c83e7063cf6c786bcc654f70"; + version = "1.3.0.1"; + sha256 = "678a833942033d45a3e492d5717834c952068bb558d60a8970eac136c2fce8d7"; configureFlags = [ "-fsystem-lua" "-f-use-pkgconfig" ]; libraryHaskellDepends = [ - base bytestring containers exceptions fail mtl text + base bytestring containers exceptions mtl text ]; librarySystemDepends = [ lua5_3 ]; doHaddock = false; doCheck = false; homepage = "https://hslua.github.io/"; description = "Bindings to Lua, an embeddable scripting language"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {inherit (pkgs) lua5_3;}; "hslua-aeson" = callPackage - ({ mkDerivation, aeson, base, hashable, hslua, scientific, stdenv + ({ mkDerivation, aeson, base, hashable, hslua, lib, scientific , text, unordered-containers, vector }: mkDerivation { pname = "hslua-aeson"; - version = "1.0.0"; - sha256 = "ffa7c2f6cb90a914f796334c8f07b1eb7bfd9b3717c55d8f756589dd14706c73"; + version = "1.0.3.1"; + sha256 = "b9c0d14c5e24f567a3e86d355603d02ac1d2564fda2b8a8b6f493ce828987a4f"; libraryHaskellDepends = [ aeson base hashable hslua scientific text unordered-containers vector @@ -16786,23 +19613,66 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/tarleb/hslua-aeson#readme"; description = "Allow aeson data types to be used with lua"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "hslua-module-doclayout" = callPackage + ({ mkDerivation, base, doclayout, hslua, lib, text }: + mkDerivation { + pname = "hslua-module-doclayout"; + version = "0.2.0.1"; + sha256 = "1e01850a3ee1625f6e3c14037621a11bacc353afe75241f43ba4884d0bea9fbb"; + libraryHaskellDepends = [ base doclayout hslua text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/hslua/hslua-module-doclayout"; + description = "Lua module wrapping Text.DocLayout."; + license = lib.licenses.mit; + }) {}; + "hslua-module-path" = callPackage + ({ mkDerivation, base, filepath, hslua, lib, text }: + mkDerivation { + pname = "hslua-module-path"; + version = "0.1.0.1"; + sha256 = "c858d8900f9fbde354ebfc90fce84d10c89b9f51ab62198df033936399a4aeff"; + libraryHaskellDepends = [ base filepath hslua text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/hslua/hslua-module-path"; + description = "Lua module to work with file paths"; + license = lib.licenses.mit; + }) {}; + "hslua-module-system" = callPackage + ({ mkDerivation, base, containers, directory, exceptions, hslua + , lib, temporary + }: + mkDerivation { + pname = "hslua-module-system"; + version = "0.2.2.1"; + sha256 = "c1ed0f31e57b13aa3ec20ae12ec62aacab21c8a250daf99ea57769e5e9d56242"; + libraryHaskellDepends = [ + base containers directory exceptions hslua temporary + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/hslua/hslua-module-system"; + description = "Lua module wrapper around Haskell's System module"; + license = lib.licenses.mit; }) {}; "hslua-module-text" = callPackage - ({ mkDerivation, base, bytestring, hslua, stdenv, text }: + ({ mkDerivation, base, bytestring, hslua, lib, text }: mkDerivation { pname = "hslua-module-text"; - version = "0.2.0"; - sha256 = "711705b9befac9b65cc44e13483dc5b6ddcca45bc049813863653276908d8f7e"; + version = "0.3.0.1"; + sha256 = "d42d06c802b7227c8accc3184fceb6b6ec99e0f81091d335bb2216906c09adee"; libraryHaskellDepends = [ base bytestring hslua text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/hslua/hslua-module-text"; description = "Lua module for text"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hsp" = callPackage - ({ mkDerivation, base, mtl, stdenv, text }: + ({ mkDerivation, base, lib, mtl, text }: mkDerivation { pname = "hsp"; version = "0.10.0"; @@ -16812,16 +19682,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://hub.darcs.net/nibro/hsp"; description = "Haskell Server Pages is a library for writing dynamic server-side web pages"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hspec" = callPackage ({ mkDerivation, base, hspec-core, hspec-discover - , hspec-expectations, QuickCheck, stdenv + , hspec-expectations, lib, QuickCheck }: mkDerivation { pname = "hspec"; - version = "2.6.1"; - sha256 = "8bf646f45bfd3d30f41f7b686af3317708456f1582555af1cfc2e4ea1bc46eca"; + version = "2.7.10"; + sha256 = "3c1bbda1962b2a493ad0bea0039720011948ac194c4c63d1c9f44d9c6be6147c"; libraryHaskellDepends = [ base hspec-core hspec-discover hspec-expectations QuickCheck ]; @@ -16829,11 +19699,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://hspec.github.io/"; description = "A Testing Framework for Haskell"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hspec-attoparsec" = callPackage ({ mkDerivation, attoparsec, base, bytestring, hspec-expectations - , stdenv, text + , lib, text }: mkDerivation { pname = "hspec-attoparsec"; @@ -16846,10 +19716,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/alpmestan/hspec-attoparsec"; description = "Utility functions for testing your attoparsec parsers with hspec"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hspec-checkers" = callPackage - ({ mkDerivation, base, checkers, hspec, stdenv }: + ({ mkDerivation, base, checkers, hspec, lib }: mkDerivation { pname = "hspec-checkers"; version = "0.1.0.2"; @@ -16858,10 +19728,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Allows to use checkers properties from hspec"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hspec-contrib" = callPackage - ({ mkDerivation, base, hspec-core, HUnit, stdenv }: + ({ mkDerivation, base, hspec-core, HUnit, lib }: mkDerivation { pname = "hspec-contrib"; version = "0.5.1"; @@ -16873,18 +19743,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://hspec.github.io/"; description = "Contributed functionality for Hspec"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hspec-core" = callPackage ({ mkDerivation, ansi-terminal, array, base, call-stack, clock - , deepseq, directory, filepath, hspec-expectations, HUnit - , QuickCheck, quickcheck-io, random, setenv, stdenv, stm, tf-random + , deepseq, directory, filepath, hspec-expectations, HUnit, lib + , QuickCheck, quickcheck-io, random, setenv, stm, tf-random , transformers }: mkDerivation { pname = "hspec-core"; - version = "2.6.1"; - sha256 = "7b2b421bc407c149e480c8028bee02781916a3671c1f814a84cadc63d51ce475"; + version = "2.7.10"; + sha256 = "61d34e914b7c6bc01cac654de7bcb587f6b17969c0e49808512ddbffcaf5698a"; libraryHaskellDepends = [ ansi-terminal array base call-stack clock deepseq directory filepath hspec-expectations HUnit QuickCheck quickcheck-io random @@ -16895,14 +19765,14 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; testTarget = "--test-option=--skip --test-option='Test.Hspec.Core.Runner.hspecResult runs specs in parallel'"; homepage = "http://hspec.github.io/"; description = "A Testing Framework for Haskell"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hspec-discover" = callPackage - ({ mkDerivation, base, directory, filepath, stdenv }: + ({ mkDerivation, base, directory, filepath, lib }: mkDerivation { pname = "hspec-discover"; - version = "2.6.1"; - sha256 = "9d569a9587d2034272d287442855490a06266192eba1da871cae7d971b922fa1"; + version = "2.7.10"; + sha256 = "0a576d00c67f1b093062130d0dcdaffb13c6812653db18f49e3a1db346dbdf8f"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base directory filepath ]; @@ -16911,10 +19781,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://hspec.github.io/"; description = "Automatically discover and run Hspec tests"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hspec-expectations" = callPackage - ({ mkDerivation, base, call-stack, HUnit, stdenv }: + ({ mkDerivation, base, call-stack, HUnit, lib }: mkDerivation { pname = "hspec-expectations"; version = "0.8.2"; @@ -16924,10 +19794,28 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/hspec/hspec-expectations#readme"; description = "Catchy combinators for HUnit"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "hspec-expectations-json" = callPackage + ({ mkDerivation, aeson, aeson-pretty, base, Diff, HUnit, lib + , scientific, text, unordered-containers, vector + }: + mkDerivation { + pname = "hspec-expectations-json"; + version = "1.0.0.4"; + sha256 = "67855531d0fcbb45c4220e9eebc36dfca30a67b293a941a9148f91ecae2744d4"; + libraryHaskellDepends = [ + aeson aeson-pretty base Diff HUnit scientific text + unordered-containers vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/freckle/hspec-expectations-json#readme"; + description = "Hspec expectations for JSON Values"; + license = lib.licenses.mit; }) {}; "hspec-expectations-lifted" = callPackage - ({ mkDerivation, base, hspec-expectations, stdenv, transformers }: + ({ mkDerivation, base, hspec-expectations, lib, transformers }: mkDerivation { pname = "hspec-expectations-lifted"; version = "0.10.0"; @@ -16936,16 +19824,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A version of hspec-expectations generalized to MonadIO"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hspec-expectations-pretty-diff" = callPackage - ({ mkDerivation, ansi-terminal, base, Diff, hscolour, HUnit - , nicify-lib, stdenv, text + ({ mkDerivation, ansi-terminal, base, Diff, hscolour, HUnit, lib + , nicify-lib, text }: mkDerivation { pname = "hspec-expectations-pretty-diff"; - version = "0.7.2.4"; - sha256 = "1bbfd524330be3cb0b27945556d01f48e3005e042ee475cdf6e441ba21b51b0a"; + version = "0.7.2.5"; + sha256 = "9479251e851c07af1b88ebe91d9a20d074f505209f253ebd6f379f3914ab6210"; libraryHaskellDepends = [ ansi-terminal base Diff hscolour HUnit nicify-lib text ]; @@ -16953,12 +19841,30 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/myfreeweb/hspec-expectations-pretty-diff#readme"; description = "Catchy combinators for HUnit"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "hspec-golden" = callPackage + ({ mkDerivation, base, directory, hspec-core, lib + , optparse-applicative + }: + mkDerivation { + pname = "hspec-golden"; + version = "0.1.0.3"; + sha256 = "9418291aed76e7654591074a04e0ff4b25b2443f8b628370983c3860c958aab4"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base directory hspec-core ]; + executableHaskellDepends = [ base directory optparse-applicative ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/stackbuilders/hspec-golden#readme"; + description = "Golden tests for hspec"; + license = lib.licenses.mit; }) {}; "hspec-golden-aeson" = callPackage ({ mkDerivation, aeson, aeson-pretty, base, bytestring, directory - , filepath, hspec, QuickCheck, quickcheck-arbitrary-adt, random - , stdenv, transformers + , filepath, hspec, lib, QuickCheck, quickcheck-arbitrary-adt + , random, transformers }: mkDerivation { pname = "hspec-golden-aeson"; @@ -16972,32 +19878,67 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/plow-technologies/hspec-golden-aeson#readme"; description = "Use tests to monitor changes in Aeson serialization"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "hspec-leancheck" = callPackage - ({ mkDerivation, base, hspec, hspec-core, HUnit, leancheck, stdenv + "hspec-hedgehog" = callPackage + ({ mkDerivation, base, hedgehog, hspec, hspec-core, HUnit, lib + , QuickCheck, splitmix }: + mkDerivation { + pname = "hspec-hedgehog"; + version = "0.0.1.2"; + sha256 = "23582ee0f9807b2e49de5da4ae8ef83cb56db63a045a7db73d537eab35c9eb9d"; + revision = "1"; + editedCabalFile = "1qv2gap0775d2zg8wbd3kq4ypziz05qlz5jfisvl3jfd6jzcf2ad"; + libraryHaskellDepends = [ + base hedgehog hspec hspec-core HUnit QuickCheck splitmix + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/parsonsmatt/hspec-hedgehog#readme"; + description = "Integrate Hedgehog and Hspec!"; + license = lib.licenses.bsd3; + }) {}; + "hspec-junit-formatter" = callPackage + ({ mkDerivation, base, conduit, directory, exceptions, hashable + , hspec, hspec-core, lib, resourcet, temporary, text, xml-conduit + , xml-types + }: + mkDerivation { + pname = "hspec-junit-formatter"; + version = "1.0.0.5"; + sha256 = "bbd544a293d3565fd8e84c5002a892143b881a287aef34b2a0c07e38b71eb368"; + libraryHaskellDepends = [ + base conduit directory exceptions hashable hspec hspec-core + resourcet temporary text xml-conduit xml-types + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/freckle/hspec-junit-formatter#readme"; + description = "A JUnit XML runner/formatter for hspec"; + license = lib.licenses.mit; + }) {}; + "hspec-leancheck" = callPackage + ({ mkDerivation, base, hspec, hspec-core, HUnit, leancheck, lib }: mkDerivation { pname = "hspec-leancheck"; - version = "0.0.3"; - sha256 = "38de8e98ca16e54370f2387c2ceb22fadab53ada5e9c0505ce9fe23f1b99d852"; + version = "0.0.6"; + sha256 = "519f3f0a172303fc3fa660bc0b62e2c962cc3c6fe61961baa2b7eae1255e7bdd"; libraryHaskellDepends = [ base hspec hspec-core HUnit leancheck ]; doHaddock = false; doCheck = false; homepage = "https://github.com/rudymatela/hspec-leancheck#readme"; description = "LeanCheck support for the Hspec test framework"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hspec-megaparsec" = callPackage - ({ mkDerivation, base, containers, hspec-expectations, megaparsec - , stdenv + ({ mkDerivation, base, containers, hspec-expectations, lib + , megaparsec }: mkDerivation { pname = "hspec-megaparsec"; - version = "2.0.0"; - sha256 = "a8f96f685cf6bbad06b70822c6c55bf7bc70e7e444402825c8ca232f18589b30"; - revision = "1"; - editedCabalFile = "15hpf1v1d4dwzdvk7xhgj37yd37pcyj6yzw750k1fcj6j0hk4rb7"; + version = "2.2.0"; + sha256 = "f609b4bb7e38ecba0503f1fc349a2600f5c799ef3c33731ad6a6e1ff9f01ce43"; libraryHaskellDepends = [ base containers hspec-expectations megaparsec ]; @@ -17005,72 +19946,66 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mrkkrp/hspec-megaparsec"; description = "Utility functions for testing Megaparsec parsers with Hspec"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hspec-meta" = callPackage ({ mkDerivation, ansi-terminal, array, base, call-stack, clock - , deepseq, directory, filepath, hspec-expectations, HUnit - , QuickCheck, quickcheck-io, random, setenv, stdenv, stm, time - , transformers + , deepseq, directory, filepath, lib, QuickCheck, quickcheck-io + , random, setenv, stm, time, transformers }: mkDerivation { pname = "hspec-meta"; - version = "2.6.0"; - sha256 = "e6d701c9f366f6762eb2a86022d1c7a7d7631c100945491ff53b3a3e86212ad8"; - revision = "1"; - editedCabalFile = "1qh3j6mhlz2bvdk8qc5fa4nqh93q4vqnvxmqqisg4agacnvyp4b2"; + version = "2.7.8"; + sha256 = "510389dc19835641c165b3d111f2f7fb34f67c7395ada7bd8b28070f8505d269"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ ansi-terminal array base call-stack clock deepseq directory - filepath hspec-expectations HUnit QuickCheck quickcheck-io random - setenv stm time transformers + filepath QuickCheck quickcheck-io random setenv stm time + transformers ]; executableHaskellDepends = [ ansi-terminal array base call-stack clock deepseq directory - filepath hspec-expectations HUnit QuickCheck quickcheck-io random - setenv stm time transformers + filepath QuickCheck quickcheck-io random setenv stm time + transformers ]; doHaddock = false; doCheck = false; homepage = "http://hspec.github.io/"; description = "A version of Hspec which is used to test Hspec itself"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hspec-need-env" = callPackage - ({ mkDerivation, base, hspec-core, hspec-expectations, stdenv }: + ({ mkDerivation, base, hspec-core, hspec-expectations, lib }: mkDerivation { pname = "hspec-need-env"; - version = "0.1.0.2"; - sha256 = "daba5ca572b1c84cf2d6394ba416ac20a753f78599b22727732d4ba51ca0230d"; + version = "0.1.0.7"; + sha256 = "7772886f6675b95abffda4159bf2ce22bf13185362669865fba017392cd90c19"; libraryHaskellDepends = [ base hspec-core hspec-expectations ]; doHaddock = false; doCheck = false; homepage = "https://github.com/debug-ito/hspec-need-env"; description = "Read environment variables for hspec tests"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "hspec-pg-transact" = callPackage - ({ mkDerivation, base, bytestring, hspec, pg-transact - , postgresql-simple, resource-pool, stdenv, text, tmp-postgres - }: + "hspec-parsec" = callPackage + ({ mkDerivation, base, hspec-expectations, lib, parsec }: mkDerivation { - pname = "hspec-pg-transact"; - version = "0.1.0.2"; - sha256 = "a5ec2a978a730500f03c15d16eff7e207a4135ebc63afe4cbca7392ad5f01c0c"; - libraryHaskellDepends = [ - base bytestring hspec pg-transact postgresql-simple resource-pool - text tmp-postgres - ]; + pname = "hspec-parsec"; + version = "0"; + sha256 = "decc5a32ba44968fbe69f213cb97a6c7d3a4601fa8df75365f7727f61b41a4e0"; + revision = "1"; + editedCabalFile = "03nsxwc5p6whq21dqwba0289g8fqqqws453kyanwgb6vvg1f0s9l"; + libraryHaskellDepends = [ base hspec-expectations parsec ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/jfischoff/pg-transact-hspec#readme"; - description = "Helpers for creating database tests with hspec and pg-transact"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/sjakobi/hspec-parsec#readme"; + description = "Hspec expectations for testing Parsec parsers"; + license = lib.licenses.bsd3; }) {}; "hspec-smallcheck" = callPackage - ({ mkDerivation, base, call-stack, hspec-core, HUnit, smallcheck - , stdenv + ({ mkDerivation, base, call-stack, hspec-core, HUnit, lib + , smallcheck }: mkDerivation { pname = "hspec-smallcheck"; @@ -17083,17 +20018,32 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://hspec.github.io/"; description = "SmallCheck support for the Hspec testing framework"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "hspec-tables" = callPackage + ({ mkDerivation, base, hspec-core, lib }: + mkDerivation { + pname = "hspec-tables"; + version = "0.0.1"; + sha256 = "3870f1db7dcc97e4ab07ec4996066301d19fb369d8c1610e9b05e506442ae81f"; + revision = "1"; + editedCabalFile = "1li02kvz1mpq0x9j7q7cjwn8b35m2aqgfbrgab4vsngqq61a4f0z"; + libraryHaskellDepends = [ base hspec-core ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/marcin-rzeznicki/hspec-tables"; + description = "Table-driven (by-example) HSpec tests"; + license = lib.licenses.mit; }) {}; "hspec-wai" = callPackage ({ mkDerivation, base, base-compat, bytestring, case-insensitive - , hspec-core, hspec-expectations, http-types, QuickCheck, stdenv - , text, transformers, wai, wai-extra + , hspec-core, hspec-expectations, http-types, lib, QuickCheck, text + , transformers, wai, wai-extra }: mkDerivation { pname = "hspec-wai"; - version = "0.9.2"; - sha256 = "055e414bd6531d3454496f9c4bfa1164b861aa9a9102867d7ffeef8d3a92283f"; + version = "0.11.0"; + sha256 = "1d5cdaa1ef75f33b5d5a2b7bfb460a76783585a7b71ef243f0f2aaa2f31e623a"; libraryHaskellDepends = [ base base-compat bytestring case-insensitive hspec-core hspec-expectations http-types QuickCheck text transformers wai @@ -17103,16 +20053,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/hspec/hspec-wai#readme"; description = "Experimental Hspec support for testing WAI applications"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hspec-wai-json" = callPackage ({ mkDerivation, aeson, aeson-qq, base, bytestring - , case-insensitive, hspec-wai, stdenv, template-haskell + , case-insensitive, hspec-wai, lib, template-haskell }: mkDerivation { pname = "hspec-wai-json"; - version = "0.9.2"; - sha256 = "82e324482e04662121a14fc75232e7359d6d1454623c37253b6550a8ec6ccadc"; + version = "0.11.0"; + sha256 = "c4a348d63f1670b94980a148128b3360e3652d6a40467a08292f49b49c042a33"; libraryHaskellDepends = [ aeson aeson-qq base bytestring case-insensitive hspec-wai template-haskell @@ -17121,45 +20071,49 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/hspec/hspec-wai#readme"; description = "Testing JSON APIs with hspec-wai"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "hstatsd" = callPackage - ({ mkDerivation, base, bytestring, mtl, network, stdenv, text }: + "hsshellscript" = callPackage + ({ mkDerivation, base, c2hs, directory, lib, parsec, random, unix + }: mkDerivation { - pname = "hstatsd"; - version = "0.1"; - sha256 = "446779594257c0fa02d5271c997ee0c22f74f7636d89e34394ad87e5bd285824"; - libraryHaskellDepends = [ base bytestring mtl network text ]; + pname = "hsshellscript"; + version = "3.5.0"; + sha256 = "f94d9d118e0b13e4a2cf5c8686e519baeca49f208c97d62b93e12cb0c632b2bd"; + libraryHaskellDepends = [ base directory parsec random unix ]; + libraryToolDepends = [ c2hs ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/mokus0/hstatsd"; - description = "Quick and dirty statsd interface"; - license = stdenv.lib.licenses.publicDomain; + homepage = "http://www.volker-wysk.de/hsshellscript/"; + description = "Haskell for Unix shell scripting tasks"; + license = "LGPL"; }) {}; "hsyslog" = callPackage - ({ mkDerivation, base, Cabal, cabal-doctest, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "hsyslog"; - version = "5.0.1"; - sha256 = "86de0d8820a6cb7fe166e046ae00c1bbe37d27885cd3aa701deaca8fdf646016"; + version = "5.0.2"; + sha256 = "3eec43c8fb42c23d03f1db7b0b594d39cd94275c2284dcd0c64aa4d680bd7ece"; + revision = "1"; + editedCabalFile = "0k1j46nk3z64zw4bqmvw5lgy16ih200m66rv4b6ygjqv7nglqq0b"; isLibrary = true; isExecutable = true; - setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/peti/hsyslog"; + homepage = "https://github.com/peti/hsyslog"; description = "FFI interface to syslog(3) from POSIX.1-2001"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "htaglib" = callPackage - ({ mkDerivation, base, bytestring, stdenv, taglib, text - , transformers + ({ mkDerivation, base, bytestring, lib, taglib, text, transformers }: mkDerivation { pname = "htaglib"; version = "1.2.0"; sha256 = "4a17c36ff45995c079d71368a3eeabe595ed7efe2b3e4a3dcbff4bed8324005e"; + revision = "1"; + editedCabalFile = "09vsz2z5sb5ai3qpksqdckb43vndqs66x4abx3lln2xr40dlkljv"; enableSeparateDataOutput = true; libraryHaskellDepends = [ base bytestring text transformers ]; librarySystemDepends = [ taglib ]; @@ -17167,10 +20121,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mrkkrp/htaglib"; description = "Bindings to TagLib, audio meta-data library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) taglib;}; "html" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "html"; version = "1.0.1.2"; @@ -17179,17 +20133,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "HTML combinator library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "html-conduit" = callPackage ({ mkDerivation, attoparsec, base, bytestring, conduit - , conduit-extra, containers, resourcet, stdenv, text, transformers + , conduit-extra, containers, lib, resourcet, text, transformers , xml-conduit, xml-types }: mkDerivation { pname = "html-conduit"; - version = "1.3.2"; - sha256 = "05fdbdbf9d7b610bd8d7a67e0036b52b1ec1aec276f3017194e59ee2d661b050"; + version = "1.3.2.1"; + sha256 = "3681534cb7fc132a78ac35bd9d415280cf3e7a56a875bc7161375c69d947cca4"; libraryHaskellDepends = [ attoparsec base bytestring conduit conduit-extra containers resourcet text transformers xml-conduit xml-types @@ -17198,39 +20152,26 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/snoyberg/xml"; description = "Parse HTML documents using xml-conduit datatypes"; - license = stdenv.lib.licenses.mit; - }) {}; - "html-email-validate" = callPackage - ({ mkDerivation, attoparsec, base, stdenv, text }: - mkDerivation { - pname = "html-email-validate"; - version = "0.2.0.0"; - sha256 = "3d2a3ec75b638cec71df57512473052d485dc118aec4662d5a8dae5e95aa6daf"; - libraryHaskellDepends = [ attoparsec base text ]; - doHaddock = false; - doCheck = false; - description = "Validating an email address against HTML standard"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; "html-entities" = callPackage - ({ mkDerivation, attoparsec, base, base-prelude, stdenv, text - , unordered-containers + ({ mkDerivation, attoparsec, base, lib, text, unordered-containers }: mkDerivation { pname = "html-entities"; - version = "1.1.4.2"; - sha256 = "161a0c9193b4c1279e41b2ce1203ee821e8d6ee2cf755b9f070d68602ed5cee7"; + version = "1.1.4.5"; + sha256 = "3b8f6c4ccfd4749c5031ec785a83eff87ca090937e6e093cf1ef822723811ea4"; libraryHaskellDepends = [ - attoparsec base base-prelude text unordered-containers + attoparsec base text unordered-containers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nikita-volkov/html-entities"; description = "A codec library for HTML-escaped text and HTML-entities"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "html-entity-map" = callPackage - ({ mkDerivation, base, stdenv, text, unordered-containers }: + ({ mkDerivation, base, lib, text, unordered-containers }: mkDerivation { pname = "html-entity-map"; version = "0.1.0.0"; @@ -17242,11 +20183,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mrkkrp/html-entity-map"; description = "Map from HTML5 entity names to the corresponding Unicode text"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "htoml" = callPackage - ({ mkDerivation, aeson, base, containers, old-locale, parsec - , stdenv, text, time, unordered-containers, vector + ({ mkDerivation, aeson, base, containers, lib, old-locale, parsec + , text, time, unordered-containers, vector }: mkDerivation { pname = "htoml"; @@ -17260,41 +20201,39 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/cies/htoml"; description = "Parser for TOML files"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "http-api-data" = callPackage ({ mkDerivation, attoparsec, attoparsec-iso8601, base, base-compat - , bytestring, Cabal, cabal-doctest, containers, cookie, hashable - , http-types, stdenv, tagged, text, time, time-locale-compat - , unordered-containers, uuid-types + , bytestring, containers, cookie, hashable, http-types, lib, tagged + , text, time-compat, transformers, unordered-containers, uuid-types }: mkDerivation { pname = "http-api-data"; - version = "0.4"; - sha256 = "837e3f39f23df2caa23d75a4608f4a0505a1ab23f7290006976a37a373164a8a"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "0.4.2"; + sha256 = "d4b2cf611ed4b4c1e7f4305914e02debc9112d4ba1d66fb3a53b8e017bdfee77"; libraryHaskellDepends = [ attoparsec attoparsec-iso8601 base base-compat bytestring - containers cookie hashable http-types tagged text time - time-locale-compat unordered-containers uuid-types + containers cookie hashable http-types tagged text time-compat + transformers unordered-containers uuid-types ]; doHaddock = false; doCheck = false; homepage = "http://github.com/fizruk/http-api-data"; description = "Converting to/from HTTP API data like URL pieces, headers and query parameters"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "http-client" = callPackage ({ mkDerivation, array, base, blaze-builder, bytestring , case-insensitive, containers, cookie, deepseq, exceptions - , filepath, ghc-prim, http-types, memory, mime-types, network - , network-uri, random, stdenv, stm, streaming-commons, text, time + , filepath, ghc-prim, http-types, lib, memory, mime-types, network + , network-uri, random, stm, streaming-commons, text, time , transformers }: mkDerivation { pname = "http-client"; - version = "0.5.14"; - sha256 = "8e50409704021c51a8955b2d03bfec900ebc3e11fbaebf973f2e654d7bde3647"; + version = "0.6.4.1"; + sha256 = "5742f36965c1030d7fb52b5fc67ccd45802f6f7e55eb7595df4eef6ea0eb22f8"; libraryHaskellDepends = [ array base blaze-builder bytestring case-insensitive containers cookie deepseq exceptions filepath ghc-prim http-types memory @@ -17305,18 +20244,57 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/snoyberg/http-client"; description = "An HTTP client engine"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "http-client-openssl" = callPackage + ({ mkDerivation, base, bytestring, HsOpenSSL, HsOpenSSL-x509-system + , http-client, lib, network + }: + mkDerivation { + pname = "http-client-openssl"; + version = "0.3.2.0"; + sha256 = "c5e483bf80b3c2e10f440f529d1332d71fa28f172718459986fbaf6d51648a84"; + libraryHaskellDepends = [ + base bytestring HsOpenSSL HsOpenSSL-x509-system http-client network + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/snoyberg/http-client"; + description = "http-client backend using the OpenSSL library"; + license = lib.licenses.mit; + }) {}; + "http-client-overrides" = callPackage + ({ mkDerivation, aeson, base, bytestring, http-client + , http-client-tls, http-types, lib, network-uri, text, yaml + }: + mkDerivation { + pname = "http-client-overrides"; + version = "0.1.1.0"; + sha256 = "944dc0c10c8e223ae93fbdc5b65129a7ebd1031cbe125397acf8643dbba15a95"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson base bytestring http-client http-types network-uri text yaml + ]; + executableHaskellDepends = [ base http-client http-client-tls ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/robbiemcmichael/http-client-overrides"; + description = "HTTP client overrides"; + license = lib.licenses.bsd3; }) {}; "http-client-tls" = callPackage ({ mkDerivation, base, bytestring, case-insensitive, connection , containers, cryptonite, data-default-class, exceptions - , http-client, http-types, memory, network, network-uri, stdenv - , text, tls, transformers + , http-client, http-types, lib, memory, network, network-uri, text + , tls, transformers }: mkDerivation { pname = "http-client-tls"; version = "0.3.5.3"; sha256 = "471abf8f29a909f40b21eab26a410c0e120ae12ce337512a61dae9f52ebb4362"; + revision = "1"; + editedCabalFile = "0llb5k8mz1h6zyv1nd433wwgyjsw7n8x0b1fwib312iiws43sz69"; libraryHaskellDepends = [ base bytestring case-insensitive connection containers cryptonite data-default-class exceptions http-client http-types memory network @@ -17326,88 +20304,126 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/snoyberg/http-client"; description = "http-client backend using the connection package and tls library"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "http-common" = callPackage ({ mkDerivation, base, base64-bytestring, blaze-builder, bytestring - , case-insensitive, directory, mtl, network, stdenv, text + , case-insensitive, directory, lib, mtl, network, text , transformers, unordered-containers }: mkDerivation { pname = "http-common"; - version = "0.8.2.0"; - sha256 = "2915e77b0d000a617d4c1304fdc46f45b70acc0942670066a95b2c8d4e504593"; + version = "0.8.2.1"; + sha256 = "b30dd831e499c51cf18941f2451b93e5e6ef3629caadb0ebfcb79a85130cf1df"; libraryHaskellDepends = [ base base64-bytestring blaze-builder bytestring case-insensitive directory mtl network text transformers unordered-containers ]; doHaddock = false; doCheck = false; - homepage = "http://research.operationaldynamics.com/projects/http-streams/"; + homepage = "https://github.com/istathar/http-common"; description = "Common types for HTTP clients and servers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "http-conduit" = callPackage - ({ mkDerivation, aeson, base, bytestring, conduit, conduit-extra - , http-client, http-client-tls, http-types, mtl, resourcet, stdenv - , transformers, unliftio-core + ({ mkDerivation, aeson, attoparsec, base, bytestring, conduit + , conduit-extra, http-client, http-client-tls, http-types, lib, mtl + , resourcet, transformers, unliftio-core }: mkDerivation { pname = "http-conduit"; - version = "2.3.4"; - sha256 = "2548b8705442817443e930c4ba19d4a6f4bfe862487a3eb028226cfbaa4f510f"; - revision = "1"; - editedCabalFile = "1c0cz9qxq3a0avcccqx07knnnxjjxgq81fp5wlxb6z5q6r3cpxag"; + version = "2.3.8"; + sha256 = "cfbef293856fdcce58618726ff911ca28e2ad07c8522b2cd1cfa2cb6e02542ae"; libraryHaskellDepends = [ - aeson base bytestring conduit conduit-extra http-client + aeson attoparsec base bytestring conduit conduit-extra http-client http-client-tls http-types mtl resourcet transformers unliftio-core ]; doHaddock = false; doCheck = false; homepage = "http://www.yesodweb.com/book/http-conduit"; description = "HTTP client package with conduit interface and HTTPS support"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "http-date" = callPackage - ({ mkDerivation, array, attoparsec, base, bytestring, stdenv, time - }: + ({ mkDerivation, array, attoparsec, base, bytestring, lib, time }: mkDerivation { pname = "http-date"; - version = "0.0.8"; - sha256 = "0f4c6348487abe4f9d58e43d3c23bdefc7fd1fd5672effd3c7d84aaff05f5427"; + version = "0.0.11"; + sha256 = "32f923ac1ad9bdfeadce7c52a03c9ba6225ba60dc14137cb1cdf32ea84ccf4d3"; libraryHaskellDepends = [ array attoparsec base bytestring time ]; doHaddock = false; doCheck = false; description = "HTTP Date parser/formatter"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "http-directory" = callPackage + ({ mkDerivation, base, bytestring, html-conduit, http-client + , http-client-tls, http-date, http-types, lib, network-uri, text + , time, xml-conduit + }: + mkDerivation { + pname = "http-directory"; + version = "0.1.8"; + sha256 = "963d09c7bf362c3d725711525eaf5dc1b63920c77943df03fe46b5b6cb3f5b69"; + libraryHaskellDepends = [ + base bytestring html-conduit http-client http-client-tls http-date + http-types network-uri text time xml-conduit + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/juhp/http-directory"; + description = "http directory listing library"; + license = lib.licenses.mit; + }) {}; + "http-download" = callPackage + ({ mkDerivation, base, base64-bytestring, bytestring, conduit + , conduit-extra, cryptonite, cryptonite-conduit, directory + , exceptions, filepath, http-client, http-conduit, http-types, lib + , memory, path, path-io, retry, rio, rio-prettyprint + }: + mkDerivation { + pname = "http-download"; + version = "0.2.0.0"; + sha256 = "1bd9514ea86a6447143e52ed94b1c05e3204dfd1bd60609bf64d14082693e5f1"; + libraryHaskellDepends = [ + base base64-bytestring bytestring conduit conduit-extra cryptonite + cryptonite-conduit directory exceptions filepath http-client + http-conduit http-types memory path path-io retry rio + rio-prettyprint + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/commercialhaskell/http-download#readme"; + description = "Verified downloads with retries"; + license = lib.licenses.bsd3; }) {}; "http-link-header" = callPackage - ({ mkDerivation, attoparsec, base, bytestring - , bytestring-conversion, errors, http-api-data, network-uri, stdenv - , text + ({ mkDerivation, attoparsec, base, bytestring, errors + , http-api-data, lib, network-uri, text }: mkDerivation { pname = "http-link-header"; - version = "1.0.3.1"; - sha256 = "da26db73df1eaebb20df2837b0352cc62a6c151d467bea9442767fd3d51c2a2d"; + version = "1.2.0"; + sha256 = "e96d6bc500a2be101a3e5c8233a02910a6d976a7e23ab57a3c575d141dca1bf8"; libraryHaskellDepends = [ - attoparsec base bytestring bytestring-conversion errors - http-api-data network-uri text + attoparsec base bytestring errors http-api-data network-uri text ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/myfreeweb/http-link-header"; - description = "A parser and writer for the HTTP Link header as specified in RFC 5988 \"Web Linking\""; - license = stdenv.lib.licenses.publicDomain; + homepage = "https://github.com/myfreeweb/http-link-header#readme"; + description = "A parser and writer for the HTTP Link header per RFC 5988"; + license = lib.licenses.publicDomain; }) {}; "http-media" = callPackage ({ mkDerivation, base, bytestring, case-insensitive, containers - , stdenv, utf8-string + , lib, utf8-string }: mkDerivation { pname = "http-media"; - version = "0.7.1.3"; - sha256 = "394ffcfb4f655721d5965870bf9861c324c14d40ed4dc173e926235fe0fe124f"; + version = "0.8.0.0"; + sha256 = "398279d1dff5b60cd8b8c650caceca248ea1184d694bedf5df5426963b2b9c53"; + revision = "5"; + editedCabalFile = "0wf39pdag8a81ksk5xrgjzzzhav62vw2s77p43y7n3zkz5vynw7n"; libraryHaskellDepends = [ base bytestring case-insensitive containers utf8-string ]; @@ -17415,12 +20431,29 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/zmthy/http-media"; description = "Processing HTTP Content-Type and Accept headers"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "http-query" = callPackage + ({ mkDerivation, aeson, base, bytestring, http-conduit, lib + , network-uri, text + }: + mkDerivation { + pname = "http-query"; + version = "0.1.0.1"; + sha256 = "bc73c93d988f99787587691c49118e6dc34ed8d083969b55aea0cdae565f8386"; + libraryHaskellDepends = [ + aeson base bytestring http-conduit network-uri text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/juhp/http-query"; + description = "Simple http queries"; + license = lib.licenses.bsd3; }) {}; "http-reverse-proxy" = callPackage ({ mkDerivation, base, blaze-builder, bytestring, case-insensitive - , conduit, conduit-extra, containers, http-client, http-types - , network, resourcet, stdenv, streaming-commons, text, transformers + , conduit, conduit-extra, containers, http-client, http-types, lib + , network, resourcet, streaming-commons, text, transformers , unliftio, wai, wai-logger, word8 }: mkDerivation { @@ -17436,19 +20469,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/fpco/http-reverse-proxy"; description = "Reverse proxy HTTP requests, either over raw sockets or with WAI"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "http-streams" = callPackage ({ mkDerivation, aeson, attoparsec, base, base64-bytestring - , blaze-builder, bytestring, Cabal, case-insensitive, directory - , HsOpenSSL, http-common, io-streams, mtl, network, network-uri - , openssl-streams, stdenv, text, transformers, unordered-containers + , blaze-builder, bytestring, case-insensitive, directory, HsOpenSSL + , http-common, io-streams, lib, mtl, network, network-uri + , openssl-streams, text, transformers, unordered-containers }: mkDerivation { pname = "http-streams"; - version = "0.8.6.1"; - sha256 = "b8d71f2753ac7cda35b4f03ec64e4b3c7cc4ec5c2435b5e5237fe863cb687da3"; - setupHaskellDepends = [ base Cabal ]; + version = "0.8.8.1"; + sha256 = "70e5ff1f78f9051196847db1e46cda92cb06b046b84e2ef397579c0885be074a"; libraryHaskellDepends = [ aeson attoparsec base base64-bytestring blaze-builder bytestring case-insensitive directory HsOpenSSL http-common io-streams mtl @@ -17457,18 +20489,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/afcowie/http-streams/"; + homepage = "https://github.com/aesiniath/http-streams/"; description = "An HTTP client using io-streams"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "http-types" = callPackage - ({ mkDerivation, array, base, bytestring, case-insensitive, stdenv + ({ mkDerivation, array, base, bytestring, case-insensitive, lib , text }: mkDerivation { pname = "http-types"; - version = "0.12.2"; - sha256 = "523102d7ba8923e1b399cfd2a1c821e858146ecd934fc147c3acd0fd2b2f9305"; + version = "0.12.3"; + sha256 = "4e8a4a66477459fa436a331c75e46857ec8026283df984d54f90576cd3024016"; libraryHaskellDepends = [ array base bytestring case-insensitive text ]; @@ -17476,72 +20508,71 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/aristidb/http-types"; description = "Generic HTTP types for Haskell (for both client and server code)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "http2" = callPackage ({ mkDerivation, array, base, bytestring, case-insensitive - , containers, network-byte-order, psqueues, stdenv, stm + , containers, http-types, lib, network, network-byte-order + , psqueues, stm, time-manager, unix-time }: mkDerivation { pname = "http2"; - version = "1.6.4"; - sha256 = "2fcadd614cb8fa031e23a0fae096be76b08af7bbd525dc67096bd575cc3f1e66"; + version = "3.0.2"; + sha256 = "a181092a3ac68c9719200bb117f3ca03b52d2f2bb695e7ef63b6c6f6caf8828d"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - array base bytestring case-insensitive containers - network-byte-order psqueues stm + array base bytestring case-insensitive containers http-types + network network-byte-order psqueues stm time-manager unix-time ]; doHaddock = false; doCheck = false; homepage = "https://github.com/kazu-yamamoto/http2"; - description = "HTTP/2 library including frames, priority queues and HPACK"; - license = stdenv.lib.licenses.bsd3; + description = "HTTP/2 library"; + license = lib.licenses.bsd3; }) {}; "httpd-shed" = callPackage - ({ mkDerivation, base, network, network-uri, stdenv }: + ({ mkDerivation, base, lib, network, network-bsd, network-uri }: mkDerivation { pname = "httpd-shed"; - version = "0.4.0.3"; - sha256 = "b0ff87d81e61f788d3920d952e4469d984742ba49c006df086c159886bf09218"; - revision = "2"; - editedCabalFile = "12y9qf8s0aq4dc80wrvh14cjvvm4mcygrqq72w4z8w9n8mp8jg9p"; + version = "0.4.1.1"; + sha256 = "590fcfcb401923652bfcaf8c9a81b3bbbe83a4b1d16f7ccfecf7e47f6b6cafa5"; isLibrary = true; isExecutable = true; - libraryHaskellDepends = [ base network network-uri ]; + libraryHaskellDepends = [ base network network-bsd network-uri ]; doHaddock = false; doCheck = false; description = "A simple web-server with an interact style API"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "human-readable-duration" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "human-readable-duration"; - version = "0.2.1.2"; - sha256 = "6552def225a0bde18dd4d416e02dc9a83472924550834529a349dd9286785690"; + version = "0.2.1.4"; + sha256 = "cc688783dd3b761bba580cc01ddd41f75d436a21af7dd10e1268c2b0d43adc1b"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://gitlab.esy.fun/yogsototh/human-readable-duration#readme"; description = "Provide duration helper"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hunit-dejafu" = callPackage - ({ mkDerivation, base, dejafu, exceptions, HUnit, stdenv }: + ({ mkDerivation, base, dejafu, exceptions, HUnit, lib }: mkDerivation { pname = "hunit-dejafu"; - version = "1.2.0.6"; - sha256 = "54aac2479fec2ecefeb7ff42e659d2d0d1fba125a339eb3df33ed2fb266ff683"; + version = "2.0.0.4"; + sha256 = "048046de2a332d6e9434bf300207b862eee1e13c2ef0c1ced3ac86c1e912a585"; libraryHaskellDepends = [ base dejafu exceptions HUnit ]; doHaddock = false; doCheck = false; homepage = "https://github.com/barrucadu/dejafu"; description = "Deja Fu support for the HUnit test framework"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hvect" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "hvect"; version = "0.4.0.0"; @@ -17551,64 +20582,82 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/agrafix/hvect"; description = "Simple strict heterogeneous lists"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hvega" = callPackage - ({ mkDerivation, aeson, base, stdenv, text, vector }: + ({ mkDerivation, aeson, base, lib, text, unordered-containers }: mkDerivation { pname = "hvega"; - version = "0.1.0.3"; - sha256 = "0a7759965ad969e2b541f4ea39dc7f9d53442e39a61893edf7446bc3eb8f0542"; - libraryHaskellDepends = [ aeson base text vector ]; + version = "0.11.0.1"; + sha256 = "dd8cb2bf65812d84d0e8025d505440a2a0b6b3603938ea27d9bc56eacf30828f"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ aeson base text unordered-containers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/DougBurke/hvega"; - description = "Create Vega and Vega-Lite visualizations"; - license = stdenv.lib.licenses.bsd3; + description = "Create Vega-Lite visualizations (version 4) in Haskell"; + license = lib.licenses.bsd3; }) {}; "hw-balancedparens" = callPackage - ({ mkDerivation, base, hw-bits, hw-excess, hw-prim - , hw-rankselect-base, stdenv, vector + ({ mkDerivation, base, bytestring, deepseq, directory, generic-lens + , hedgehog, hspec, hw-bits, hw-excess, hw-fingertree, hw-int + , hw-prim, hw-rankselect-base, lens, lib, mmap + , optparse-applicative, vector }: mkDerivation { pname = "hw-balancedparens"; - version = "0.2.0.2"; - sha256 = "1622757f59d5fc789fc27c2311ba5147cd9491ad80d4e517755cb158ae87575d"; + version = "0.4.1.1"; + sha256 = "ffbc0b25bab9a8f50179acc868809d7fa4e50795f467459fe9962b55a433639b"; + revision = "3"; + editedCabalFile = "1myzy3wjwjaqlm31pa90msr8rl26vczd5yqd29mx0gy7p4x2dmgi"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - base hw-bits hw-excess hw-prim hw-rankselect-base vector + base deepseq directory hedgehog hspec hw-bits hw-excess + hw-fingertree hw-int hw-prim hw-rankselect-base vector + ]; + executableHaskellDepends = [ + base bytestring generic-lens hw-bits hw-prim lens mmap + optparse-applicative vector ]; doHaddock = false; doCheck = false; homepage = "http://github.com/haskell-works/hw-balancedparens#readme"; description = "Balanced parentheses"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hw-bits" = callPackage - ({ mkDerivation, base, bytestring, hw-int, hw-prim, hw-string-parse - , safe, stdenv, vector + ({ mkDerivation, base, bitvec, bytestring, deepseq, hw-int, hw-prim + , hw-string-parse, lib, vector }: mkDerivation { pname = "hw-bits"; - version = "0.7.0.5"; - sha256 = "1a4561307e8df6a6334db962fd772bf5bcc7d545727a9e2133e6d7aaffc46bdc"; + version = "0.7.2.1"; + sha256 = "b818acd47d4896d5da1aea39f98b80b1acbc52c660ee2dd87a7fb6063dc889a2"; + revision = "2"; + editedCabalFile = "1almm4nl56gf99wys1kzalqcz0dkaih0pgxsyqv4q1j1w3ggfmfq"; libraryHaskellDepends = [ - base bytestring hw-int hw-prim hw-string-parse safe vector + base bitvec bytestring deepseq hw-int hw-prim hw-string-parse + vector ]; doHaddock = false; doCheck = false; homepage = "http://github.com/haskell-works/hw-bits#readme"; description = "Bit manipulation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hw-conduit" = callPackage ({ mkDerivation, array, base, bytestring, conduit - , conduit-combinators, stdenv, time, transformers, unliftio-core + , conduit-combinators, lib, time, transformers, unliftio-core , word8 }: mkDerivation { pname = "hw-conduit"; - version = "0.2.0.5"; - sha256 = "047d5abec487bf522050d2a7f318ce9f0e67766a58cf67669d2d6fa7ae8dd701"; + version = "0.2.1.0"; + sha256 = "02c6ec93a9c749f2fc7bb60b5c9cd3b77902b198024a69823b31fac7f09dd3f6"; + revision = "1"; + editedCabalFile = "1rmdwb4a7ax9yadj4xv63n582vsmk84h03qkr6npj9b9gw4qw6i3"; libraryHaskellDepends = [ array base bytestring conduit conduit-combinators time transformers unliftio-core word8 @@ -17617,61 +20666,105 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/haskell-works/hw-conduit#readme"; description = "Conduits for tokenizing streams"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hw-conduit-merges" = callPackage - ({ mkDerivation, base, conduit, conduit-extra, mtl, stdenv }: + ({ mkDerivation, base, conduit, conduit-extra, lib, mtl }: mkDerivation { pname = "hw-conduit-merges"; - version = "0.2.0.0"; - sha256 = "9bcea270cc01a117c892315fff0dd46de3e58466e9ef82f7571eedad9b58028c"; - revision = "1"; - editedCabalFile = "1azji7zc0ygqjgd2shbqw7p8a2ll2qp3b1yq5i3665448brlwpvc"; + version = "0.2.1.0"; + sha256 = "a03e37517f8a6c1d277762eb68e8f148dceebfec26e7b810465a5e7c340b5110"; libraryHaskellDepends = [ base conduit conduit-extra mtl ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-works/hw-conduit-merges#readme"; description = "Additional merges and joins for Conduit"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hw-diagnostics" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "hw-diagnostics"; - version = "0.0.0.5"; - sha256 = "5ceaec01c446c5a507e889f514201e4739ea6f1cc22a4c68894bb023257bd931"; + version = "0.0.1.0"; + sha256 = "722b10f7afeaf62c654779244393e2beb7f1960961f9b54d8cf2c15518292f84"; + revision = "1"; + editedCabalFile = "04qpkr54wkb99hdfzk6gxhi6ak5lc564jzab1cc7675s7lsj1nji"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "http://github.com/haskell-works/hw-diagnostics#readme"; description = "Diagnostics library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "hw-dsv" = callPackage + ({ mkDerivation, appar, base, bits-extra, bytestring, deepseq + , generic-lens, ghc-prim, hedgehog, hw-bits, hw-ip, hw-prim + , hw-rankselect, hw-rankselect-base, hw-simd, lens, lib + , optparse-applicative, resourcet, text, transformers, vector + }: + mkDerivation { + pname = "hw-dsv"; + version = "0.4.1.0"; + sha256 = "488f2c4f61c4f68b83a6b18e3d608927ec54f4940ebb7727c16b3061ccf360f3"; + revision = "5"; + editedCabalFile = "0dzysj8fzyfg4ggda5ramq1zad8jb810rg2nncnzv95xmnlwakgl"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base bits-extra bytestring deepseq ghc-prim hw-bits hw-prim + hw-rankselect hw-rankselect-base hw-simd transformers vector + ]; + executableHaskellDepends = [ + appar base bits-extra bytestring deepseq generic-lens ghc-prim + hedgehog hw-bits hw-ip hw-prim hw-rankselect hw-rankselect-base + hw-simd lens optparse-applicative resourcet text transformers + vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell-works/hw-dsv#readme"; + description = "Unbelievably fast streaming DSV file parser"; + license = lib.licenses.bsd3; }) {}; "hw-eliasfano" = callPackage - ({ mkDerivation, base, hw-bits, hw-int, hw-packed-vector, hw-prim - , safe, stdenv, vector + ({ mkDerivation, base, binary, bytestring, deepseq, generic-lens + , hw-bits, hw-int, hw-packed-vector, hw-prim, hw-rankselect + , hw-rankselect-base, lens, lib, optparse-applicative, resourcet + , temporary-resourcet, vector }: mkDerivation { pname = "hw-eliasfano"; - version = "0.1.0.1"; - sha256 = "14710bcbfe4e44bfe683fa0db73d9546268c24101770968c13083defca2048e6"; + version = "0.1.2.0"; + sha256 = "d2be1f2ab6caa25201f350a40be2e187b744e25bcc65f8394274995fedff17f3"; + revision = "5"; + editedCabalFile = "0w8kikrrkv8v1drnrjfabzflbgs768qbrfv8n17y4id76aqazml5"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - base hw-bits hw-int hw-packed-vector hw-prim safe vector + base deepseq hw-bits hw-int hw-packed-vector hw-prim hw-rankselect + hw-rankselect-base temporary-resourcet vector + ]; + executableHaskellDepends = [ + base binary bytestring generic-lens hw-bits hw-packed-vector + hw-prim hw-rankselect hw-rankselect-base lens optparse-applicative + resourcet temporary-resourcet vector ]; doHaddock = false; doCheck = false; homepage = "http://github.com/haskell-works/hw-eliasfano#readme"; description = "Elias-Fano"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hw-excess" = callPackage - ({ mkDerivation, base, hw-bits, hw-prim, hw-rankselect-base, safe - , stdenv, vector + ({ mkDerivation, base, hw-bits, hw-prim, hw-rankselect-base, lib + , safe, vector }: mkDerivation { pname = "hw-excess"; - version = "0.2.0.2"; - sha256 = "6735d0cd4ee86d5c13d5ea067251c6b1126f7569d78c6241f3147eb114b7a1f6"; + version = "0.2.3.0"; + sha256 = "6fe802aead2589c47fa4a9129e4d5b9a61804d673e691ae79bc499e7fb703e76"; + revision = "1"; + editedCabalFile = "0qq8svkn9365vdbb0y3y4m2pdklsrf6z3a1m0kyfmbr0vphza369"; libraryHaskellDepends = [ base hw-bits hw-prim hw-rankselect-base safe vector ]; @@ -17679,143 +20772,249 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/haskell-works/hw-excess#readme"; description = "Excess"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "hw-fingertree" = callPackage + ({ mkDerivation, base, deepseq, hw-prim, lib }: + mkDerivation { + pname = "hw-fingertree"; + version = "0.1.2.0"; + sha256 = "11c076891194369cbc5b67b0430f2fdd8ceafa7b7863e1fc552e26a58a732a2c"; + revision = "1"; + editedCabalFile = "0hg9hnga0d15a5md67q7xl53kgp34hwvl4aw9s8xkjm4fs7a54z9"; + libraryHaskellDepends = [ base deepseq hw-prim ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell-works/hw-fingertree#readme"; + description = "Generic finger-tree structure, with example instances"; + license = lib.licenses.bsd3; }) {}; "hw-fingertree-strict" = callPackage - ({ mkDerivation, base, deepseq, stdenv }: + ({ mkDerivation, base, deepseq, lib }: mkDerivation { pname = "hw-fingertree-strict"; - version = "0.1.1.1"; - sha256 = "1127b7cff38319a292ca6d57c8b7a1996bb80b90e86488a0f82a76eba9f91268"; + version = "0.1.2.0"; + sha256 = "8a7dfb25bebef0541eee125ccdbed2ce6f89b56148fb54c0b1714154493210fe"; + revision = "1"; + editedCabalFile = "0vr8xqvwihg3j83bqfhcqlnlpdq7k2v6kkx1xly7fdjw2hcwgkhl"; libraryHaskellDepends = [ base deepseq ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-works/hw-fingertree-strict#readme"; description = "Generic strict finger-tree structure"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "hw-hedgehog" = callPackage + ({ mkDerivation, base, hedgehog, lib, vector }: + mkDerivation { + pname = "hw-hedgehog"; + version = "0.1.1.0"; + sha256 = "e9ff0a96e11e02bd39954988bf532c7349fe295b8a2313d56c73a004058b5728"; + revision = "1"; + editedCabalFile = "1fwgxwbfz6yfj6xfl9471q7fpsckm2wvpb8wxwb32c3x5122ly5v"; + libraryHaskellDepends = [ base hedgehog vector ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell-works/hw-hedgehog#readme"; + description = "Extra hedgehog functionality"; + license = lib.licenses.bsd3; }) {}; "hw-hspec-hedgehog" = callPackage - ({ mkDerivation, base, call-stack, hedgehog, hspec, HUnit, stdenv + ({ mkDerivation, base, call-stack, hedgehog, hspec, HUnit, lib + , transformers }: mkDerivation { pname = "hw-hspec-hedgehog"; - version = "0.1.0.4"; - sha256 = "58bd37f98e59d10cd27cf90fc04e6fdb459f3caff1f47b0e51e746aaa6ce99ee"; + version = "0.1.1.0"; + sha256 = "d6cfd42f59482b153b276b2bc897320c6b633be87e0eea78649e184316042313"; revision = "2"; - editedCabalFile = "1jh0p4i87c2bn926s0d7qx6ykssjj26fia0d24grlklkd14bnmpq"; - libraryHaskellDepends = [ base call-stack hedgehog hspec HUnit ]; + editedCabalFile = "16v3dcpm51m8g2va85jfnbxqyc6dds2nazyd31080fa4804a90wz"; + libraryHaskellDepends = [ + base call-stack hedgehog hspec HUnit transformers + ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-works/hw-hspec-hedgehog#readme"; description = "Interoperability between hspec and hedgehog"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hw-int" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "hw-int"; - version = "0.0.0.3"; - sha256 = "8336a5111638d3298266c9a1458233a09798bfa6d558219d4fe3bdd35d8d4a3f"; + version = "0.0.2.0"; + sha256 = "c00c3dc0b3e18318213c03310a63163fd6da8685452b5ee18a118ab090502e8e"; + revision = "1"; + editedCabalFile = "13vc1hvyil8qql2d6ryi2m4a6snhm2v8vghh8s9hr4qx6dzh4irv"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "http://github.com/haskell-works/hw-int#readme"; - description = "Integers"; - license = stdenv.lib.licenses.bsd3; + description = "Additional facilities for Integers"; + license = lib.licenses.bsd3; }) {}; "hw-ip" = callPackage - ({ mkDerivation, appar, base, containers, generic-lens, hw-bits - , iproute, stdenv, text + ({ mkDerivation, appar, base, binary, bytestring, containers + , generic-lens, hedgehog, hw-bits, iproute, lens, lib + , optparse-applicative, text }: mkDerivation { pname = "hw-ip"; - version = "2.0.1.0"; - sha256 = "196b99e9f439ca361fec7bb5ced42202ee6a8a8143dcdbc24afdb408129a2ce4"; + version = "2.4.2.0"; + sha256 = "dd6db176e0b505180027eaa85ca17c8c5a3f5f1666dac8911fd9b9f0a62370af"; + revision = "4"; + editedCabalFile = "0pjry2xjnhfl3jii8j9dqmqz88hw7g8wkwy4fqnajnchrxb8f06w"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - appar base containers generic-lens hw-bits iproute text + appar base containers generic-lens hedgehog hw-bits iproute text + ]; + executableHaskellDepends = [ + appar base binary bytestring generic-lens lens optparse-applicative + text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-works/hw-ip#readme"; description = "Library for manipulating IP addresses and CIDR blocks"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "hw-json" = callPackage - ({ mkDerivation, ansi-wl-pprint, array, attoparsec, base - , bytestring, containers, criterion, dlist, hw-balancedparens - , hw-bits, hw-mquery, hw-parser, hw-prim, hw-rankselect - , hw-rankselect-base, lens, mmap, optparse-applicative, stdenv - , text, vector, word8 + "hw-json-simd" = callPackage + ({ mkDerivation, base, bytestring, c2hs, hw-prim, lens, lib + , optparse-applicative, vector }: mkDerivation { - pname = "hw-json"; - version = "0.9.0.1"; - sha256 = "1cbffc0840050d3d021d337481887c56e1db6ef7f005bc457a02ac2c47dcf902"; + pname = "hw-json-simd"; + version = "0.1.1.0"; + sha256 = "36a97b93dfe610fffbc02a73e57ac4f62f306a6350b9853ccaec9eb644f7ee2e"; + revision = "3"; + editedCabalFile = "0f7y8kaj2bv3l1fscwxdnqj7378mrls1mcnsm23cpb5dizy3p2nf"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base bytestring hw-prim lens vector ]; + libraryToolDepends = [ c2hs ]; + executableHaskellDepends = [ + base bytestring hw-prim lens optparse-applicative vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell-works/hw-json-simd#readme"; + description = "SIMD-based JSON semi-indexer"; + license = lib.licenses.bsd3; + }) {}; + "hw-json-simple-cursor" = callPackage + ({ mkDerivation, base, bytestring, generic-lens, hw-balancedparens + , hw-bits, hw-json-simd, hw-prim, hw-rankselect, hw-rankselect-base + , lens, lib, mmap, optparse-applicative, text, vector, word8 + }: + mkDerivation { + pname = "hw-json-simple-cursor"; + version = "0.1.1.0"; + sha256 = "749530c82e9a72e8fd31ee7cd5a4a7e53853658f39b18c942e7c56a134b69dcf"; + revision = "6"; + editedCabalFile = "1ws3mcyvba05s0wvwzbig54wxkw37pp55c5jwbsc96inic8cfq3y"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - ansi-wl-pprint array attoparsec base bytestring containers dlist - hw-balancedparens hw-bits hw-mquery hw-parser hw-prim hw-rankselect - hw-rankselect-base mmap text vector word8 + base bytestring hw-balancedparens hw-bits hw-prim hw-rankselect + hw-rankselect-base vector word8 ]; executableHaskellDepends = [ - base bytestring criterion dlist hw-balancedparens hw-bits hw-mquery - hw-prim hw-rankselect hw-rankselect-base lens mmap - optparse-applicative vector + base bytestring generic-lens hw-balancedparens hw-json-simd hw-prim + hw-rankselect hw-rankselect-base lens mmap optparse-applicative + text vector ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/haskell-works/hw-json#readme"; + homepage = "http://github.com/haskell-works/hw-json-simple-cursor#readme"; description = "Memory efficient JSON parser"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "hw-mquery" = callPackage - ({ mkDerivation, ansi-wl-pprint, base, dlist, lens, semigroups - , stdenv + "hw-json-standard-cursor" = callPackage + ({ mkDerivation, array, base, bits-extra, bytestring, generic-lens + , hw-balancedparens, hw-bits, hw-json-simd, hw-prim, hw-rankselect + , hw-rankselect-base, lens, lib, mmap, optparse-applicative, text + , vector, word8 }: mkDerivation { - pname = "hw-mquery"; - version = "0.1.0.3"; - sha256 = "458f5730abc50c60d35f43cd00ee7bfee74963ead58596019ad30a17e8060244"; + pname = "hw-json-standard-cursor"; + version = "0.2.3.1"; + sha256 = "396eb290944d802786a3b357abd1ca61f15547da2c0385c6c65fa865eed5fad6"; + revision = "4"; + editedCabalFile = "18x3vinc6j5nnq3j5x7zdcy3ys6b2clmb7lhz6qg1wklnfcyjxsb"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - ansi-wl-pprint base dlist lens semigroups + array base bits-extra bytestring hw-balancedparens hw-bits + hw-json-simd hw-prim hw-rankselect hw-rankselect-base mmap vector + word8 ]; executableHaskellDepends = [ - ansi-wl-pprint base dlist lens semigroups + base bytestring generic-lens hw-balancedparens hw-json-simd hw-prim + hw-rankselect hw-rankselect-base lens mmap optparse-applicative + text vector ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/haskell-works/hw-mquery#readme"; - description = "Monadic query DSL"; - license = stdenv.lib.licenses.bsd3; + homepage = "http://github.com/haskell-works/hw-json-standard-cursor#readme"; + description = "Memory efficient JSON parser"; + license = lib.licenses.bsd3; }) {}; + "hw-kafka-client" = callPackage + ({ mkDerivation, base, bifunctors, bytestring, c2hs, containers + , lib, rdkafka, text, transformers, unix + }: + mkDerivation { + pname = "hw-kafka-client"; + version = "4.0.3"; + sha256 = "af158668540a008e93fa159f88c747b7fbc085e0d5e7c4c1dd87d50463917ce8"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base bifunctors bytestring containers text transformers unix + ]; + librarySystemDepends = [ rdkafka ]; + libraryToolDepends = [ c2hs ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell-works/hw-kafka-client"; + description = "Kafka bindings for Haskell"; + license = lib.licenses.mit; + }) {inherit (pkgs) rdkafka;}; "hw-packed-vector" = callPackage - ({ mkDerivation, base, bytestring, hw-bits, hw-int, hw-prim - , hw-string-parse, safe, stdenv, vector + ({ mkDerivation, base, binary, bytestring, deepseq, generic-lens + , hw-bits, hw-prim, lens, lib, optparse-applicative, vector }: mkDerivation { pname = "hw-packed-vector"; - version = "0.0.0.1"; - sha256 = "b6980a80cb23cd6e889a4bb6302f684a158c9d81d7b80873812ea6b3c6014931"; + version = "0.2.1.0"; + sha256 = "68e0a420fccb577ad003ed14dc6b3e6f573e22914fcf688a247d9afebdf0148e"; + revision = "5"; + editedCabalFile = "0pnrjx4sbbxpr1fvib5z95cxjgfif2iay1j6hk5ysavwn6i2qxqx"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - base bytestring hw-bits hw-int hw-prim hw-string-parse safe vector + base bytestring deepseq hw-bits hw-prim vector + ]; + executableHaskellDepends = [ + base binary bytestring generic-lens hw-bits hw-prim lens + optparse-applicative vector ]; doHaddock = false; doCheck = false; homepage = "http://github.com/haskell-works/hw-packed-vector#readme"; description = "Packed Vector"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hw-parser" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, hw-prim, stdenv - , text + ({ mkDerivation, attoparsec, base, bytestring, hw-prim, lib, text }: mkDerivation { pname = "hw-parser"; - version = "0.1.0.0"; - sha256 = "5de02aca124597dc7f51a5ab72c175a327a8dcd9efda8eef3ffb47076a0a9391"; + version = "0.1.1.0"; + sha256 = "aabfe2fcf9126df7b08cfc6d6cd79ba1ef65156631631210b16ef05ac4e14bff"; + revision = "2"; + editedCabalFile = "15r5ydza7dawa5b7y3xi80016pa3s5sb706hvsqvn82fhqp5dziw"; libraryHaskellDepends = [ attoparsec base bytestring hw-prim text ]; @@ -17823,87 +21022,120 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/haskell-works/hw-parser#readme"; description = "Simple parser support"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hw-prim" = callPackage - ({ mkDerivation, base, bytestring, mmap, semigroups, stdenv - , transformers, vector + ({ mkDerivation, base, bytestring, deepseq, ghc-prim, lib, mmap + , transformers, unliftio-core, vector }: mkDerivation { pname = "hw-prim"; - version = "0.6.2.22"; - sha256 = "114cc374cf048f99f46c524d76f3ecd5f7d1774b47098cee79274eeabf54ae99"; + version = "0.6.3.0"; + sha256 = "67774312191bb0b0f5ed1d20cbee241fafc5e605d0435e6c28a9a738813e163f"; + revision = "2"; + editedCabalFile = "14x1bijg1d8jdh963rxrlwzlqa1p1vh0bc7hjdysk8dzbrc7fbmv"; libraryHaskellDepends = [ - base bytestring mmap semigroups transformers vector + base bytestring deepseq ghc-prim mmap transformers unliftio-core + vector ]; doHaddock = false; doCheck = false; homepage = "http://github.com/haskell-works/hw-prim#readme"; description = "Primitive functions and data types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hw-rankselect" = callPackage - ({ mkDerivation, base, deepseq, directory, hw-balancedparens - , hw-bits, hw-prim, hw-rankselect-base, lens, mmap, mtl - , optparse-applicative, stdenv, vector + ({ mkDerivation, base, deepseq, directory, generic-lens, hedgehog + , hspec, hw-balancedparens, hw-bits, hw-fingertree, hw-prim + , hw-rankselect-base, lens, lib, mmap, mtl, optparse-applicative + , vector }: mkDerivation { pname = "hw-rankselect"; - version = "0.12.0.4"; - sha256 = "70e278abdec4c9baf9e208f1740242bf0ca5fbdb4b4c782ea189c68db5bb4750"; + version = "0.13.4.0"; + sha256 = "e732bffc6d828279229cf4d84d4cc57b3dd8efc183023e48eab794b5891d1332"; + revision = "5"; + editedCabalFile = "1jbfanh0028sxj0arx92w753dwgpazs8j2flqjq9svc91rpk82px"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - base deepseq hw-balancedparens hw-bits hw-prim hw-rankselect-base - vector + base deepseq hedgehog hspec hw-balancedparens hw-bits hw-fingertree + hw-prim hw-rankselect-base vector ]; executableHaskellDepends = [ - base directory hw-bits hw-prim hw-rankselect-base lens mmap mtl - optparse-applicative vector + base directory generic-lens hw-bits hw-prim hw-rankselect-base lens + mmap mtl optparse-applicative vector ]; doHaddock = false; doCheck = false; homepage = "http://github.com/haskell-works/hw-rankselect#readme"; description = "Rank-select"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hw-rankselect-base" = callPackage - ({ mkDerivation, base, bits-extra, hw-bits, hw-int, hw-prim - , hw-string-parse, safe, stdenv, vector + ({ mkDerivation, base, bits-extra, bitvec, hw-bits, hw-int, hw-prim + , hw-string-parse, lib, vector }: mkDerivation { pname = "hw-rankselect-base"; - version = "0.3.2.1"; - sha256 = "d20a6cab42189cf71a85b355d0ed52167bc2991210c3af76139a2e6229f79360"; + version = "0.3.4.1"; + sha256 = "300d8222c3fb26d503ef8554489da77f1d0622eed6414d8d62b2ca0c30c714e8"; + revision = "2"; + editedCabalFile = "174a3qhkdam5m5rqwb9qzapg2xkd8vb0lirkz2d0xb4xxc0vzcy7"; libraryHaskellDepends = [ - base bits-extra hw-bits hw-int hw-prim hw-string-parse safe vector + base bits-extra bitvec hw-bits hw-int hw-prim hw-string-parse + vector ]; doHaddock = false; doCheck = false; homepage = "http://github.com/haskell-works/hw-rankselect-base#readme"; description = "Rank-select base"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "hw-simd" = callPackage + ({ mkDerivation, base, bits-extra, bytestring, c2hs, deepseq + , hw-bits, hw-prim, hw-rankselect, hw-rankselect-base, lib + , transformers, vector + }: + mkDerivation { + pname = "hw-simd"; + version = "0.1.2.0"; + sha256 = "8e885d52e976be2e24e92b4a64eb09be3939598fc6a62615da61e58b7f1740e4"; + revision = "2"; + editedCabalFile = "05rax91afykkmwnxnyi6bmmjh0n9ryw006k9k3klwnvy8h2yaf4m"; + libraryHaskellDepends = [ + base bits-extra bytestring deepseq hw-bits hw-prim hw-rankselect + hw-rankselect-base transformers vector + ]; + libraryToolDepends = [ c2hs ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell-works/hw-simd#readme"; + description = "SIMD library"; + license = lib.licenses.bsd3; }) {}; "hw-streams" = callPackage - ({ mkDerivation, base, bytestring, ghc-prim, hw-bits, hw-prim, mmap - , primitive, semigroups, stdenv, transformers, vector + ({ mkDerivation, base, bytestring, ghc-prim, hw-bits, hw-prim, lib + , mmap, primitive, transformers, vector }: mkDerivation { pname = "hw-streams"; - version = "0.0.0.10"; - sha256 = "bcf7bbf4d28913fc59b2412e39e498cba195ae417204e1570d6b84e6df96f021"; + version = "0.0.1.0"; + sha256 = "a55a5834fe7ff7b6e6278f4f1bd6babb0e3deca753fbca3ef028410364e8f743"; + revision = "1"; + editedCabalFile = "0fib78604y6cjchah7zhjsfli820ks51qq7yjv81wwbckjjkpw5v"; libraryHaskellDepends = [ - base bytestring ghc-prim hw-bits hw-prim mmap primitive semigroups + base bytestring ghc-prim hw-bits hw-prim mmap primitive transformers vector ]; doHaddock = false; doCheck = false; homepage = "http://github.com/haskell-works/hw-streams#readme"; description = "Primitive functions and data types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hw-string-parse" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "hw-string-parse"; version = "0.0.0.4"; @@ -17913,12 +21145,12 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/haskell-works/hw-string-parse#readme"; description = "String parser"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hw-succinct" = callPackage ({ mkDerivation, attoparsec, base, bytestring, conduit, containers , hw-balancedparens, hw-bits, hw-prim, hw-rankselect - , hw-rankselect-base, mmap, mono-traversable, stdenv, text, vector + , hw-rankselect-base, lib, mmap, mono-traversable, text, vector , word8 }: mkDerivation { @@ -17934,11 +21166,44 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/haskell-works/hw-succinct#readme"; description = "Succint datastructures"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "hw-xml" = callPackage + ({ mkDerivation, ansi-wl-pprint, array, attoparsec, base + , bytestring, cereal, containers, deepseq, generic-lens, ghc-prim + , hw-balancedparens, hw-bits, hw-parser, hw-prim, hw-rankselect + , hw-rankselect-base, lens, lib, mmap, mtl, optparse-applicative + , resourcet, text, transformers, vector, word8 + }: + mkDerivation { + pname = "hw-xml"; + version = "0.5.1.0"; + sha256 = "84d76b219c16dc787a73f4c091bf933601820e84ffcdd379d9862d4aed9c013d"; + revision = "7"; + editedCabalFile = "1rikq6wxjg4h5pfg9miw14np7b1h2vf036gawyazq5c4d6l2wfzv"; + isLibrary = true; + isExecutable = true; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + ansi-wl-pprint array attoparsec base bytestring cereal containers + deepseq ghc-prim hw-balancedparens hw-bits hw-parser hw-prim + hw-rankselect hw-rankselect-base lens mmap mtl resourcet text + transformers vector word8 + ]; + executableHaskellDepends = [ + attoparsec base bytestring deepseq generic-lens hw-balancedparens + hw-bits hw-prim hw-rankselect lens mmap mtl optparse-applicative + resourcet text vector + ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/haskell-works/hw-xml#readme"; + description = "XML parser based on succinct data structures"; + license = lib.licenses.bsd3; }) {}; "hweblib" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, containers, mtl - , stdenv, text, transformers + ({ mkDerivation, attoparsec, base, bytestring, containers, lib, mtl + , text, transformers }: mkDerivation { pname = "hweblib"; @@ -17951,17 +21216,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/aycanirican/hweblib"; description = "Haskell Web Library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hxt" = callPackage ({ mkDerivation, base, binary, bytestring, containers, deepseq , directory, filepath, hxt-charproperties, hxt-regex-xmlschema - , hxt-unicode, mtl, network-uri, parsec, stdenv + , hxt-unicode, lib, mtl, network-uri, parsec }: mkDerivation { pname = "hxt"; - version = "9.3.1.16"; - sha256 = "0d55e35cc718891d0987b7c8e6c43499efa727c68bc92e88e8b99461dff403e3"; + version = "9.3.1.22"; + sha256 = "ef602fe674225527750574dd555dbdf402ab77d054af75d41ca21b42dbb23ad9"; configureFlags = [ "-fnetwork-uri" ]; libraryHaskellDepends = [ base binary bytestring containers deepseq directory filepath @@ -17972,23 +21237,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/UweSchmidt/hxt"; description = "A collection of tools for processing XML with Haskell"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hxt-charproperties" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "hxt-charproperties"; - version = "9.2.0.1"; - sha256 = "e46614d6bf0390b2a6a1aeeb0771e6d366944da40fb21c12c2f8a94d1f47b4d6"; + version = "9.5.0.0"; + sha256 = "28836949512a2aedb63b2a02e0b05a4f519dc3511cfd259804a6e9d59a44a94a"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/UweSchmidt/hxt"; description = "Character properties and classes for XML and Unicode"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hxt-css" = callPackage - ({ mkDerivation, base, hxt, parsec, split, stdenv }: + ({ mkDerivation, base, hxt, lib, parsec, split }: mkDerivation { pname = "hxt-css"; version = "0.1.0.3"; @@ -18000,10 +21265,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/redneb/hxt-css"; description = "CSS selectors for HXT"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hxt-curl" = callPackage - ({ mkDerivation, base, bytestring, curl, hxt, parsec, stdenv }: + ({ mkDerivation, base, bytestring, curl, hxt, lib, parsec }: mkDerivation { pname = "hxt-curl"; version = "9.1.1.1"; @@ -18014,10 +21279,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; homepage = "https://github.com/UweSchmidt/hxt"; description = "LibCurl interface for HXT"; license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; + hydraPlatforms = lib.platforms.none; }) {}; "hxt-expat" = callPackage - ({ mkDerivation, base, bytestring, hexpat, hxt, stdenv }: + ({ mkDerivation, base, bytestring, hexpat, hxt, lib }: mkDerivation { pname = "hxt-expat"; version = "9.1.1"; @@ -18028,11 +21293,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; homepage = "http://www.fh-wedel.de/~si/HXmlToolbox/index.html"; description = "Expat parser for HXT"; license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; + hydraPlatforms = lib.platforms.none; }) {}; "hxt-http" = callPackage - ({ mkDerivation, base, bytestring, HTTP, hxt, network, network-uri - , parsec, stdenv + ({ mkDerivation, base, bytestring, HTTP, hxt, lib, network + , network-uri, parsec }: mkDerivation { pname = "hxt-http"; @@ -18046,16 +21311,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/UweSchmidt/hxt"; description = "Interface to native Haskell HTTP package HTTP"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hxt-regex-xmlschema" = callPackage - ({ mkDerivation, base, bytestring, hxt-charproperties, parsec - , stdenv, text + ({ mkDerivation, base, bytestring, hxt-charproperties, lib, parsec + , text }: mkDerivation { pname = "hxt-regex-xmlschema"; - version = "9.2.0.3"; - sha256 = "f4743ba65498d6001cdfcf5cbc3317d4bc43941be5c7030b60beb83408c892b0"; + version = "9.2.0.7"; + sha256 = "b9b6bcfc7d8c5e9a0be87dc56b13a237a51ca2c19c6665a51378a9538b71d97a"; libraryHaskellDepends = [ base bytestring hxt-charproperties parsec text ]; @@ -18063,10 +21328,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Regular_expressions_for_XML_Schema"; description = "A regular expression library for W3C XML Schema regular expressions"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hxt-tagsoup" = callPackage - ({ mkDerivation, base, hxt, hxt-charproperties, hxt-unicode, stdenv + ({ mkDerivation, base, hxt, hxt-charproperties, hxt-unicode, lib , tagsoup }: mkDerivation { @@ -18081,10 +21346,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; homepage = "https://github.com/UweSchmidt/hxt"; description = "TagSoup parser for HXT"; license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; + hydraPlatforms = lib.platforms.none; }) {}; "hxt-unicode" = callPackage - ({ mkDerivation, base, hxt-charproperties, stdenv }: + ({ mkDerivation, base, hxt-charproperties, lib }: mkDerivation { pname = "hxt-unicode"; version = "9.0.2.4"; @@ -18094,16 +21359,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/UweSchmidt/hxt"; description = "Unicode en-/decoding functions for utf8, iso-latin-* and other encodings"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "hybrid-vectors" = callPackage - ({ mkDerivation, base, deepseq, primitive, semigroups, stdenv - , vector + ({ mkDerivation, base, deepseq, lib, primitive, semigroups, vector }: mkDerivation { pname = "hybrid-vectors"; version = "0.2.2"; sha256 = "41c6c371df64b9083354e66101ad8c92f87458474fed2a149e4632db644f86d7"; + revision = "1"; + editedCabalFile = "16wpgh7cxgmap5acyccbff02b2jvhqiad5m3fknribpbahvmkk88"; libraryHaskellDepends = [ base deepseq primitive semigroups vector ]; @@ -18111,75 +21377,63 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/hybrid-vectors"; description = "Hybrid vectors e.g. Mixed Boxed/Unboxed vectors"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "hyper" = callPackage + ({ mkDerivation, base, blaze-html, deepseq, lib, text }: + mkDerivation { + pname = "hyper"; + version = "0.2.1.1"; + sha256 = "222398df9d12d006c030a5e5a19df6d1e906aba98b46021345de96f34ec9e792"; + libraryHaskellDepends = [ base blaze-html deepseq text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/HeinrichApfelmus/hyper-haskell"; + description = "Display class for the HyperHaskell graphical Haskell interpreter"; + license = lib.licenses.bsd3; }) {}; "hyperloglog" = callPackage - ({ mkDerivation, approximate, base, binary, bits, bytes, Cabal - , cabal-doctest, cereal, cereal-vector, comonad, deepseq - , distributive, hashable, lens, reflection, safecopy, semigroupoids - , semigroups, siphash, stdenv, tagged, vector + ({ mkDerivation, approximate, base, binary, bits, bytes, cereal + , cereal-vector, comonad, deepseq, distributive, hashable, lens + , lib, reflection, semigroupoids, semigroups, siphash, tagged + , vector }: mkDerivation { pname = "hyperloglog"; - version = "0.4.2"; - sha256 = "f5b83cfcc2c9d1e40e04bbc9724428b2655c3b54b26beef714c98dabee5f1048"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "0.4.4"; + sha256 = "7bd0546afc9e4fdf6b1b04f0da25666d8b92cf2618fbaefe3a2d6e32d2ee9247"; libraryHaskellDepends = [ approximate base binary bits bytes cereal cereal-vector comonad - deepseq distributive hashable lens reflection safecopy - semigroupoids semigroups siphash tagged vector + deepseq distributive hashable lens reflection semigroupoids + semigroups siphash tagged vector ]; doHaddock = false; doCheck = false; homepage = "http://github.com/analytics/hyperloglog"; description = "An approximate streaming (constant space) unique object counter"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "hyphenation" = callPackage - ({ mkDerivation, base, bytestring, Cabal, cabal-doctest, containers - , stdenv, unordered-containers, zlib + ({ mkDerivation, base, bytestring, containers, file-embed, lib + , text, unordered-containers, zlib }: mkDerivation { pname = "hyphenation"; - version = "0.7.1"; - sha256 = "a25c5073f42896ccf81ff5936f3a42f290730f61da7f225b126ad22ff601b1c0"; - revision = "4"; - editedCabalFile = "0pp7qm40alsfd9z5dvp6l2c7dp9zp0skl9g0iib3jahxs3n8qcrr"; + version = "0.8.2"; + sha256 = "1e18152bcdc0a6bc8dc9f39c9085ad773b2b263f486a23b8d9e9b194da046314"; enableSeparateDataOutput = true; - setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ - base bytestring containers unordered-containers zlib + base bytestring containers file-embed text unordered-containers + zlib ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/hyphenation"; description = "Configurable Knuth-Liang hyphenation"; - license = stdenv.lib.licenses.bsd2; - }) {}; - "hyraxAbif" = callPackage - ({ mkDerivation, base, binary, bytestring, directory, filepath - , hscolour, pretty-show, protolude, stdenv, text - }: - mkDerivation { - pname = "hyraxAbif"; - version = "0.2.3.15"; - sha256 = "013a861a57bb71af8394ee68404d52411ae65d627e36d0c1903194331fa6d5f1"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - base binary bytestring directory filepath protolude text - ]; - executableHaskellDepends = [ - base bytestring hscolour pretty-show protolude text - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/hyraxbio/hyraxAbif/#readme"; - description = "Modules for parsing, generating and manipulating AB1 files"; - license = "(BSD-3-Clause OR Apache-2.0)"; + license = lib.licenses.bsd2; }) {}; "iconv" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "iconv"; version = "0.4.1.3"; @@ -18188,26 +21442,26 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "String encoding conversion"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "identicon" = callPackage - ({ mkDerivation, base, bytestring, JuicyPixels, stdenv }: + ({ mkDerivation, base, bytestring, JuicyPixels, lib }: mkDerivation { pname = "identicon"; version = "0.2.2"; sha256 = "3679b4fcc0a5bcc93b6ed2009f43e3ec87bf9549aee3eef182f7403d0c10f263"; - revision = "3"; - editedCabalFile = "0vya6zm3nnbdv3wmj3dwqwwjgsagql8q17078knhjddv2lm8m49q"; + revision = "4"; + editedCabalFile = "1mlmn7ccns2rnhgmnlq9m2rqc9mgj0262ckqbm01w1fiycw3nq7b"; enableSeparateDataOutput = true; libraryHaskellDepends = [ base bytestring JuicyPixels ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mrkkrp/identicon"; description = "Flexible generation of identicons"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "ieee754" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "ieee754"; version = "0.8.0"; @@ -18217,10 +21471,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/patperry/hs-ieee754"; description = "Utilities for dealing with IEEE floating point numbers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "if" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "if"; version = "0.1.0.0"; @@ -18230,10 +21484,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/winterland1989/if"; description = "(?) and (?>) conditional operator"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "iff" = callPackage - ({ mkDerivation, base, binary, bytestring, stdenv }: + ({ mkDerivation, base, binary, bytestring, lib }: mkDerivation { pname = "iff"; version = "0.0.6"; @@ -18245,8 +21499,40 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; description = "Constructing and dissecting IFF files"; license = "GPL"; }) {}; + "ihaskell" = callPackage + ({ mkDerivation, aeson, base, base64-bytestring, bytestring, cereal + , cmdargs, containers, directory, exceptions, filepath, ghc + , ghc-boot, ghc-parser, ghc-paths, haskeline, hlint, http-client + , http-client-tls, ipython-kernel, lib, mtl, parsec, process + , random, shelly, split, stm, strict, text, time, transformers + , unix, unordered-containers, utf8-string, vector + }: + mkDerivation { + pname = "ihaskell"; + version = "0.10.2.1"; + sha256 = "6c8bb407f767e95dfbeecf0d1d0252272bebd270a29db7d9a10c38c442a9fdae"; + isLibrary = true; + isExecutable = true; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + aeson base base64-bytestring bytestring cereal cmdargs containers + directory exceptions filepath ghc ghc-boot ghc-parser ghc-paths + haskeline hlint http-client http-client-tls ipython-kernel mtl + parsec process random shelly split stm strict text time + transformers unix unordered-containers utf8-string vector + ]; + executableHaskellDepends = [ + aeson base bytestring containers directory ghc ipython-kernel + process strict text transformers unix unordered-containers + ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/gibiansky/IHaskell"; + description = "A Haskell backend kernel for the IPython project"; + license = lib.licenses.mit; + }) {}; "ihs" = callPackage - ({ mkDerivation, base, process, stdenv }: + ({ mkDerivation, base, lib, process }: mkDerivation { pname = "ihs"; version = "0.1.0.3"; @@ -18258,24 +21544,24 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/minad/ihs"; description = "Interpolated Haskell"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "ilist" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "ilist"; - version = "0.3.1.0"; - sha256 = "e898e1dd1077e5a268f66e2de15f15ef64eddac94133954c9e054d59092afe97"; + version = "0.4.0.1"; + sha256 = "0448857296974317ee162551ef3e2f31c434e114df6d17d7f6acd3476c52dc04"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/aelve/ilist"; + homepage = "http://github.com/kowainik/ilist"; description = "Optimised list functions for doing index-related things"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mpl20; }) {}; "imagesize-conduit" = callPackage ({ mkDerivation, base, bytestring, conduit, conduit-extra - , exceptions, stdenv + , exceptions, lib }: mkDerivation { pname = "imagesize-conduit"; @@ -18290,10 +21576,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/silkapp/imagesize-conduit"; description = "Determine the size of some common image formats"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "immortal" = callPackage - ({ mkDerivation, base, stdenv, stm, unliftio-core }: + ({ mkDerivation, base, lib, stm, unliftio-core }: mkDerivation { pname = "immortal"; version = "0.3"; @@ -18303,91 +21589,165 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/feuerbach/immortal"; description = "Spawn threads that never die (unless told to do so)"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "immortal-queue" = callPackage + ({ mkDerivation, async, base, immortal, lib }: + mkDerivation { + pname = "immortal-queue"; + version = "0.1.0.1"; + sha256 = "e73b83dbf09b2532feef650ebf158bebe53fe58f582a2211151d2c2089d74091"; + libraryHaskellDepends = [ async base immortal ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/prikhi/immortal-queue#readme"; + description = "Build a pool of queue-processing worker threads"; + license = lib.licenses.bsd3; + }) {}; + "inbox" = callPackage + ({ mkDerivation, async, base, error-or, lib, text, time }: + mkDerivation { + pname = "inbox"; + version = "0.1.0"; + sha256 = "382b9fdc1c51952031def648e0e99e6668da1597186c19916ae59c9362130188"; + libraryHaskellDepends = [ async base error-or text time ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/luntain/error-or-bundle/blob/master/inbox#readme"; + description = "Inbox for asychronous messages"; + license = lib.licenses.bsd3; }) {}; "include-file" = callPackage - ({ mkDerivation, base, bytestring, random, stdenv, template-haskell + ({ mkDerivation, base, bytestring, Cabal, lib, random + , template-haskell }: mkDerivation { pname = "include-file"; - version = "0.1.0.3"; - sha256 = "208f1f3bdc717f5f953cb7c9935c84d6a6291b7cd5ed8a22fa8567184be33d29"; + version = "0.1.0.4"; + sha256 = "5b1f93482bc5ed85bbe04a1c63fa8bee6d4156b79cee43f812db92765fa1666e"; + setupHaskellDepends = [ base bytestring Cabal random ]; libraryHaskellDepends = [ base bytestring random template-haskell ]; doHaddock = false; doCheck = false; description = "Inclusion of files in executables at compile-time"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "incremental-parser" = callPackage - ({ mkDerivation, base, monoid-subclasses, stdenv }: + ({ mkDerivation, base, input-parsers, lib, monoid-subclasses + , parsers, rank2classes, transformers + }: mkDerivation { pname = "incremental-parser"; - version = "0.3.2.1"; - sha256 = "d9515a1938d47bc9861600aac5304ac1b98727905145a061dc12664b45b56a1d"; - libraryHaskellDepends = [ base monoid-subclasses ]; + version = "0.5.0.2"; + sha256 = "d2a5fa9530697175d2cb4f3ca6c6ad7669e3c464060e168e5a274864673b8394"; + libraryHaskellDepends = [ + base input-parsers monoid-subclasses parsers rank2classes + transformers + ]; doHaddock = false; doCheck = false; homepage = "https://github.com/blamario/incremental-parser"; description = "Generic parser library capable of providing partial results from partial input"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; }) {}; - "indentation-core" = callPackage - ({ mkDerivation, base, mtl, stdenv }: + "indents" = callPackage + ({ mkDerivation, base, lib, mtl, parsec }: mkDerivation { - pname = "indentation-core"; - version = "0.0.0.2"; - sha256 = "099a3e3bb82c6af1b99172722bb01e954d1722d468e2d0722415f4f479993fd0"; - libraryHaskellDepends = [ base mtl ]; + pname = "indents"; + version = "0.5.0.1"; + sha256 = "a1582cc6b705170bab6ea5cbe360530641ae94a31714a61b56c5f2067ee4ec36"; + revision = "1"; + editedCabalFile = "0zbcf8m4n63ff06hjp0mr18i59y5wd6c1k5z1j6rnl7kymghkjrg"; + libraryHaskellDepends = [ base mtl parsec ]; doHaddock = false; doCheck = false; - homepage = "https://bitbucket.org/adamsmd/indentation"; - description = "Indentation sensitive parsing combinators core library"; - license = stdenv.lib.licenses.bsd3; + homepage = "http://github.com/jaspervdj/indents"; + description = "indentation sensitive parser-combinators for parsec"; + license = lib.licenses.bsd3; }) {}; - "indentation-parsec" = callPackage - ({ mkDerivation, base, indentation-core, mtl, parsec, stdenv }: + "indexed" = callPackage + ({ mkDerivation, base, lib }: mkDerivation { - pname = "indentation-parsec"; - version = "0.0.0.2"; - sha256 = "0e37846ef1ea045d6c365be38f2b55ff7dd36e960f21ba28e879137874c8f2d4"; - libraryHaskellDepends = [ base indentation-core mtl parsec ]; + pname = "indexed"; + version = "0.1.3"; + sha256 = "ef84090ec6bf79e7dc6e9d570fc370c9eea6cd251d3c023979f6e1f8d3fbf5c2"; + libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://bitbucket.org/adamsmd/indentation"; - description = "Indentation sensitive parsing combinators for Parsec"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/reinerp/indexed"; + description = "Haskell98 indexed functors, monads, comonads"; + license = lib.licenses.bsd3; }) {}; - "indents" = callPackage - ({ mkDerivation, base, mtl, parsec, stdenv }: + "indexed-containers" = callPackage + ({ mkDerivation, base, lib }: mkDerivation { - pname = "indents"; - version = "0.5.0.0"; - sha256 = "16bcc7ca0c1292e196a9c545df507e20e96f54a94392b775a686312503d9c3d3"; - libraryHaskellDepends = [ base mtl parsec ]; + pname = "indexed-containers"; + version = "0.1.0.2"; + sha256 = "0e09ebffb03eaa382cc45db04a80a997a119428b879ce2127e7371d1b9b2d2a2"; + libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/jaspervdj/indents"; - description = "indentation sensitive parser-combinators for parsec"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/zliu41/indexed-containers"; + description = "Simple, no-frills indexed lists"; + license = lib.licenses.bsd3; }) {}; "indexed-list-literals" = callPackage - ({ mkDerivation, base, Only, stdenv }: + ({ mkDerivation, base, lib, Only }: mkDerivation { pname = "indexed-list-literals"; - version = "0.2.1.2"; - sha256 = "d896ae5b3919a7a9fecdd9336e8f330d055fbdae4821be04b7c1266ccaa07d10"; + version = "0.2.1.3"; + sha256 = "26e399e285ddf44822781559f7202ed821382457ed6c1c32bdaac7945c033f9d"; libraryHaskellDepends = [ base Only ]; doHaddock = false; doCheck = false; homepage = "https://github.com/davidm-d/indexed-list-literals"; description = "Type safe indexed list literals"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "indexed-profunctors" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "indexed-profunctors"; + version = "0.1.1"; + sha256 = "5aba418a92a4f75efc626de7c0e4d88ed57033e0de0f2743ce6d9c9ef7626cb1"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + description = "Utilities for indexed profunctors"; + license = lib.licenses.bsd3; + }) {}; + "indexed-traversable" = callPackage + ({ mkDerivation, array, base, containers, lib, transformers }: + mkDerivation { + pname = "indexed-traversable"; + version = "0.1.1"; + sha256 = "7ac36ae3153cbe7a8e99eacffd065367b87544953cc92997f424a150db468139"; + libraryHaskellDepends = [ array base containers transformers ]; + doHaddock = false; + doCheck = false; + description = "FunctorWithIndex, FoldableWithIndex, TraversableWithIndex"; + license = lib.licenses.bsd2; + }) {}; + "indexed-traversable-instances" = callPackage + ({ mkDerivation, base, indexed-traversable, lib, tagged + , unordered-containers, vector + }: + mkDerivation { + pname = "indexed-traversable-instances"; + version = "0.1"; + sha256 = "faec44807902b58e50c8e12394d15ebda1f00c0e235b490f7b1c4ae5b5ae68dc"; + libraryHaskellDepends = [ + base indexed-traversable tagged unordered-containers vector + ]; + doHaddock = false; + doCheck = false; + description = "More instances of FunctorWithIndex, FoldableWithIndex, TraversableWithIndex"; + license = lib.licenses.bsd2; }) {}; "infer-license" = callPackage - ({ mkDerivation, base, directory, filepath, stdenv, text - , text-metrics + ({ mkDerivation, base, directory, filepath, lib, text, text-metrics }: mkDerivation { pname = "infer-license"; @@ -18399,16 +21759,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Infer software license from a given license file"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "inflections" = callPackage - ({ mkDerivation, base, exceptions, megaparsec, stdenv, text + ({ mkDerivation, base, exceptions, lib, megaparsec, text , unordered-containers }: mkDerivation { pname = "inflections"; - version = "0.4.0.4"; - sha256 = "94393624bb73e5a8f436c8f823292bab9b5ca5bb47ebf733379848773b585753"; + version = "0.4.0.6"; + sha256 = "41f680b984653e782438295c85b5451be9c6bf03e6e6b56758cfa00b8ad8a480"; libraryHaskellDepends = [ base exceptions megaparsec text unordered-containers ]; @@ -18416,18 +21776,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/stackbuilders/inflections-hs"; description = "Inflections library for Haskell"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "influxdb" = callPackage ({ mkDerivation, aeson, attoparsec, base, bytestring, Cabal , cabal-doctest, clock, containers, foldl, http-client, http-types - , lens, network, optional-args, scientific, stdenv, tagged, text - , time, unordered-containers, vector + , lens, lib, network, optional-args, scientific, tagged, text, time + , unordered-containers, vector }: mkDerivation { pname = "influxdb"; - version = "1.6.1.1"; - sha256 = "d167219c93d0c900ec58824a225b34ac9e465f671728d7890d7f4b0036f1b032"; + version = "1.9.1.2"; + sha256 = "d612e2c0d9e5fc873884048f2c6dc71e04d4aeb49e0b524477303b59a372b929"; isLibrary = true; isExecutable = true; setupHaskellDepends = [ base Cabal cabal-doctest ]; @@ -18439,19 +21799,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; homepage = "https://github.com/maoe/influxdb-haskell"; - description = "Haskell client library for InfluxDB"; - license = stdenv.lib.licenses.bsd3; + description = "InfluxDB client library for Haskell"; + license = lib.licenses.bsd3; }) {}; "ini" = callPackage - ({ mkDerivation, attoparsec, base, stdenv, text - , unordered-containers + ({ mkDerivation, attoparsec, base, lib, text, unordered-containers }: mkDerivation { pname = "ini"; - version = "0.3.6"; - sha256 = "fcbbe3745a125e80dd6d0b4fe9b3a590507cf73dfaa62e115b20a46f0fd53cd9"; - revision = "1"; - editedCabalFile = "0gfikdal67aws20i5r4wg4r0lgn844glykcn3nnmbmyvwsks049l"; + version = "0.4.1"; + sha256 = "14293c2a209f938cc3e779132f3411c330636a91b1a58549a154c025518c7c57"; libraryHaskellDepends = [ attoparsec base text unordered-containers ]; @@ -18459,17 +21816,28 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/chrisdone/ini"; description = "Quick and easy configuration files in the INI format"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "inj" = callPackage + ({ mkDerivation, lib }: + mkDerivation { + pname = "inj"; + version = "1.0"; + sha256 = "4012310e5e80d4f4eb11ec73aeda311f7cb94a5c68e7393bfb3b99513cd61ab6"; + doHaddock = false; + doCheck = false; + description = "A class for injective (one-to-one) functions"; + license = lib.licenses.publicDomain; }) {}; "inline-c" = callPackage ({ mkDerivation, ansi-wl-pprint, base, bytestring, containers - , hashable, mtl, parsec, parsers, stdenv, template-haskell + , hashable, lib, mtl, parsec, parsers, template-haskell , transformers, unordered-containers, vector }: mkDerivation { pname = "inline-c"; - version = "0.7.0.1"; - sha256 = "daf2f2f286ff549e319ebc9f9491ea809f27996e234ac99a5e2eecc8e35e4ca7"; + version = "0.9.1.5"; + sha256 = "f1c0c1b57d7c7b1961a29457ffe959aaf0a7a97b7d7266c82b0c8404e11a1528"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -18479,28 +21847,51 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Write Haskell source files including C code inline. No FFI required."; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "inline-c-cpp" = callPackage - ({ mkDerivation, base, inline-c, safe-exceptions, stdenv + ({ mkDerivation, base, containers, inline-c, lib, safe-exceptions , template-haskell }: mkDerivation { pname = "inline-c-cpp"; - version = "0.3.0.1"; - sha256 = "019c1706259c9ca2ffe961fda29d04840bfe6cdd9837e79d65c55bb3b3700403"; + version = "0.4.0.3"; + sha256 = "80c6b26b5e862e5c6105bfaee4f624f9725d3a9e55db791ebe81b3c1a287192f"; libraryHaskellDepends = [ - base inline-c safe-exceptions template-haskell + base containers inline-c safe-exceptions template-haskell ]; doHaddock = false; doCheck = false; description = "Lets you embed C++ code into Haskell"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; + "inline-r" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers + , data-default-class, deepseq, exceptions, inline-c, lib, mtl + , pretty, primitive, process, R, reflection, setenv, singletons + , template-haskell, text, th-lift, th-orphans, transformers, unix + , vector + }: + mkDerivation { + pname = "inline-r"; + version = "0.10.4"; + sha256 = "b4222e49587132fc5596373558c33d9d7637b483309bff7bb1c076f8a3886e4b"; + libraryHaskellDepends = [ + aeson base bytestring containers data-default-class deepseq + exceptions inline-c mtl pretty primitive process reflection setenv + singletons template-haskell text th-lift th-orphans transformers + unix vector + ]; + libraryPkgconfigDepends = [ R ]; + doHaddock = false; + doCheck = false; + homepage = "https://tweag.github.io/HaskellR"; + description = "Seamlessly call R from Haskell and vice versa. No FFI required."; + license = lib.licenses.bsd3; + }) {inherit (pkgs) R;}; "inliterate" = callPackage ({ mkDerivation, base, blaze-html, cheapskate, containers - , haskell-src-exts, lucid, lucid-extras, plotlyhs, stdenv, text - , time + , haskell-src-exts, lib, lucid, lucid-extras, plotlyhs, text, time }: mkDerivation { pname = "inliterate"; @@ -18517,37 +21908,54 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/diffusionkinetics/open/inliterate"; description = "Interactive literate programming"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "input-parsers" = callPackage + ({ mkDerivation, attoparsec, base, binary, bytestring, lib + , monoid-subclasses, parsec, parsers, text, transformers + }: + mkDerivation { + pname = "input-parsers"; + version = "0.2.2"; + sha256 = "3fab98fdf9538eabcd8a5bf8b157eec274e8f10a88030fda3a512ef4ba0567cd"; + libraryHaskellDepends = [ + attoparsec base binary bytestring monoid-subclasses parsec parsers + text transformers + ]; + doHaddock = false; + doCheck = false; + description = "Extension of the parsers library with more capability and efficiency"; + license = lib.licenses.bsd3; }) {}; "insert-ordered-containers" = callPackage - ({ mkDerivation, aeson, base, base-compat, hashable, lens - , semigroupoids, semigroups, stdenv, text, transformers + ({ mkDerivation, aeson, base, base-compat, deepseq, hashable + , indexed-traversable, lens, lib, optics-core, optics-extra + , semigroupoids, semigroups, text, transformers , unordered-containers }: mkDerivation { pname = "insert-ordered-containers"; - version = "0.2.1.0"; - sha256 = "d71d126bf455898492e1d2ba18b2ad04453f8b0e4daff3926a67f0560a712298"; - revision = "9"; - editedCabalFile = "02d4zqyb9dbahkpcbpgxylrc5xxc0zbw1awj5w0jyrql2g2b6a5f"; + version = "0.2.5"; + sha256 = "3e3051ec8591bbe05a030b9033d0d882895396d52edc5f77fde52316ff7b632d"; libraryHaskellDepends = [ - aeson base base-compat hashable lens semigroupoids semigroups text - transformers unordered-containers + aeson base base-compat deepseq hashable indexed-traversable lens + optics-core optics-extra semigroupoids semigroups text transformers + unordered-containers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/phadej/insert-ordered-containers#readme"; description = "Associative containers retaining insertion order for traversals"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "inspection-testing" = callPackage - ({ mkDerivation, base, containers, ghc, mtl, stdenv - , template-haskell, transformers + ({ mkDerivation, base, containers, ghc, lib, mtl, template-haskell + , transformers }: mkDerivation { pname = "inspection-testing"; - version = "0.4.1.1"; - sha256 = "9474250584400659a420e6860b255dc0d808933c7b6b9580020ed25263d73ed2"; + version = "0.4.5.0"; + sha256 = "01f40b2aabc455106d5f28d246a4455729d88d79944955fb26dc9f5481890bb5"; libraryHaskellDepends = [ base containers ghc mtl template-haskell transformers ]; @@ -18555,10 +21963,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/nomeata/inspection-testing"; description = "GHC plugin to do inspection testing"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "instance-control" = callPackage - ({ mkDerivation, base, mtl, stdenv, transformers }: + ({ mkDerivation, base, lib, mtl, transformers }: mkDerivation { pname = "instance-control"; version = "0.1.2.0"; @@ -18568,25 +21976,53 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/lazac/instance-control"; description = "Controls how the compiler searches for instances using type families"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "int-cast" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "int-cast"; + version = "0.2.0.0"; + sha256 = "e006956a08b751a996a92828ccb728b7237c9c435c4b35b5169eb8d44ac51969"; + revision = "4"; + editedCabalFile = "1l5n3hsa8gr0wzc3cb32ha2j8kcf976i84z04580q41macf0r0h6"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/hvr/int-cast"; + description = "Checked conversions between integral types"; + license = lib.licenses.bsd3; }) {}; "integer-logarithms" = callPackage - ({ mkDerivation, array, base, ghc-prim, integer-gmp, stdenv }: + ({ mkDerivation, array, base, ghc-prim, integer-gmp, lib }: mkDerivation { pname = "integer-logarithms"; - version = "1.0.2.2"; - sha256 = "ba86628d5c14f31fddccea86eeec122ed992af28d5b7ad964b2f5487605e7fc3"; - revision = "1"; - editedCabalFile = "1684dkh8j2xqsd85bfsmhv3iam37hasjg4x79mvl6xh7scmpfdbw"; + version = "1.0.3.1"; + sha256 = "9b0a9f9fab609b15cd015865721fb05f744a1bc77ae92fd133872de528bbea7f"; libraryHaskellDepends = [ array base ghc-prim integer-gmp ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/Bodigrim/integer-logarithms"; + homepage = "https://github.com/haskellari/integer-logarithms"; description = "Integer logarithms"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "integer-roots" = callPackage + ({ mkDerivation, base, integer-gmp, lib }: + mkDerivation { + pname = "integer-roots"; + version = "1.0"; + sha256 = "c13f79d3a887e132e6e5157eea26a00121c301b3b6680ac6a445ca343203a788"; + revision = "1"; + editedCabalFile = "0h130qddg27234mhi5spkwcgcxpnmq07bppwig5vq8z70fh5f1qx"; + libraryHaskellDepends = [ base integer-gmp ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/Bodigrim/integer-roots"; + description = "Integer roots and perfect powers"; + license = lib.licenses.mit; }) {}; "integration" = callPackage - ({ mkDerivation, base, parallel, stdenv }: + ({ mkDerivation, base, lib, parallel }: mkDerivation { pname = "integration"; version = "0.2.1"; @@ -18596,16 +22032,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/ekmett/integration"; description = "Fast robust numeric integration via tanh-sinh quadrature"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "intern" = callPackage - ({ mkDerivation, array, base, bytestring, hashable, stdenv, text + ({ mkDerivation, array, base, bytestring, hashable, lib, text , unordered-containers }: mkDerivation { pname = "intern"; - version = "0.9.2"; - sha256 = "93a3b20e96dad8d83c9145dfc68bd9d2a6a72c9f64e4a7bc257d330070f42e20"; + version = "0.9.4"; + sha256 = "40a297573d684fe5b60bfbd0642e492ce3ffcb492ccc5fbbbce12ac1ae228701"; libraryHaskellDepends = [ array base bytestring hashable text unordered-containers ]; @@ -18613,30 +22049,29 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/intern/"; description = "Efficient hash-consing for arbitrary data types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "interpolate" = callPackage - ({ mkDerivation, base, haskell-src-meta, stdenv, template-haskell - }: + ({ mkDerivation, base, haskell-src-meta, lib, template-haskell }: mkDerivation { pname = "interpolate"; - version = "0.2.0"; - sha256 = "6e112006073f2d91e7e93432ccb147b79a21fcc21a9dedd0d8c38cef51926abe"; + version = "0.2.1"; + sha256 = "2776dd5083aead756a761c3350a87312b4fbf4851555cf9560800bc3929c590e"; libraryHaskellDepends = [ base haskell-src-meta template-haskell ]; doHaddock = false; doCheck = false; homepage = "https://github.com/sol/interpolate#readme"; description = "String interpolation done right"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "interpolatedstring-perl6" = callPackage - ({ mkDerivation, base, bytestring, Cabal, haskell-src-meta, process - , stdenv, template-haskell, text + ({ mkDerivation, base, bytestring, Cabal, haskell-src-meta, lib + , process, template-haskell, text }: mkDerivation { pname = "interpolatedstring-perl6"; - version = "1.0.1"; - sha256 = "5eadba4ba24c10a8f2a4a1cc48af6eb0f07190d7c0e691a22c5a99fb37367258"; + version = "1.0.2"; + sha256 = "5a8b1e8b65253ce1e1b07b9de1075e9306483160a7b419d5f126d7e2744b7bb7"; enableSeparateDataOutput = true; setupHaskellDepends = [ base Cabal process ]; libraryHaskellDepends = [ @@ -18645,14 +22080,14 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "QuasiQuoter for Perl6-style multi-line interpolated strings"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "interpolation" = callPackage - ({ mkDerivation, base, stdenv, utility-ht }: + ({ mkDerivation, base, lib, utility-ht }: mkDerivation { pname = "interpolation"; - version = "0.1.0.3"; - sha256 = "e29794d7bb07e13c0fc3e6a05948862fd5ccd50910b9718e4818d354e26f3049"; + version = "0.1.1.1"; + sha256 = "c5735cf6cde9439188890290e2d01dd40fabca670ecf17b70e12dc9e8aa33d20"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base utility-ht ]; @@ -18660,17 +22095,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://hub.darcs.net/thielema/interpolation/"; description = "piecewise linear and cubic Hermite interpolation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "interpolator" = callPackage - ({ mkDerivation, aeson, base, containers, either, mono-traversable - , mtl, product-profunctors, profunctors, QuickCheck, stdenv - , template-haskell, text + ({ mkDerivation, aeson, base, containers, either, lib + , mono-traversable, mtl, product-profunctors, profunctors + , QuickCheck, template-haskell, text }: mkDerivation { pname = "interpolator"; - version = "0.1.1"; - sha256 = "c065b48e36af4d9cfc301403c9224af78c7b5e5ae826428eed4decdd21ac5e8f"; + version = "1.1.0.2"; + sha256 = "6ebfc6f3e9e16c2f7693bd7a0a16e50fa3115b86cb622a4db5792510fc7836d3"; libraryHaskellDepends = [ aeson base containers either mono-traversable mtl product-profunctors profunctors QuickCheck template-haskell text @@ -18679,47 +22114,42 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/tvision-insights/interpolator"; description = "Runtime interpolation of environment variables in records using profunctors"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "intervals" = callPackage - ({ mkDerivation, array, base, Cabal, cabal-doctest, distributive - , ghc-prim, stdenv - }: + ({ mkDerivation, array, base, distributive, ghc-prim, lib }: mkDerivation { pname = "intervals"; - version = "0.8.1"; - sha256 = "9ce3bf9d31b9ab2296fccc25031fd52e1c3e4abeca5d3bb452a725b586eb7e03"; - revision = "4"; - editedCabalFile = "1qx3q0v13l1zaln9zdk8chxpxhshbz5x0vqm0qda7d1kpv7h6a7r"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "0.9.2"; + sha256 = "9b421de662873e65e90380b9c5a0c7497afa581b3e0e65530f8653a4fddb2be2"; libraryHaskellDepends = [ array base distributive ghc-prim ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/intervals"; description = "Interval Arithmetic"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "intro" = callPackage - ({ mkDerivation, base, bytestring, containers, deepseq, dlist - , extra, hashable, mtl, safe, stdenv, text, transformers - , unordered-containers, writer-cps-mtl + ({ mkDerivation, base, bytestring, containers, extra, hashable, lib + , mtl, safe, text, transformers, unordered-containers + , writer-cps-mtl }: mkDerivation { pname = "intro"; - version = "0.5.2.1"; - sha256 = "e8e2124179c749e597998628bf2cd167d15e977db0f1105f5856a02e8bbaac44"; + version = "0.9.0.0"; + sha256 = "1de4d8a9e7a70ca7bf00eada60da3758ea5be5b608747ea5865fc46c935c8874"; libraryHaskellDepends = [ - base bytestring containers deepseq dlist extra hashable mtl safe - text transformers unordered-containers writer-cps-mtl + base bytestring containers extra hashable mtl safe text + transformers unordered-containers writer-cps-mtl ]; doHaddock = false; doCheck = false; homepage = "https://github.com/minad/intro#readme"; description = "Safe and minimal prelude"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "intset-imperative" = callPackage - ({ mkDerivation, base, deepseq, primitive, stdenv }: + ({ mkDerivation, base, deepseq, lib, primitive }: mkDerivation { pname = "intset-imperative"; version = "0.1.0.0"; @@ -18729,41 +22159,40 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/hverr/haskell-intset-imperative#readme"; description = "An imperative integer set written in Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "invariant" = callPackage ({ mkDerivation, array, base, bifunctors, comonad, containers - , contravariant, ghc-prim, profunctors, semigroups, StateVar - , stdenv, stm, tagged, template-haskell, th-abstraction - , transformers, transformers-compat, unordered-containers + , contravariant, ghc-prim, lib, profunctors, StateVar, stm, tagged + , template-haskell, th-abstraction, transformers + , transformers-compat, unordered-containers }: mkDerivation { pname = "invariant"; - version = "0.5.1"; - sha256 = "eb8c9c45ad24020af2978f22271458bf3787937d931c50c86b580c53ca3f122b"; - revision = "1"; - editedCabalFile = "100gsacbpal53khj94m5qs4aq70hbsp4dz4065czfm49ysd4yqq4"; + version = "0.5.4"; + sha256 = "b9fa0a1805dde1a4d39bed154e297a37933d2a82b295231098a76be9d60397ca"; libraryHaskellDepends = [ array base bifunctors comonad containers contravariant ghc-prim - profunctors semigroups StateVar stm tagged template-haskell - th-abstraction transformers transformers-compat - unordered-containers + profunctors StateVar stm tagged template-haskell th-abstraction + transformers transformers-compat unordered-containers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nfrisby/invariant-functors"; description = "Haskell98 invariant functors"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; }) {}; "invertible" = callPackage - ({ mkDerivation, base, haskell-src-meta, invariant, lens - , partial-isomorphisms, semigroupoids, stdenv, template-haskell + ({ mkDerivation, base, haskell-src-meta, invariant, lens, lib + , partial-isomorphisms, semigroupoids, template-haskell , transformers }: mkDerivation { pname = "invertible"; - version = "0.2.0.5"; - sha256 = "0a0adaa1f371f739fd2c506ff2ba3c4db278bbdfda0171bd8329d678c15b8dbb"; + version = "0.2.0.7"; + sha256 = "311e9bb0ca4c22955f02ab410e614608df685e7f4421cb5a2c2f7b968aafecd9"; + revision = "1"; + editedCabalFile = "19xcczz26ji5xaws4ikvacqz991qgislj32hs8rlks07qw3qmnbn"; libraryHaskellDepends = [ base haskell-src-meta invariant lens partial-isomorphisms semigroupoids template-haskell transformers @@ -18771,27 +22200,31 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "bidirectional arrows, bijective functions, and invariant functors"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "io-choice" = callPackage - ({ mkDerivation, base, lifted-base, monad-control, stdenv - , template-haskell, transformers, transformers-base + "invertible-grammar" = callPackage + ({ mkDerivation, base, bifunctors, containers, lib, mtl + , prettyprinter, profunctors, semigroups, tagged, template-haskell + , text, transformers }: mkDerivation { - pname = "io-choice"; - version = "0.0.7"; - sha256 = "394a60c4b0bcb3ce0dab6618891ab6e7405e583f724ca445ddc58b59725a669b"; + pname = "invertible-grammar"; + version = "0.1.3"; + sha256 = "36599b2371fa9598b675370dc153f6a30f89597c425f8776e552dd5aeee11098"; + revision = "1"; + editedCabalFile = "021pq45sz1x819yksgyl8p4h7c659gb99798j791a3r8583cz2za"; libraryHaskellDepends = [ - base lifted-base monad-control template-haskell transformers - transformers-base + base bifunctors containers mtl prettyprinter profunctors semigroups + tagged template-haskell text transformers ]; doHaddock = false; doCheck = false; - description = "Choice for IO and lifted IO"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/esmolanka/invertible-grammar"; + description = "Invertible parsing combinators framework"; + license = lib.licenses.bsd3; }) {}; "io-machine" = callPackage - ({ mkDerivation, base, stdenv, time }: + ({ mkDerivation, base, lib, time }: mkDerivation { pname = "io-machine"; version = "0.2.0.0"; @@ -18801,14 +22234,14 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/YoshikuniJujo/io-machine#readme"; description = "Easy I/O model to learn IO monad"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "io-manager" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "io-manager"; - version = "0.1.0.2"; - sha256 = "bf0aa7740a8aaf31fc4f2570a47957365ae7d9248edd309e694053f1cd804138"; + version = "0.1.0.3"; + sha256 = "7ac48c5af0a3bc3ee59f7302ffe076d2f098cdedcb22ad6cfb1c0fdea923a810"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base containers ]; @@ -18816,10 +22249,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Skeleton library around the IO monad"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "io-memoize" = callPackage - ({ mkDerivation, async, base, stdenv }: + ({ mkDerivation, async, base, lib }: mkDerivation { pname = "io-memoize"; version = "1.1.1.0"; @@ -18829,10 +22262,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/DanBurton/io-memoize"; description = "Memoize IO actions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "io-region" = callPackage - ({ mkDerivation, base, stdenv, stm }: + ({ mkDerivation, base, lib, stm }: mkDerivation { pname = "io-region"; version = "0.1.1"; @@ -18842,10 +22275,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/Yuras/io-region/wiki"; description = "Exception safe resource management with dynamic regions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "io-storage" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "io-storage"; version = "0.3"; @@ -18855,39 +22288,39 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/willdonnelly/io-storage"; description = "A key-value store in the IO monad"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "io-streams" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, bytestring-builder - , network, primitive, process, stdenv, text, time, transformers - , vector, zlib-bindings + ({ mkDerivation, attoparsec, base, bytestring, lib, network + , primitive, process, text, time, transformers, vector + , zlib-bindings }: mkDerivation { pname = "io-streams"; - version = "1.5.0.1"; - sha256 = "5dcb3717933197a84f31be74abf545126b3d25eb0e0d64f722c480d3c46b2c8b"; - revision = "2"; - editedCabalFile = "1mcab95d6hm098myh9gp7sh10srigjphgvm8s9pfs7jg5hzghy14"; - configureFlags = [ "-fNoInteractiveTests" ]; + version = "1.5.2.1"; + sha256 = "de666408a44db1bb7a9116a56d3100165df4f6dfc34142eff97a469e7bc57af8"; + revision = "1"; + editedCabalFile = "0zgrhvafnk9ds29n6x93cifw4993mgvvx3p2d3922frkjvd6xa5v"; + configureFlags = [ "-fnointeractivetests" ]; libraryHaskellDepends = [ - attoparsec base bytestring bytestring-builder network primitive - process text time transformers vector zlib-bindings + attoparsec base bytestring network primitive process text time + transformers vector zlib-bindings ]; doHaddock = false; doCheck = false; description = "Simple, composable, and easy-to-use stream I/O"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "io-streams-haproxy" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, io-streams, network - , stdenv, transformers + ({ mkDerivation, attoparsec, base, bytestring, io-streams, lib + , network, transformers }: mkDerivation { pname = "io-streams-haproxy"; - version = "1.0.0.2"; - sha256 = "77814f8258b5c32707a13e0d30ab2e144e7ad073aee821d6def65554024ed086"; - revision = "4"; - editedCabalFile = "06c51a057n5bc9xfbp2m4jz5ds4z1xvmsx5mppch6qfwbz7x5i9l"; + version = "1.0.1.0"; + sha256 = "b74eca9290fe838a0e3be857a38b62cf6fb7478acee400eac19e47471a2c96b5"; + revision = "3"; + editedCabalFile = "02k9halblgnynlm781ahc81yxla8z7cck1gikm8555v78rf5hv7x"; libraryHaskellDepends = [ attoparsec base bytestring io-streams network transformers ]; @@ -18895,84 +22328,100 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://snapframework.com/"; description = "HAProxy protocol 1.5 support for io-streams"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "ip" = callPackage - ({ mkDerivation, aeson, attoparsec, base, bytestring, deepseq - , hashable, primitive, stdenv, text, vector - }: - mkDerivation { - pname = "ip"; - version = "1.4.1"; - sha256 = "f1c2f1993c82cbbc2e6230d4b669b3df4128286490473528d642c16e5617ec5b"; - libraryHaskellDepends = [ - aeson attoparsec base bytestring deepseq hashable primitive text - vector - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/andrewthad/haskell-ip#readme"; - description = "Library for IP and MAC addresses"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "ip6addr" = callPackage - ({ mkDerivation, base, cmdargs, IPv6Addr, stdenv, text }: + ({ mkDerivation, base, cmdargs, IPv6Addr, lib, text }: mkDerivation { pname = "ip6addr"; - version = "1.0.0"; - sha256 = "e805be52d77edfb0e71740dbfa57403654cb34929083589d79d44757c01f80f1"; + version = "1.0.2"; + sha256 = "57a795830df8e6562fb6ebd04c3d53e6a0e018719bb3463a52e8c1824086492e"; isLibrary = false; isExecutable = true; executableHaskellDepends = [ base cmdargs IPv6Addr text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/MichelBoucey/ip6addr"; - description = "Commandline tool to generate IPv6 address text representations"; - license = stdenv.lib.licenses.bsd3; + description = "Commandline tool to deal with IPv6 address text representations"; + license = lib.licenses.bsd3; + }) {}; + "ipa" = callPackage + ({ mkDerivation, attoparsec, base, lib, template-haskell, text + , unicode-transforms + }: + mkDerivation { + pname = "ipa"; + version = "0.3.1.1"; + sha256 = "4499be4ffe831e1b49ca009122abf10e7b861c039c73cac703d733b9013dc422"; + libraryHaskellDepends = [ + attoparsec base template-haskell text unicode-transforms + ]; + doHaddock = false; + doCheck = false; + homepage = "https://gitlab.com/ngua/ipa-hs/-/blob/master/README.org"; + description = "Internal Phonetic Alphabet (IPA)"; + license = lib.licenses.bsd3; }) {}; "iproute" = callPackage - ({ mkDerivation, appar, base, byteorder, containers, network - , stdenv + ({ mkDerivation, appar, base, byteorder, bytestring, containers + , lib, network }: mkDerivation { pname = "iproute"; - version = "1.7.7"; - sha256 = "e6a3fe4a6f2a78fcee0f98255f97232d8b6b9b1fa48faee3bef96f0b462a4b3d"; + version = "1.7.11"; + sha256 = "205dcd27cce76345e4fc60060b5d428b015a09e9023f5f1bba58be1f562a8a8b"; libraryHaskellDepends = [ - appar base byteorder containers network + appar base byteorder bytestring containers network ]; doHaddock = false; doCheck = false; homepage = "http://www.mew.org/~kazu/proj/iproute/"; description = "IP Routing Table"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "ipynb" = callPackage + ({ mkDerivation, aeson, base, base64-bytestring, bytestring + , containers, lib, text, unordered-containers + }: + mkDerivation { + pname = "ipynb"; + version = "0.1.0.1"; + sha256 = "2b7b13bbe685ba753a9cc3d93c7155dfa5403122d72c9ce3ec39e47323f89753"; + libraryHaskellDepends = [ + aeson base base64-bytestring bytestring containers text + unordered-containers + ]; + doHaddock = false; + doCheck = false; + description = "Data structure for working with Jupyter notebooks (ipynb)"; + license = lib.licenses.bsd3; }) {}; "ipython-kernel" = callPackage - ({ mkDerivation, aeson, base, bytestring, cereal, containers - , cryptonite, directory, filepath, memory, mtl, process, stdenv - , temporary, text, transformers, unordered-containers, uuid - , zeromq4-haskell + ({ mkDerivation, aeson, base, bytestring, cereal, cereal-text + , containers, cryptonite, directory, filepath, lib, memory, mtl + , parsec, process, temporary, text, transformers + , unordered-containers, uuid, zeromq4-haskell }: mkDerivation { pname = "ipython-kernel"; - version = "0.9.1.0"; - sha256 = "53616435d1fef56a5ba3ad219e9ccf9d8845024b0f2cc5864575440078cc8424"; + version = "0.10.2.1"; + sha256 = "68e03ccc9782594ff6775f98d305db0d5b67f02f03ef41ad65618e28eb3adc04"; isLibrary = true; isExecutable = true; enableSeparateDataOutput = true; libraryHaskellDepends = [ - aeson base bytestring cereal containers cryptonite directory - filepath memory mtl process temporary text transformers - unordered-containers uuid zeromq4-haskell + aeson base bytestring cereal cereal-text containers cryptonite + directory filepath memory mtl parsec process temporary text + transformers unordered-containers uuid zeromq4-haskell ]; doHaddock = false; doCheck = false; homepage = "http://github.com/gibiansky/IHaskell"; description = "A library for creating kernels for IPython frontends"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "irc" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, stdenv }: + ({ mkDerivation, attoparsec, base, bytestring, lib }: mkDerivation { pname = "irc"; version = "0.6.1.0"; @@ -18981,19 +22430,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A small library for parsing IRC messages"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "irc-client" = callPackage ({ mkDerivation, base, bytestring, conduit, connection, containers - , contravariant, exceptions, irc-conduit, irc-ctcp, mtl - , network-conduit-tls, old-locale, profunctors, stdenv, stm - , stm-chans, text, time, tls, transformers, x509, x509-store - , x509-validation + , contravariant, exceptions, irc-conduit, irc-ctcp, lib, mtl + , network-conduit-tls, old-locale, profunctors, stm, stm-chans + , text, time, tls, transformers, x509, x509-store, x509-validation }: mkDerivation { pname = "irc-client"; - version = "1.1.0.5"; - sha256 = "27e224e1323cdc56ae3b536283a133e7e2b8051e4c5dfa9505a8bd79992a0c8f"; + version = "1.1.2.1"; + sha256 = "8d86a309befdb8adda5e6a704dddb62a8a5d12e6ecfbf8a833a9827194454afd"; libraryHaskellDepends = [ base bytestring conduit connection containers contravariant exceptions irc-conduit irc-ctcp mtl network-conduit-tls old-locale @@ -19004,17 +22452,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/barrucadu/irc-client"; description = "An IRC client library"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "irc-conduit" = callPackage ({ mkDerivation, async, base, bytestring, conduit, conduit-extra - , connection, irc, irc-ctcp, network-conduit-tls, profunctors - , stdenv, text, time, tls, transformers, x509-validation + , connection, irc, irc-ctcp, lib, network-conduit-tls, profunctors + , text, time, tls, transformers, x509-validation }: mkDerivation { pname = "irc-conduit"; - version = "0.3.0.1"; - sha256 = "b0a8f935eb3b4613e74efce7a913592f72835194b8977271f35eb09c578b3b52"; + version = "0.3.0.4"; + sha256 = "8149ee5e5e075662971c4cbd7059a0825b124ac1ea6fb816b8cbb2b6586b4a2b"; libraryHaskellDepends = [ async base bytestring conduit conduit-extra connection irc irc-ctcp network-conduit-tls profunctors text time tls transformers @@ -19024,10 +22472,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/barrucadu/irc-conduit"; description = "Streaming IRC message library using conduits"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "irc-ctcp" = callPackage - ({ mkDerivation, base, bytestring, stdenv, text }: + ({ mkDerivation, base, bytestring, lib, text }: mkDerivation { pname = "irc-ctcp"; version = "0.1.3.0"; @@ -19037,10 +22485,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/barrucadu/irc-ctcp"; description = "A CTCP encoding and decoding library for IRC clients"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "isbn" = callPackage + ({ mkDerivation, base, lib, text }: + mkDerivation { + pname = "isbn"; + version = "1.1.0.2"; + sha256 = "520c95afac57954152fc8dc9205dd2c04852e7f650796b48ea124e9d027e7e3f"; + libraryHaskellDepends = [ base text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/charukiewicz/hs-isbn"; + description = "ISBN Validation and Manipulation"; + license = lib.licenses.asl20; }) {}; "islink" = callPackage - ({ mkDerivation, base, stdenv, unordered-containers }: + ({ mkDerivation, base, lib, unordered-containers }: mkDerivation { pname = "islink"; version = "0.1.0.0"; @@ -19050,10 +22511,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/redneb/islink"; description = "Check if an HTML element is a link"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "iso3166-country-codes" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "iso3166-country-codes"; version = "0.20140203.8"; @@ -19067,7 +22528,7 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; license = "LGPL"; }) {}; "iso639" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "iso639"; version = "0.1.0.3"; @@ -19077,10 +22538,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/HugoDaniel/iso639"; description = "ISO-639-1 language codes"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "iso8601-time" = callPackage - ({ mkDerivation, base, stdenv, time }: + ({ mkDerivation, base, lib, time }: mkDerivation { pname = "iso8601-time"; version = "0.1.5"; @@ -19090,11 +22551,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/nh2/iso8601-time"; description = "Convert to/from the ISO 8601 time format"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "iterable" = callPackage - ({ mkDerivation, base, mtl, stdenv, tagged, template-haskell - , vector + ({ mkDerivation, base, lib, mtl, tagged, template-haskell, vector }: mkDerivation { pname = "iterable"; @@ -19108,10 +22568,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/BioHaskell/iterable"; description = "API for hierarchical multilevel collections"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "ix-shapable" = callPackage - ({ mkDerivation, array, base, stdenv }: + ({ mkDerivation, array, base, lib }: mkDerivation { pname = "ix-shapable"; version = "0.1.0"; @@ -19120,33 +22580,74 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Reshape multi-dimensional arrays"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "ixset-typed" = callPackage - ({ mkDerivation, base, containers, deepseq, safecopy, stdenv, syb + ({ mkDerivation, base, containers, deepseq, lib, safecopy, syb , template-haskell }: mkDerivation { pname = "ixset-typed"; - version = "0.4.0.1"; - sha256 = "a8d3655f4cebf66013363a4456287052391faad76f00f5b4001ba7d11073ac8c"; + version = "0.5"; + sha256 = "fa4752639813997acb7a090312168457a4b34ec8adcdbcffa3b9528da2c3c71e"; libraryHaskellDepends = [ base containers deepseq safecopy syb template-haskell ]; doHaddock = false; doCheck = false; description = "Efficient relational queries on Haskell sets"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "ixset-typed-binary-instance" = callPackage + ({ mkDerivation, base, binary, ixset-typed, lib }: + mkDerivation { + pname = "ixset-typed-binary-instance"; + version = "0.1.0.2"; + sha256 = "7d7b2a15861f4d69cbc180f78154da55e3005cf9adf98b149c6edfa27d60f8c9"; + libraryHaskellDepends = [ base binary ixset-typed ]; + doHaddock = false; + doCheck = false; + description = "Binary instance for ixset-typed"; + license = lib.licenses.mit; + }) {}; + "ixset-typed-conversions" = callPackage + ({ mkDerivation, base, exceptions, free, hashable, ixset-typed, lib + , unordered-containers, zipper-extra + }: + mkDerivation { + pname = "ixset-typed-conversions"; + version = "0.1.2.0"; + sha256 = "1d88a2bd0bd09fd1a744bcab401184bc18c522175893594cec6e0253918e1d96"; + libraryHaskellDepends = [ + base exceptions free hashable ixset-typed unordered-containers + zipper-extra + ]; + doHaddock = false; + doCheck = false; + description = "Conversions from ixset-typed to other containers"; + license = lib.licenses.mit; + }) {}; + "ixset-typed-hashable-instance" = callPackage + ({ mkDerivation, base, hashable, ixset-typed, lib }: + mkDerivation { + pname = "ixset-typed-hashable-instance"; + version = "0.1.0.2"; + sha256 = "dbd7fe4102462237470632ebdcea74c63c55ab673553138cd0f1ce2029968a2f"; + libraryHaskellDepends = [ base hashable ixset-typed ]; + doHaddock = false; + doCheck = false; + description = "Hashable instance for ixset-typed"; + license = lib.licenses.mit; }) {}; "jack" = callPackage ({ mkDerivation, array, base, bytestring, enumset, event-list - , explicit-exception, libjack2, midi, non-negative, semigroups - , stdenv, transformers + , explicit-exception, lib, libjack2, midi, non-negative, semigroups + , transformers }: mkDerivation { pname = "jack"; - version = "0.7.1.4"; - sha256 = "42aeb281fb62a08bbaca4b20801d55879b0688e25a92962158fbd0578bd21405"; + version = "0.7.2"; + sha256 = "9d0ded366f9b9e75020feb248690742afc52a5ed5304572dd087ebe5d1b74729"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -19158,75 +22659,127 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/JACK"; description = "Bindings for the JACK Audio Connection Kit"; - license = "GPL"; + license = lib.licenses.gpl2Only; }) {inherit (pkgs) libjack2;}; "jailbreak-cabal" = callPackage - ({ mkDerivation, base, Cabal, stdenv }: + ({ mkDerivation, base, Cabal, lib }: mkDerivation { pname = "jailbreak-cabal"; - version = "1.3.3"; - sha256 = "6bac08ad1a1ff7452a2963272f96f5de0a3df200fb3219dde6ee93e4963dd01c"; - revision = "3"; - editedCabalFile = "0f4gqssh2ayl089zzl8m5rwa66x430dg1q5hfwcfd56r6xr6wi1l"; + version = "1.3.5"; + sha256 = "8d1fce7dd9b755367f8236d91c94c5bb212a5fea9d8bc32696774cff5e7f4188"; isLibrary = false; isExecutable = true; executableHaskellDepends = [ base Cabal ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/peti/jailbreak-cabal#readme"; + homepage = "https://github.com/peti/jailbreak-cabal"; description = "Strip version restrictions from Cabal files"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "jalaali" = callPackage + ({ mkDerivation, base, lib, time }: + mkDerivation { + pname = "jalaali"; + version = "1.0.0.0"; + sha256 = "f993fd1a097489281d19978dce95324cd44b786536b37770448e4e26f7dbc041"; + libraryHaskellDepends = [ base time ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jalaali/jalaali-hs#readme"; + description = "Jalaali calendar systems"; + license = lib.licenses.mit; + }) {}; + "jira-wiki-markup" = callPackage + ({ mkDerivation, base, lib, mtl, parsec, text }: + mkDerivation { + pname = "jira-wiki-markup"; + version = "1.4.0"; + sha256 = "1c210d3c575779a7b5b974e6873b265117944746862b5bb40684903a8decca5c"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base mtl parsec text ]; + executableHaskellDepends = [ base text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/tarleb/jira-wiki-markup"; + description = "Handle Jira wiki markup"; + license = lib.licenses.mit; }) {}; "jose" = callPackage ({ mkDerivation, aeson, attoparsec, base, base64-bytestring - , bytestring, concise, containers, cryptonite, lens, memory + , bytestring, concise, containers, cryptonite, lens, lib, memory , monad-time, mtl, network-uri, QuickCheck, quickcheck-instances - , safe, semigroups, stdenv, template-haskell, text, time, unix - , unordered-containers, vector, x509 + , safe, template-haskell, text, time, unordered-containers, vector + , x509 }: mkDerivation { pname = "jose"; - version = "0.8.0.0"; - sha256 = "84e1bc59670a49430aa4197926bf0cd184cbf12f4c8f0e04b111d1823b4ae608"; + version = "0.8.4"; + sha256 = "cbdf42fb88a5718f3d6737095af9293551339d83cdfe810f20ccbd653fc94477"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ aeson attoparsec base base64-bytestring bytestring concise containers cryptonite lens memory monad-time mtl network-uri - QuickCheck quickcheck-instances safe semigroups template-haskell - text time unordered-containers vector x509 - ]; - executableHaskellDepends = [ - aeson base bytestring lens mtl semigroups text unix + QuickCheck quickcheck-instances safe template-haskell text time + unordered-containers vector x509 ]; doHaddock = false; doCheck = false; homepage = "https://github.com/frasertweedale/hs-jose"; description = "Javascript Object Signing and Encryption and JSON Web Token library"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; }) {}; "jose-jwt" = callPackage ({ mkDerivation, aeson, attoparsec, base, bytestring, cereal - , containers, cryptonite, either, memory, mtl, stdenv, text, time + , containers, cryptonite, lib, memory, mtl, text, time , transformers, transformers-compat, unordered-containers, vector }: mkDerivation { pname = "jose-jwt"; - version = "0.8.0"; - sha256 = "4fb098e8ec18ebec7ab93f229dbaca992c704d006bc0f1ca98e8f00a579db6c2"; + version = "0.9.2"; + sha256 = "c44a13c28fb416de767298d270372183dfb299b3637b08050317d2d4decd9fc7"; libraryHaskellDepends = [ aeson attoparsec base bytestring cereal containers cryptonite - either memory mtl text time transformers transformers-compat + memory mtl text time transformers transformers-compat unordered-containers vector ]; doHaddock = false; doCheck = false; homepage = "http://github.com/tekul/jose-jwt"; description = "JSON Object Signing and Encryption Library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "js-chart" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "js-chart"; + version = "2.9.4.1"; + sha256 = "0a08efdd35bd1b8f293f9163f59305f31835304b74c3e3a1a840fc94bbc9bd0e"; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jonascarpay/js-chart#readme"; + description = "Obtain minified chart.js code"; + license = lib.licenses.mit; + }) {}; + "js-dgtable" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "js-dgtable"; + version = "0.5.2"; + sha256 = "e28dd65bee8083b17210134e22e01c6349dc33c3b7bd17705973cd014e9f20ac"; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ndmitchell/js-dgtable#readme"; + description = "Obtain minified jquery.dgtable code"; + license = lib.licenses.mit; }) {}; "js-flot" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "js-flot"; version = "0.8.3"; @@ -19237,10 +22790,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/ndmitchell/js-flot#readme"; description = "Obtain minified flot code"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "js-jquery" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "js-jquery"; version = "3.3.1"; @@ -19251,93 +22804,34 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/ndmitchell/js-jquery#readme"; description = "Obtain minified jQuery code"; - license = stdenv.lib.licenses.mit; - }) {}; - "json" = callPackage - ({ mkDerivation, array, base, bytestring, containers, mtl, parsec - , pretty, stdenv, syb, text - }: - mkDerivation { - pname = "json"; - version = "0.9.3"; - sha256 = "8baf1de09983df8036fda854c4d1446f156a52d4988b863175e29af35c1d1afd"; - libraryHaskellDepends = [ - array base bytestring containers mtl parsec pretty syb text - ]; - doHaddock = false; - doCheck = false; - description = "Support for serialising Haskell to and from JSON"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "json-alt" = callPackage - ({ mkDerivation, aeson, base, stdenv }: - mkDerivation { - pname = "json-alt"; - version = "1.0.0"; - sha256 = "b850533adf93fbda01d4aee1f0116cfd67bfce17baf0a035ddc20cfe4a5d75c7"; - libraryHaskellDepends = [ aeson base ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/mgajda/json-autotype"; - description = "Union 'alternative' or Either that has untagged JSON encoding"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "json-autotype" = callPackage - ({ mkDerivation, aeson, base, bytestring, containers, filepath - , GenericPretty, hashable, json-alt, lens, mtl - , optparse-applicative, pretty, process, QuickCheck, scientific - , smallcheck, stdenv, template-haskell, text, uniplate - , unordered-containers, vector, yaml - }: - mkDerivation { - pname = "json-autotype"; - version = "3.0.1"; - sha256 = "6aae99110b29fcdbd3e7918eabc4ebf1d1f4bc1a6a94a33f0814324eba25395a"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - aeson base containers filepath GenericPretty hashable json-alt lens - mtl pretty process QuickCheck scientific smallcheck - template-haskell text uniplate unordered-containers vector - ]; - executableHaskellDepends = [ - aeson base bytestring containers filepath GenericPretty hashable - json-alt lens mtl optparse-applicative pretty process scientific - template-haskell text uniplate unordered-containers vector yaml - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/mgajda/json-autotype"; - description = "Automatic type declaration for JSON input data"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; "json-feed" = callPackage - ({ mkDerivation, aeson, base, bytestring, mime-types, network-uri - , stdenv, tagsoup, text, time + ({ mkDerivation, aeson, base, bytestring, lib, mime-types + , network-uri, tagsoup, text, time }: mkDerivation { pname = "json-feed"; - version = "1.0.5"; - sha256 = "1a17437637404bc71cb1d3c1ad82bf26fc5b8c27cd71673a3b0f2a72b185c89f"; + version = "1.0.13"; + sha256 = "256a02be4c0bb939299d10d5d6e66a59f5acb4e89a9b24f7345df53331da9893"; libraryHaskellDepends = [ aeson base bytestring mime-types network-uri tagsoup text time ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/tfausak/json-feed#readme"; description = "JSON Feed"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "json-rpc" = callPackage ({ mkDerivation, aeson, attoparsec, base, bytestring, conduit - , conduit-extra, deepseq, hashable, monad-logger, mtl, QuickCheck - , stdenv, stm-conduit, text, time, unliftio, unordered-containers - , vector + , conduit-extra, deepseq, hashable, lib, monad-logger, mtl + , QuickCheck, stm-conduit, text, time, unliftio + , unordered-containers, vector }: mkDerivation { pname = "json-rpc"; - version = "1.0.0"; - sha256 = "73b1f10ebccbd8860f10da5362399dc15a5b1b4da73e83f4c125239e06e6f85a"; + version = "1.0.3"; + sha256 = "0f988a6a87683ce3d68ec10351d281a9fc9ad5e674831a8aa7b167accb84c804"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -19352,36 +22846,14 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/xenog/json-rpc.git#readme"; + homepage = "https://github.com/jprupp/json-rpc.git#readme"; description = "Fully-featured JSON-RPC 2.0 library"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.mit; }) {}; - "json-rpc-client" = callPackage - ({ mkDerivation, aeson, base, bytestring, json-rpc-server, mtl - , stdenv, text, unordered-containers, vector, vector-algorithms - }: - mkDerivation { - pname = "json-rpc-client"; - version = "0.2.5.0"; - sha256 = "5349f5c0b0fa8f6c5433152d6effc10846cfb3480e78c5aa99adb7540bcff49c"; - revision = "9"; - editedCabalFile = "04b65m8lhk2g2d5x5i637ff3wkgvf4z6dhn5x1pizsj9y3aq35zm"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - aeson base bytestring json-rpc-server mtl text unordered-containers - vector vector-algorithms - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/grayjay/json-rpc-client"; - description = "JSON-RPC 2.0 on the client side."; - license = stdenv.lib.licenses.mit; - }) {}; - "json-rpc-generic" = callPackage - ({ mkDerivation, aeson, aeson-generic-compat, base, containers - , dlist, scientific, stdenv, text, transformers - , unordered-containers, vector + "json-rpc-generic" = callPackage + ({ mkDerivation, aeson, aeson-generic-compat, base, containers + , dlist, lib, scientific, text, transformers, unordered-containers + , vector }: mkDerivation { pname = "json-rpc-generic"; @@ -19395,31 +22867,57 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/khibino/haskell-json-rpc-generic"; description = "Generic encoder and decode for JSON-RPC"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "json-rpc-server" = callPackage - ({ mkDerivation, aeson, base, bytestring, deepseq, mtl, stdenv - , text, unordered-containers, vector + "jsonifier" = callPackage + ({ mkDerivation, base, bytestring, lib, ptr-poker, scientific, text }: mkDerivation { - pname = "json-rpc-server"; - version = "0.2.6.0"; - sha256 = "169e9997734bd1d7d07a13b5ae0223d5363c43de93b0d5fbb845a598f9eaccf5"; - revision = "6"; - editedCabalFile = "1rfabr679pk605v141gm0ynbp3l6x87s3ip3wa49lwnpab495mxs"; - isLibrary = true; - isExecutable = true; + pname = "jsonifier"; + version = "0.1.1"; + sha256 = "8eaf784012290b835e983a6296d1f90effd6b12d81c4e93b3b7d6a699b128927"; + libraryHaskellDepends = [ + base bytestring ptr-poker scientific text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/nikita-volkov/jsonifier"; + description = "Fast and simple JSON encoding toolkit"; + license = lib.licenses.mit; + }) {}; + "jsonpath" = callPackage + ({ mkDerivation, aeson, attoparsec, base, lib, text + , unordered-containers, vector + }: + mkDerivation { + pname = "jsonpath"; + version = "0.2.0.0"; + sha256 = "7bcb12435c89b4471976f358a559636b785a71082485d26ab77dc7f1d49d4bbd"; libraryHaskellDepends = [ - aeson base bytestring deepseq mtl text unordered-containers vector + aeson attoparsec base text unordered-containers vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/grayjay/json-rpc-server"; - description = "JSON-RPC 2.0 on the server side."; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/akshaymankar/jsonpath-hs#readme"; + description = "Library to parse and execute JSONPath"; + license = lib.licenses.bsd3; + }) {}; + "junit-xml" = callPackage + ({ mkDerivation, base, lib, text, xml-conduit }: + mkDerivation { + pname = "junit-xml"; + version = "0.1.0.2"; + sha256 = "046ca1b2450163adf41134100123c8f5158deeb619b8cd90b5ad6e9e231aa76a"; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ base text xml-conduit ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jwoudenberg/junit-xml#readme"; + description = "Producing JUnit-style XML test reports"; + license = lib.licenses.bsd3; }) {}; "justified-containers" = callPackage - ({ mkDerivation, base, containers, roles, stdenv }: + ({ mkDerivation, base, containers, lib, roles }: mkDerivation { pname = "justified-containers"; version = "0.3.0.0"; @@ -19429,17 +22927,40 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/matt-noonan/justified-containers"; description = "Keyed container types with type-checked proofs of key presence"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; + }) {}; + "jwt" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers, cryptonite + , http-types, lib, memory, network-uri, scientific, semigroups + , text, time, unordered-containers, vector, x509, x509-store + }: + mkDerivation { + pname = "jwt"; + version = "0.10.0"; + sha256 = "bc1c7b18ba3366dd537f0ccd46e887e5892591a2a60b5ccbc15289ea70c52ea8"; + revision = "2"; + editedCabalFile = "1ld5dh4x3sb28416bk3k39k46vmx1s7agk17v7cb5cxam4hj3c1c"; + libraryHaskellDepends = [ + aeson base bytestring containers cryptonite http-types memory + network-uri scientific semigroups text time unordered-containers + vector x509 x509-store + ]; + doHaddock = false; + doCheck = false; + homepage = "https://bitbucket.org/puffnfresh/haskell-jwt"; + description = "JSON Web Token (JWT) decoding and encoding"; + license = lib.licenses.mit; }) {}; "kan-extensions" = callPackage ({ mkDerivation, adjunctions, array, base, comonad, containers - , contravariant, distributive, free, invariant, mtl, profunctors - , semigroupoids, stdenv, tagged, transformers, transformers-compat + , contravariant, distributive, free, invariant, lib, mtl + , profunctors, semigroupoids, tagged, transformers + , transformers-compat }: mkDerivation { pname = "kan-extensions"; - version = "5.2"; - sha256 = "6b727e586f744b96529415eeabc745dfe05feea61f6b6bad90c224c879f4dbd3"; + version = "5.2.2"; + sha256 = "3bf3ce4cacf9c57c03e9a1c36ecb1baf5d8356730853a2592d2112d1248498a0"; libraryHaskellDepends = [ adjunctions array base comonad containers contravariant distributive free invariant mtl profunctors semigroupoids tagged @@ -19449,19 +22970,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/kan-extensions/"; description = "Kan extensions, Kan lifts, the Yoneda lemma, and (co)density (co)monads"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "kanji" = callPackage ({ mkDerivation, aeson, aeson-pretty, base, containers, deepseq - , hashable, microlens, microlens-aeson, optparse-applicative - , stdenv, text, transformers + , hashable, lib, microlens, microlens-aeson, optparse-applicative + , text, transformers }: mkDerivation { pname = "kanji"; - version = "3.4.0"; - sha256 = "d945ded925216b8f260c62c2fce593631d772bffa1f203550a6b9750ca3a81f1"; - revision = "2"; - editedCabalFile = "1bcc3kh6kndmkqi3vaxp27mg1qb7xbg1h8pgjc1kk1iawnhl930j"; + version = "3.4.1"; + sha256 = "59500a92369df84e3d8810ae8f037ce82ec550fe0e50759812d4a3712cafffdd"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -19475,22 +22994,20 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/fosskers/kanji"; description = "Perform 漢字検定 (Japan Kanji Aptitude Test) level analysis on Japanese Kanji"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "katip" = callPackage ({ mkDerivation, aeson, async, auto-update, base, bytestring - , containers, either, hostname, microlens, microlens-th + , containers, either, hostname, lib, microlens, microlens-th , monad-control, mtl, old-locale, resourcet, safe-exceptions - , scientific, semigroups, stdenv, stm, string-conv - , template-haskell, text, time, transformers, transformers-base - , transformers-compat, unix, unliftio-core, unordered-containers + , scientific, semigroups, stm, string-conv, template-haskell, text + , time, transformers, transformers-base, transformers-compat, unix + , unliftio-core, unordered-containers }: mkDerivation { pname = "katip"; - version = "0.7.0.0"; - sha256 = "0ba53e13cfa9e717c3e040f0c858f0d1de1417cffaf670542d546951d21885fc"; - revision = "1"; - editedCabalFile = "1lzla1iv5ll9iks5xh8399vs2mjxb33pbdg115kqbq9r5z3h84qp"; + version = "0.8.5.0"; + sha256 = "53beca4f7a3d81c8da7829b91a660e9c1f5ea12cef7a54c2b6762eec48d75fce"; libraryHaskellDepends = [ aeson async auto-update base bytestring containers either hostname microlens microlens-th monad-control mtl old-locale resourcet @@ -19502,11 +23019,29 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/Soostone/katip"; description = "A structured logging framework"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "katip-logstash" = callPackage + ({ mkDerivation, aeson, base, katip, lib, logstash, retry, stm + , stm-chans, text, transformers, unliftio + }: + mkDerivation { + pname = "katip-logstash"; + version = "0.1.0.0"; + sha256 = "d4a808b745c574efa9bdf660e93cd9a86875703bf2a37fcda77396b8fa123c9b"; + libraryHaskellDepends = [ + aeson base katip logstash retry stm stm-chans text transformers + unliftio + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/mbg/logstash#readme"; + description = "Logstash backend for katip"; + license = lib.licenses.mit; }) {}; "kawhi" = callPackage ({ mkDerivation, aeson, base, bytestring, exceptions, http-client - , http-conduit, http-types, mtl, safe, scientific, stdenv, text + , http-conduit, http-types, lib, mtl, safe, scientific, text }: mkDerivation { pname = "kawhi"; @@ -19520,10 +23055,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/thunky-monk/kawhi"; description = "stats.NBA.com library"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "kazura-queue" = callPackage - ({ mkDerivation, atomic-primops, base, primitive, stdenv }: + ({ mkDerivation, atomic-primops, base, lib, primitive }: mkDerivation { pname = "kazura-queue"; version = "0.1.0.4"; @@ -19533,10 +23068,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/asakamirai/kazura-queue#readme"; description = "Fast concurrent queues much inspired by unagi-chan"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "kdt" = callPackage - ({ mkDerivation, base, deepseq, deepseq-generics, heap, stdenv }: + ({ mkDerivation, base, deepseq, deepseq-generics, heap, lib }: mkDerivation { pname = "kdt"; version = "0.2.4"; @@ -19546,18 +23081,30 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/giogadi/kdt"; description = "Fast and flexible k-d trees for various types of point queries"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "keep-alive" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "keep-alive"; + version = "0.2.0.0"; + sha256 = "53a4e75097a309baf872741217969585476ce89ce55c84f2a7cdf83152a875c2"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/3kyro/keep-alive#readme"; + description = "TCP keep alive implementation"; + license = lib.licenses.bsd3; }) {}; "keycode" = callPackage - ({ mkDerivation, base, containers, ghc-prim, stdenv - , template-haskell + ({ mkDerivation, base, containers, ghc-prim, lib, template-haskell }: mkDerivation { pname = "keycode"; version = "0.2.2"; sha256 = "56f9407cf182b01e5f0fda80f569ff629f37d894f75ef28b6b8af3024343d310"; - revision = "3"; - editedCabalFile = "18dgbpf3xwdm3x9j63vsr5q7l028qvifgc6jmjf1ar4p2wv1fzz0"; + revision = "7"; + editedCabalFile = "1xfhm486mgkf744nbx94aw0b1lraj1yv29c57rbx1c2b84v2z8k2"; libraryHaskellDepends = [ base containers ghc-prim template-haskell ]; @@ -19565,17 +23112,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/RyanGlScott/keycode"; description = "Maps web browser keycodes to their corresponding keyboard keys"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "keys" = callPackage ({ mkDerivation, array, base, comonad, containers, free, hashable - , semigroupoids, semigroups, stdenv, tagged, transformers + , lib, semigroupoids, semigroups, tagged, transformers , transformers-compat, unordered-containers }: mkDerivation { pname = "keys"; - version = "3.12.1"; - sha256 = "7fcea48187df82c02c159dea07a581cddf371023e6a3c34de7fa69a8ef2315fb"; + version = "3.12.3"; + sha256 = "d51e4288a3cc89c5be3327a499212a651549a58af78d0dfeb2cd80e19ce66646"; libraryHaskellDepends = [ array base comonad containers free hashable semigroupoids semigroups tagged transformers transformers-compat @@ -19585,71 +23132,63 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/keys/"; description = "Keyed functors and containers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "ki" = callPackage + ({ mkDerivation, base, containers, lib, stm }: + mkDerivation { + pname = "ki"; + version = "0.2.0.1"; + sha256 = "d9b32b9dbbd58577157cdfffee3fced23de4ae8fa9185975835cc03ec97eb5db"; + libraryHaskellDepends = [ base containers stm ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/mitchellwrosen/ki"; + description = "A lightweight, structured-concurrency library"; + license = lib.licenses.bsd3; }) {}; "kind-apply" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "kind-apply"; - version = "0.3.0.0"; - sha256 = "078bcb06aeb6b0942b5065c96ee0a4a242ed8a78ee1753e296570379dca497cc"; + version = "0.3.2.0"; + sha256 = "98dd45968f777f08aa4e6a8fe20dfa0b345ab474b92ac37835503589a2930073"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; description = "Utilities to work with lists of types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "kind-generics" = callPackage - ({ mkDerivation, base, kind-apply, stdenv }: + ({ mkDerivation, base, kind-apply, lib }: mkDerivation { pname = "kind-generics"; - version = "0.3.0.0"; - sha256 = "1df923a4a223c8c3c69135bd4be65bab6d6404cad026d90539fd350ab98c7976"; + version = "0.4.1.0"; + sha256 = "dde6ba1f5aef32fceaae6e0466ce9cb2a3822beade59e0efa2bd0ebd7389aed1"; libraryHaskellDepends = [ base kind-apply ]; doHaddock = false; doCheck = false; description = "Generic programming in GHC style for arbitrary kinds and GADTs"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "kind-generics-th" = callPackage - ({ mkDerivation, base, kind-generics, stdenv, template-haskell - , th-abstraction + ({ mkDerivation, base, ghc-prim, kind-generics, lib + , template-haskell, th-abstraction }: mkDerivation { pname = "kind-generics-th"; - version = "0.1.0.0"; - sha256 = "ed6f8f2ff36b2b4535a77f6b10d3ee54c3df261367989eac3ebe46b43c117db5"; + version = "0.2.2.2"; + sha256 = "c42658e56dcdbe0b24777ba84296e0537338ba63d5d77f723178cbf2373fffd1"; libraryHaskellDepends = [ - base kind-generics template-haskell th-abstraction + base ghc-prim kind-generics template-haskell th-abstraction ]; doHaddock = false; doCheck = false; description = "Template Haskell support for generating `GenericK` instances"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "kleene" = callPackage - ({ mkDerivation, base, base-compat-batteries, containers, lattices - , MemoTrie, QuickCheck, range-set-list, regex-applicative, stdenv - , step-function, text, transformers - }: - mkDerivation { - pname = "kleene"; - version = "0"; - sha256 = "c652aecfb2a42fec6b7cc0135fe95764a27fe099c6934071ef5fa55075cd0b02"; - revision = "1"; - editedCabalFile = "1izdmr7a2d7qssnj732m2qc02inm3hrc882x9nyvz68648pvwwsx"; - libraryHaskellDepends = [ - base base-compat-batteries containers lattices MemoTrie QuickCheck - range-set-list regex-applicative step-function text transformers - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/phadej/kleene"; - description = "Kleene algebra"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "kmeans" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "kmeans"; version = "0.1.3"; @@ -19658,11 +23197,24 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "K-means clustering algorithm"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "koji" = callPackage + ({ mkDerivation, base, haxr, lib, mtl }: + mkDerivation { + pname = "koji"; + version = "0.0.2"; + sha256 = "0d1ff84f700558574ab7145ede935352a849e9035cd35e745a208f424429f9fa"; + libraryHaskellDepends = [ base haxr mtl ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/juhp/koji-hs"; + description = "Koji buildsystem XML-RPC API bindings"; + license = lib.licenses.gpl2Only; }) {}; "koofr-client" = callPackage ({ mkDerivation, aeson, base, bytestring, filepath, http-client - , http-client-tls, http-types, mtl, stdenv + , http-client-tls, http-types, lib, mtl }: mkDerivation { pname = "koofr-client"; @@ -19678,28 +23230,55 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/edofic/koofr-api-hs"; description = "Client to Koofr API"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "kraken" = callPackage - ({ mkDerivation, aeson, base, bytestring, http-client - , http-client-tls, mtl, stdenv + "krank" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers, http-client + , http-types, lib, lifted-async, mtl, optparse-applicative + , pcre-heavy, pretty-terminal, PyF, req, safe-exceptions, text + , unordered-containers }: mkDerivation { - pname = "kraken"; - version = "0.1.0"; - sha256 = "335ce7cb85f7d3ed71eb067ad9642d13d2ca1d62ce8670596c8b69aacc27828a"; - revision = "2"; - editedCabalFile = "141qx2fb3dimv20qsl2q1bagwcn9i0r72z2ha1w7191m557in319"; + pname = "krank"; + version = "0.2.2"; + sha256 = "dcec2bcba8940667c8fee6d5520b5ef74767cffb51009e923ec026cbeeda8683"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson base bytestring containers http-client http-types + lifted-async mtl pcre-heavy pretty-terminal PyF req safe-exceptions + text unordered-containers + ]; + executableHaskellDepends = [ + base containers mtl optparse-applicative pcre-heavy pretty-terminal + PyF text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/guibou/krank"; + description = "Krank checks your code source comments for important markers"; + license = lib.licenses.bsd3; + }) {}; + "kubernetes-webhook-haskell" = callPackage + ({ mkDerivation, aeson, base, base64-bytestring, binary, bytestring + , lib, text, unordered-containers + }: + mkDerivation { + pname = "kubernetes-webhook-haskell"; + version = "0.2.0.3"; + sha256 = "019385344171c916e8464495b2f0fb0f3ad3fdffed7573ff8f56e81565196cf7"; libraryHaskellDepends = [ - aeson base bytestring http-client http-client-tls mtl + aeson base base64-bytestring binary bytestring text + unordered-containers ]; doHaddock = false; doCheck = false; - description = "Kraken.io API client"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/EarnestResearch/kubernetes-webhook-haskell#readme"; + description = "Create Kubernetes Admission Webhooks in Haskell"; + license = lib.licenses.mit; }) {}; "l10n" = callPackage - ({ mkDerivation, base, stdenv, text, time }: + ({ mkDerivation, base, lib, text, time }: mkDerivation { pname = "l10n"; version = "0.1.0.1"; @@ -19709,10 +23288,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/louispan/l10n#readme"; description = "Enables providing localization as typeclass instances in separate files"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "labels" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { pname = "labels"; version = "0.3.3"; @@ -19722,41 +23301,41 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/chrisdone/labels#readme"; description = "Anonymous records via named tuples"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "lackey" = callPackage - ({ mkDerivation, base, servant, servant-foreign, stdenv, text }: + ({ mkDerivation, base, lib, servant, servant-foreign, text }: mkDerivation { pname = "lackey"; - version = "1.0.7"; - sha256 = "8618f010d34ddc7a077198e6afc5ed3fcbcac4d3aaf3c916e9e43aac1ba92059"; + version = "1.0.15"; + sha256 = "3cafd334ae928fa0c82e36e73d74ad02569c0e0d2eac3c96f4e7ab57cea59c90"; libraryHaskellDepends = [ base servant servant-foreign text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/tfausak/lackey#readme"; description = "Generate Ruby clients from Servant APIs"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "lambdabot-core" = callPackage ({ mkDerivation, base, binary, bytestring, containers , dependent-map, dependent-sum, dependent-sum-template, directory - , edit-distance, filepath, haskeline, hslogger, HTTP, lifted-base - , monad-control, mtl, network, parsec, prim-uniq, random, random-fu - , random-source, regex-tdfa, SafeSemaphore, split, stdenv, syb - , template-haskell, time, transformers, transformers-base, unix - , utf8-string, zlib + , edit-distance, exceptions, filepath, haskeline, hslogger, HTTP + , lib, lifted-base, monad-control, mtl, network, network-bsd + , parsec, prim-uniq, random, random-fu, random-source, regex-tdfa + , SafeSemaphore, split, syb, template-haskell, time, transformers + , transformers-base, unix, utf8-string, zlib }: mkDerivation { pname = "lambdabot-core"; - version = "5.1.0.4"; - sha256 = "f33bcef0e390c50569613696fa2dad8e5b5f6407a981e5e90f1a5c770807d7b2"; + version = "5.3.0.1"; + sha256 = "5e8d9c51b743eb9cc615c53595a33dcefe58e1e537a08b66d087dd371c32bd17"; libraryHaskellDepends = [ base binary bytestring containers dependent-map dependent-sum - dependent-sum-template directory edit-distance filepath haskeline - hslogger HTTP lifted-base monad-control mtl network parsec - prim-uniq random random-fu random-source regex-tdfa SafeSemaphore - split syb template-haskell time transformers transformers-base unix - utf8-string zlib + dependent-sum-template directory edit-distance exceptions filepath + haskeline hslogger HTTP lifted-base monad-control mtl network + network-bsd parsec prim-uniq random random-fu random-source + regex-tdfa SafeSemaphore split syb template-haskell time + transformers transformers-base unix utf8-string zlib ]; doHaddock = false; doCheck = false; @@ -19764,145 +23343,119 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; description = "Lambdabot core functionality"; license = "GPL"; }) {}; - "lambdabot-irc-plugins" = callPackage - ({ mkDerivation, base, bytestring, containers, directory, filepath - , lambdabot-core, lifted-base, mtl, network, SafeSemaphore, split - , stdenv, time - }: - mkDerivation { - pname = "lambdabot-irc-plugins"; - version = "5.1.0.4"; - sha256 = "4e3d5b8e464c1ccbf12c5a255785c07cdd7208943d2cdeab4a537b899b9e4c4f"; - libraryHaskellDepends = [ - base bytestring containers directory filepath lambdabot-core - lifted-base mtl network SafeSemaphore split time - ]; - doHaddock = false; - doCheck = false; - homepage = "https://wiki.haskell.org/Lambdabot"; - description = "IRC plugins for lambdabot"; - license = "GPL"; - }) {}; "lame" = callPackage - ({ mkDerivation, base, bytestring, data-default-class, directory - , exceptions, filepath, mp3lame, stdenv, text, transformers, wave + ({ mkDerivation, base, bytestring, directory, exceptions, filepath + , lib, mp3lame, text, transformers, wave }: mkDerivation { pname = "lame"; - version = "0.1.1"; - sha256 = "b36009a35c02f7f18b4ba91d9ead7e5b47aef4eb5c0d014d4d60dd0bddfd6548"; - revision = "4"; - editedCabalFile = "0r364limqm570a8xd82wwpcvmcx2j7nfndg5kad022vz2v5n0smz"; + version = "0.2.0"; + sha256 = "578b5b8bff09bcf3cde8f26026cef02633aa5d93a72ab007d5cd3967951a18af"; + revision = "1"; + editedCabalFile = "1czjga37b56xs6jrylsf5gip5srmlfg2982k96l5w4300sj8ricz"; enableSeparateDataOutput = true; libraryHaskellDepends = [ - base bytestring data-default-class directory exceptions filepath - text transformers wave + base bytestring directory exceptions filepath text transformers + wave ]; librarySystemDepends = [ mp3lame ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mrkkrp/lame"; description = "Fairly complete high-level binding to LAME encoder"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) mp3lame;}; + "language-avro" = callPackage + ({ mkDerivation, avro, base, containers, directory, filepath, lib + , megaparsec, text, vector + }: + mkDerivation { + pname = "language-avro"; + version = "0.1.3.1"; + sha256 = "14e01f37f7c7079219edd5d02a8d8cfda9641a8ae5a4c9dc69d9e9f00301a42c"; + libraryHaskellDepends = [ + avro base containers directory filepath megaparsec text vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/kutyel/avro-parser-haskell#readme"; + description = "Language definition and parser for AVRO files"; + license = lib.licenses.asl20; + }) {}; + "language-bash" = callPackage + ({ mkDerivation, base, lib, parsec, prettyprinter, transformers }: + mkDerivation { + pname = "language-bash"; + version = "0.9.2"; + sha256 = "6628c0c6a43bf035703f02226bbaf283f723d88f74522c12e997c23e3703745e"; + libraryHaskellDepends = [ base parsec prettyprinter transformers ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/knrafto/language-bash/"; + description = "Parsing and pretty-printing Bash shell scripts"; + license = lib.licenses.bsd3; + }) {}; "language-c" = callPackage ({ mkDerivation, alex, array, base, bytestring, containers, deepseq - , directory, filepath, happy, pretty, process, stdenv, syb + , directory, filepath, happy, lib, mtl, pretty, process }: mkDerivation { pname = "language-c"; - version = "0.8.2"; - sha256 = "b729d3b2263b0f029a66c37ae1c05b86b68bad1cde6c0b407bfd5201b91fce15"; - revision = "1"; - editedCabalFile = "1xg49j4bykgdm6l14m65wyz8r3s4v4dqc7a9zjcsr12ffkiv8nam"; + version = "0.9.0.1"; + sha256 = "d44cbb963fdea53ee9850af767a01137666044702938b57fda0c17644719d207"; libraryHaskellDepends = [ - array base bytestring containers deepseq directory filepath pretty - process syb + array base bytestring containers deepseq directory filepath mtl + pretty process ]; libraryToolDepends = [ alex happy ]; doHaddock = false; doCheck = false; homepage = "http://visq.github.io/language-c/"; description = "Analysis and generation of C code"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "language-c-quote" = callPackage ({ mkDerivation, alex, array, base, bytestring, containers , exception-mtl, exception-transformers, filepath, happy - , haskell-src-meta, mainland-pretty, mtl, srcloc, stdenv, syb - , symbol, template-haskell + , haskell-src-meta, lib, mainland-pretty, mtl, srcloc, syb + , template-haskell }: mkDerivation { pname = "language-c-quote"; - version = "0.12.2"; - sha256 = "eb319b4d1154f88f4d0f8817c85efad34c14d774c47d4c9193c89c9064cb8695"; - revision = "1"; - editedCabalFile = "099w1lln1vm000sf06wrmq6gya5sx2w4flrlwqz2c8wwvv8c9j9h"; + version = "0.13"; + sha256 = "cd388db0a34dc10c3d169094b147a58469ff924d43374c84cbe2699488f95d09"; libraryHaskellDepends = [ array base bytestring containers exception-mtl exception-transformers filepath haskell-src-meta mainland-pretty - mtl srcloc syb symbol template-haskell + mtl srcloc syb template-haskell ]; libraryToolDepends = [ alex happy ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mainland/language-c-quote"; description = "C/CUDA/OpenCL/Objective-C quasiquoting library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "language-docker" = callPackage - ({ mkDerivation, base, bytestring, containers, free, megaparsec - , mtl, prettyprinter, split, stdenv, template-haskell, text - , th-lift, time + ({ mkDerivation, base, bytestring, containers, data-default-class + , lib, megaparsec, prettyprinter, split, text, time }: mkDerivation { pname = "language-docker"; - version = "8.0.0"; - sha256 = "f64c31a468ad70d6ee5f4c6747c7586883535bb9313c84b53fe100a6edf4f903"; + version = "10.0.1"; + sha256 = "46d933293f860005ae74975274b8924dae19f916925e6ae5bffc8c1981aefea6"; libraryHaskellDepends = [ - base bytestring containers free megaparsec mtl prettyprinter split - template-haskell text th-lift time + base bytestring containers data-default-class megaparsec + prettyprinter split text time ]; doHaddock = false; doCheck = false; homepage = "https://github.com/hadolint/language-docker#readme"; description = "Dockerfile parser, pretty-printer and embedded DSL"; - license = stdenv.lib.licenses.gpl3; - }) {}; - "language-ecmascript" = callPackage - ({ mkDerivation, ansi-wl-pprint, base, charset, containers - , data-default-class, Diff, mtl, parsec, QuickCheck, stdenv - , template-haskell, uniplate - }: - mkDerivation { - pname = "language-ecmascript"; - version = "0.19"; - sha256 = "570a4b7bdebf4532e9c059f2afa7575247be2b7f539361995297308c387c658f"; - libraryHaskellDepends = [ - ansi-wl-pprint base charset containers data-default-class Diff mtl - parsec QuickCheck template-haskell uniplate - ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/jswebtools/language-ecmascript"; - description = "JavaScript parser and pretty-printer library"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "language-haskell-extract" = callPackage - ({ mkDerivation, base, regex-posix, stdenv, template-haskell }: - mkDerivation { - pname = "language-haskell-extract"; - version = "0.2.4"; - sha256 = "14da16e56665bf971723e0c5fd06dbb7cc30b4918cf8fb5748570785ded1acdb"; - libraryHaskellDepends = [ base regex-posix template-haskell ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/finnsson/template-helper"; - description = "Module to automatically extract functions from the local code"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.gpl3Only; }) {}; "language-java" = callPackage - ({ mkDerivation, alex, array, base, parsec, pretty, stdenv }: + ({ mkDerivation, alex, array, base, lib, parsec, pretty }: mkDerivation { pname = "language-java"; version = "0.2.9"; @@ -19915,16 +23468,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/vincenthz/language-java"; description = "Java source manipulation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "language-javascript" = callPackage ({ mkDerivation, alex, array, base, blaze-builder, bytestring - , containers, happy, mtl, stdenv, text, utf8-string + , containers, happy, lib, mtl, text, utf8-string }: mkDerivation { pname = "language-javascript"; - version = "0.6.0.11"; - sha256 = "d4756e9bc9a180cb93701e964a3157a03d4db4c7cb5a7b6b196067e587cc6143"; + version = "0.7.1.0"; + sha256 = "d1a036aa4c747fa7a347e78dc6d3609a3d51dc28580ff6b897a27646ca7ad168"; libraryHaskellDepends = [ array base blaze-builder bytestring containers mtl text utf8-string ]; @@ -19933,90 +23486,160 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/erikd/language-javascript"; description = "Parser for JavaScript"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "language-nix" = callPackage - ({ mkDerivation, base, base-compat, Cabal, deepseq, lens, pretty - , QuickCheck, stdenv + ({ mkDerivation, base, deepseq, lens, lib, parsec-class, pretty + , QuickCheck }: mkDerivation { pname = "language-nix"; - version = "2.1.0.1"; - sha256 = "f0147300724ac39ce388cd6cd717ac3ccc6ed1884ffaafebb18d0f3021e01acf"; - revision = "1"; - editedCabalFile = "1zv12p4ralrks0517zs52rzmzmsxxkcxkqz7zijfgcsvh6bsmafi"; + version = "2.2.0"; + sha256 = "fd67425268707de245e4b1f5dfee61e091c417106c95dbbe188abc16c23800d3"; libraryHaskellDepends = [ - base base-compat Cabal deepseq lens pretty QuickCheck + base deepseq lens parsec-class pretty QuickCheck ]; doHaddock = false; doCheck = false; homepage = "https://github.com/peti/language-nix#readme"; - description = "Data types and useful functions to represent and manipulate the Nix language"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "language-puppet" = callPackage - ({ mkDerivation, aeson, ansi-wl-pprint, async, attoparsec, base - , base16-bytestring, bytestring, case-insensitive, containers - , cryptonite, directory, filecache, filepath, formatting, Glob - , hashable, hruby, hslogger, http-api-data, http-client, lens - , lens-aeson, megaparsec, memory, mtl, operational - , optparse-applicative, parsec, parser-combinators, pcre-utils - , protolude, random, regex-pcre-builtin, scientific, servant - , servant-client, split, stdenv, stm, strict-base-types, text, time - , transformers, unix, unordered-containers, vector, yaml - }: - mkDerivation { - pname = "language-puppet"; - version = "1.4.2"; - sha256 = "18976ee3ada02c828342c4194c94e84fb5ee775ad4483c2943a4222a5928b12d"; + description = "Data types and functions to represent the Nix language"; + license = lib.licenses.bsd3; + }) {}; + "language-protobuf" = callPackage + ({ mkDerivation, base, lib, megaparsec, text }: + mkDerivation { + pname = "language-protobuf"; + version = "1.0.1"; + sha256 = "e24368fb1b02d2b05eaca73d5e5a30824dea391374351242c4ba03319c87b1f3"; + libraryHaskellDepends = [ base megaparsec text ]; + doHaddock = false; + doCheck = false; + description = "Language definition and parser for Protocol Buffers"; + license = lib.licenses.asl20; + }) {}; + "language-python" = callPackage + ({ mkDerivation, alex, array, base, containers, happy, lib + , monads-tf, pretty, transformers, utf8-string + }: + mkDerivation { + pname = "language-python"; + version = "0.5.8"; + sha256 = "224e5abcd92e2aa78ca268c37db9c4a4f360d93d2f31b0e914a82468f767c3d5"; + libraryHaskellDepends = [ + array base containers monads-tf pretty transformers utf8-string + ]; + libraryToolDepends = [ alex happy ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/bjpop/language-python"; + description = "Parsing and pretty printing of Python code"; + license = lib.licenses.bsd3; + }) {}; + "language-thrift" = callPackage + ({ mkDerivation, ansi-wl-pprint, base, containers, lib, megaparsec + , scientific, semigroups, text, transformers + }: + mkDerivation { + pname = "language-thrift"; + version = "0.12.0.0"; + sha256 = "14364533aa63dcf4195d031e31e5503ed5a49ffdf915634c1fcced7fc600fba8"; + libraryHaskellDepends = [ + ansi-wl-pprint base containers megaparsec scientific semigroups + text transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/abhinav/language-thrift#readme"; + description = "Parser and pretty printer for the Thrift IDL format"; + license = lib.licenses.bsd3; + }) {}; + "lapack" = callPackage + ({ mkDerivation, base, blas-ffi, blaze-html, boxes, comfort-array + , deepseq, fixed-length, guarded-allocation, hyper, lapack-ffi + , lazyio, lib, netlib-ffi, non-empty, semigroups, text, tfp + , transformers, utility-ht + }: + mkDerivation { + pname = "lapack"; + version = "0.3.2"; + sha256 = "c0973f630a7991829d36687f7c024435f530efb3f411a1ea50eee2d1219a098a"; + revision = "1"; + editedCabalFile = "1ji3cj8ggj6prxcn9z0678x1i5j25cwxj3bxnv4s9nn8qayyflpn"; isLibrary = true; isExecutable = true; - enableSeparateDataOutput = true; libraryHaskellDepends = [ - aeson ansi-wl-pprint attoparsec base base16-bytestring bytestring - case-insensitive containers cryptonite directory filecache filepath - formatting hashable hruby hslogger http-api-data http-client lens - lens-aeson megaparsec memory mtl operational parsec - parser-combinators pcre-utils protolude random regex-pcre-builtin - scientific servant servant-client split stm strict-base-types text - time transformers unix unordered-containers vector yaml + base blas-ffi blaze-html boxes comfort-array deepseq fixed-length + guarded-allocation hyper lapack-ffi lazyio netlib-ffi non-empty + semigroups text tfp transformers utility-ht ]; - executableHaskellDepends = [ - aeson ansi-wl-pprint async base bytestring containers Glob hslogger - http-client lens mtl optparse-applicative regex-pcre-builtin - strict-base-types text transformers unordered-containers vector - yaml + doHaddock = false; + doCheck = false; + homepage = "https://hub.darcs.net/thielema/lapack/"; + description = "Numerical Linear Algebra using LAPACK"; + license = lib.licenses.bsd3; + }) {}; + "lapack-carray" = callPackage + ({ mkDerivation, base, carray, lapack-ffi, lib, netlib-carray + , netlib-ffi, storable-complex, transformers + }: + mkDerivation { + pname = "lapack-carray"; + version = "0.0.3"; + sha256 = "510ffbbe349add60dd147181a7517f57071b71f7691e299255b95433dbe48dd0"; + libraryHaskellDepends = [ + base carray lapack-ffi netlib-carray netlib-ffi storable-complex + transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "http://hub.darcs.net/thielema/lapack-carray/"; + description = "Auto-generated interface to Fortran LAPACK via CArrays"; + license = lib.licenses.bsd3; + }) {}; + "lapack-comfort-array" = callPackage + ({ mkDerivation, base, comfort-array, lapack-ffi, lib + , netlib-comfort-array, netlib-ffi, storable-complex, transformers + }: + mkDerivation { + pname = "lapack-comfort-array"; + version = "0.0.0.1"; + sha256 = "01d2c8c33ab89193e2531db0fdc46433885b335eb86552ea5f5a9c83c75ac94e"; + libraryHaskellDepends = [ + base comfort-array lapack-ffi netlib-comfort-array netlib-ffi + storable-complex transformers ]; doHaddock = false; doCheck = false; - homepage = "http://lpuppet.banquise.net/"; - description = "Tools to parse and evaluate the Puppet DSL"; - license = stdenv.lib.licenses.bsd3; + homepage = "http://hub.darcs.net/thielema/lapack-comfort-array/"; + description = "Auto-generated interface to Fortran LAPACK via comfort-array"; + license = lib.licenses.bsd3; }) {}; "lapack-ffi" = callPackage - ({ mkDerivation, base, liblapack, netlib-ffi, stdenv }: + ({ mkDerivation, base, lib, liblapack, netlib-ffi }: mkDerivation { pname = "lapack-ffi"; - version = "0.0.2"; - sha256 = "d4b73268bb25244f0234ef4a8b4407818e244d297612a189c7f34fe0b64ae584"; + version = "0.0.3"; + sha256 = "d9871d1ff70b5ab6a5e6b8d6a9ca1381626f71a2339535ed03ffa8a9aaa047e2"; libraryHaskellDepends = [ base netlib-ffi ]; libraryPkgconfigDepends = [ liblapack ]; doHaddock = false; doCheck = false; - homepage = "http://hub.darcs.net/thielema/lapack-ffi/"; + homepage = "https://hub.darcs.net/thielema/lapack-ffi/"; description = "Auto-generated interface to Fortran LAPACK"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) liblapack;}; "lapack-ffi-tools" = callPackage ({ mkDerivation, base, bytestring, cassava, containers - , explicit-exception, filepath, non-empty, optparse-applicative - , parsec, pathtype, stdenv, transformers, unordered-containers - , utility-ht, vector + , explicit-exception, filepath, lib, non-empty + , optparse-applicative, parsec, pathtype, transformers + , unordered-containers, utility-ht, vector }: mkDerivation { pname = "lapack-ffi-tools"; - version = "0.1.1"; - sha256 = "739b40bdd776a057ab272195f54a8ef76534abd780076f48a02dca356b3270f8"; + version = "0.1.2.1"; + sha256 = "b03d22ca5d322ec50418e5e8e937b640910fd76a855722ec63ca1850f5256542"; + revision = "1"; + editedCabalFile = "1h5chlb66ycg96ab56hwqr4qk82l19gq1pg1zfzhfdl5byg24fln"; isLibrary = false; isExecutable = true; enableSeparateDataOutput = true; @@ -20029,10 +23652,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://hub.darcs.net/thielema/lapack-ffi-tools/"; description = "Generator for Haskell interface to Fortran LAPACK"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "largeword" = callPackage - ({ mkDerivation, base, binary, stdenv }: + ({ mkDerivation, base, binary, lib }: mkDerivation { pname = "largeword"; version = "1.2.5"; @@ -20042,10 +23665,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/idontgetoutmuch/largeword"; description = "Provides Word128, Word192 and Word256 and a way of producing other large words if required"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "latex" = callPackage - ({ mkDerivation, base, containers, stdenv, utility-ht }: + ({ mkDerivation, base, containers, lib, utility-ht }: mkDerivation { pname = "latex"; version = "0.1.0.4"; @@ -20055,31 +23678,33 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/LaTeX"; description = "Parse, format and process LaTeX files"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "lattices" = callPackage ({ mkDerivation, base, base-compat, containers, deepseq, hashable - , semigroupoids, stdenv, tagged, universe-base - , universe-reverse-instances, unordered-containers + , integer-logarithms, lib, QuickCheck, semigroupoids, tagged + , transformers, universe-base, universe-reverse-instances + , unordered-containers }: mkDerivation { pname = "lattices"; - version = "1.7.1.1"; - sha256 = "797c89a34c6d631f76ff3bf342275f090ebceb705d6ad69c1a4108582b14ddaf"; - revision = "1"; - editedCabalFile = "18182vlzaz5kzcn2j0k1jmdl8kgqmnpjc3ynsi7v6jdl3vig89dr"; + version = "2.0.2"; + sha256 = "3d6e750cb308cad178c2c305830a40325031ec79b5610f68eb468ad3d5851981"; + revision = "3"; + editedCabalFile = "1n1sv7477v88ibcwb5rh4p1r9r4hj0jj7s0vh6r0y2w4hbhpslvr"; libraryHaskellDepends = [ - base base-compat containers deepseq hashable semigroupoids tagged - universe-base universe-reverse-instances unordered-containers + base base-compat containers deepseq hashable integer-logarithms + QuickCheck semigroupoids tagged transformers universe-base + universe-reverse-instances unordered-containers ]; doHaddock = false; doCheck = false; homepage = "http://github.com/phadej/lattices/"; description = "Fine-grained library for constructing and manipulating lattices"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "lawful" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "lawful"; version = "0.1.0.0"; @@ -20089,10 +23714,26 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/matt-noonan/lawful#readme"; description = "Assert the lawfulness of your typeclass instances"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "lazy-csv" = callPackage + ({ mkDerivation, base, bytestring, lib }: + mkDerivation { + pname = "lazy-csv"; + version = "0.5.1"; + sha256 = "888bcbdd43886099f197c1c246cea324c97c076d4839e97eea0b8d6d7b49649f"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base bytestring ]; + executableHaskellDepends = [ base bytestring ]; + doHaddock = false; + doCheck = false; + homepage = "http://code.haskell.org/lazy-csv"; + description = "Efficient lazy parsers for CSV (comma-separated values)"; + license = lib.licenses.bsd3; }) {}; "lazyio" = callPackage - ({ mkDerivation, base, stdenv, transformers, unsafe }: + ({ mkDerivation, base, lib, transformers, unsafe }: mkDerivation { pname = "lazyio"; version = "0.1.0.4"; @@ -20104,50 +23745,66 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Lazy_IO"; description = "Run IO actions lazily while respecting their order"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "lazysmallcheck" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "lazysmallcheck"; + version = "0.6"; + sha256 = "9dd4dfb590c77e4f6aff68296602de58422eed5e7148fc29190d875a4e7d0f53"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "http://www.cs.york.ac.uk/~mfn/lazysmallcheck/"; + description = "A library for demand-driven testing of Haskell programs"; + license = lib.licenses.bsd3; }) {}; "lca" = callPackage - ({ mkDerivation, base, Cabal, cabal-doctest, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "lca"; - version = "0.3.1"; - sha256 = "8a8d045ae00d82ddb491e873cc36f1ca89e91556a183c343b99f4df6abfe434e"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "0.4"; + sha256 = "2e14b83704b83e50e171e005eb422ca19848e6b8855998ef2ee2302c46893256"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/lca/"; description = "O(log n) persistent online lowest common ancestor search without preprocessing"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "leancheck" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { pname = "leancheck"; - version = "0.8.0"; - sha256 = "3a7cd0b60131a254f4f4fe5176e76347479ffbdf519bddd6c35a05841eed74d1"; + version = "0.9.10"; + sha256 = "b63104f076e28b3a2a21740070ab189791790cf5dd19a9e61adc2530fce06534"; libraryHaskellDepends = [ base template-haskell ]; doHaddock = false; doCheck = false; homepage = "https://github.com/rudymatela/leancheck#readme"; description = "Enumerative property-based testing"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "leancheck-instances" = callPackage - ({ mkDerivation, base, bytestring, leancheck, nats, stdenv, text }: + ({ mkDerivation, array, base, bytestring, containers, leancheck + , lib, nats, text, time + }: mkDerivation { pname = "leancheck-instances"; - version = "0.0.1"; - sha256 = "985a181e4070484ffce723577b4267f4ef6f99c119b01037a209192dd037eddc"; - libraryHaskellDepends = [ base bytestring leancheck nats text ]; + version = "0.0.4"; + sha256 = "a7c5a0c448aa8cf89031047fc8ac6bf0a7b49eed28ae0cb1d6c7d7d7e1e430d0"; + libraryHaskellDepends = [ + array base bytestring containers leancheck nats text time + ]; doHaddock = false; doCheck = false; homepage = "https://github.com/rudymatela/leancheck-instances#readme"; description = "Common LeanCheck instances"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "leapseconds-announced" = callPackage - ({ mkDerivation, base, stdenv, time }: + ({ mkDerivation, base, lib, time }: mkDerivation { pname = "leapseconds-announced"; version = "2017.1.0.1"; @@ -20157,68 +23814,87 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/bjornbm/leapseconds-announced"; description = "Leap seconds announced at library release time"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "lens" = callPackage - ({ mkDerivation, array, base, base-orphans, bifunctors, bytestring - , Cabal, cabal-doctest, call-stack, comonad, containers - , contravariant, distributive, exceptions, filepath, free, ghc-prim - , hashable, kan-extensions, mtl, parallel, profunctors, reflection - , semigroupoids, semigroups, stdenv, tagged, template-haskell, text - , th-abstraction, transformers, transformers-compat - , unordered-containers, vector, void + "learn-physics" = callPackage + ({ mkDerivation, base, gloss, gnuplot, hmatrix, lib, not-gloss + , spatial-math, vector-space }: mkDerivation { - pname = "lens"; - version = "4.17"; - sha256 = "473664de541023bef44aa29105abbb1e35542e9254cdc846963183e0dd3f08cc"; - setupHaskellDepends = [ base Cabal cabal-doctest filepath ]; + pname = "learn-physics"; + version = "0.6.5"; + sha256 = "4b03a2d2d5871906fea7b7926d7ad3bfad537b300eb53311a0d360fdfc008d41"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base gloss gnuplot hmatrix not-gloss spatial-math vector-space + ]; + executableHaskellDepends = [ + base gloss gnuplot not-gloss spatial-math + ]; + doHaddock = false; + doCheck = false; + description = "Haskell code for learning physics"; + license = lib.licenses.bsd3; + }) {}; + "lens" = callPackage + ({ mkDerivation, array, base, base-orphans, bifunctors, bytestring + , Cabal, cabal-doctest, call-stack, comonad, containers + , contravariant, distributive, exceptions, filepath, free, ghc-prim + , hashable, kan-extensions, lib, mtl, parallel, profunctors + , reflection, semigroupoids, tagged, template-haskell, text + , th-abstraction, transformers, transformers-compat + , unordered-containers, vector + }: + mkDerivation { + pname = "lens"; + version = "4.19.2"; + sha256 = "52f858ae3971a5104cdba5e81a27d154fda11fe65a54a4ac328c85904bdec23b"; + revision = "6"; + editedCabalFile = "1k08my9rh1il3ibiyhljxkgndfgk143pn5a6nyzjnckw3la09myl"; + setupHaskellDepends = [ base Cabal cabal-doctest filepath ]; libraryHaskellDepends = [ array base base-orphans bifunctors bytestring call-stack comonad containers contravariant distributive exceptions filepath free ghc-prim hashable kan-extensions mtl parallel profunctors - reflection semigroupoids semigroups tagged template-haskell text + reflection semigroupoids tagged template-haskell text th-abstraction transformers transformers-compat - unordered-containers vector void + unordered-containers vector ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/lens/"; description = "Lenses, Folds and Traversals"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; }) {}; "lens-action" = callPackage - ({ mkDerivation, base, Cabal, cabal-doctest, comonad, contravariant - , lens, mtl, profunctors, semigroupoids, semigroups, stdenv - , transformers + ({ mkDerivation, base, comonad, contravariant, lens, lib, mtl + , profunctors, semigroupoids, transformers }: mkDerivation { pname = "lens-action"; - version = "0.2.3"; - sha256 = "06848a6c7f217c3dd3228633bedc9a73b2cce139c1a6dff61af0994d410a98e0"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "0.2.5"; + sha256 = "596ce088497b1b4005ba13276348cd282ae55ce95ab277c53dc58fac9c395b0b"; libraryHaskellDepends = [ base comonad contravariant lens mtl profunctors semigroupoids - semigroups transformers + transformers ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/lens-action/"; description = "Monadic Getters and Folds"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "lens-aeson" = callPackage - ({ mkDerivation, aeson, attoparsec, base, bytestring, Cabal - , cabal-doctest, lens, scientific, stdenv, text - , unordered-containers, vector + ({ mkDerivation, aeson, attoparsec, base, bytestring, lens, lib + , scientific, text, unordered-containers, vector }: mkDerivation { pname = "lens-aeson"; - version = "1.0.2"; - sha256 = "4311f035caa39db3a70915a165bcbfb55ad22376085d95a9b4f57c58994702cc"; - revision = "6"; - editedCabalFile = "1pg5v8fnlqw1krgi3d2a03a0zkjjdv5yp5f5z6q4mlb5jldz99a8"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "1.1.1"; + sha256 = "6fd7e1a83e97c91289cc26401159edb5f3443dce04575afc86c3af222e6267bc"; + revision = "1"; + editedCabalFile = "16n6id5l84v2n3yd8n5i2my4s4p8m0z85hgbzfrpm3rhr1haja00"; libraryHaskellDepends = [ aeson attoparsec base bytestring lens scientific text unordered-containers vector @@ -20227,10 +23903,22 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/lens/lens-aeson/"; description = "Law-abiding lenses for aeson"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "lens-csv" = callPackage + ({ mkDerivation, base, bytestring, cassava, lens, lib }: + mkDerivation { + pname = "lens-csv"; + version = "0.1.1.0"; + sha256 = "37e741b9cf4440393b2f906856c843b4a45e04829dd81bc0a7b0c366c5587c4e"; + libraryHaskellDepends = [ base bytestring cassava lens ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ChrisPenner/lens-csv#readme"; + license = lib.licenses.bsd3; }) {}; "lens-datetime" = callPackage - ({ mkDerivation, base, lens, stdenv, time }: + ({ mkDerivation, base, lens, lib, time }: mkDerivation { pname = "lens-datetime"; version = "0.3"; @@ -20240,64 +23928,53 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/nilcons/lens-datetime"; description = "Lenses for Data.Time.* types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "lens-family" = callPackage - ({ mkDerivation, base, containers, lens-family-core, mtl, stdenv + ({ mkDerivation, base, containers, lens-family-core, lib, mtl , transformers }: mkDerivation { pname = "lens-family"; - version = "1.2.3"; - sha256 = "8059e2b7a917e0108861ca795b0adfbb0bf1db5b1bdb55e677256a37d8de0e29"; + version = "2.0.0"; + sha256 = "6793f2a5c5030f02258532043d57eac42318cd7f9cef47f6720a7b99276f03db"; + revision = "1"; + editedCabalFile = "1nf0zxhwqkg54mc3kimnqcvg9b732rn35r1rjs1fzf0vwssla3zw"; libraryHaskellDepends = [ base containers lens-family-core mtl transformers ]; doHaddock = false; doCheck = false; description = "Lens Families"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "lens-family-core" = callPackage - ({ mkDerivation, base, containers, stdenv, transformers }: + ({ mkDerivation, base, containers, lib, transformers }: mkDerivation { pname = "lens-family-core"; - version = "1.2.3"; - sha256 = "914f5f077d7bed8a93866ac696e69c35bb8d0fbe81314236288b057941703901"; + version = "2.0.0"; + sha256 = "19b4fcd3bd37dd0056c112a9b16cf405644fabd6652013c61a5078380ed2265a"; libraryHaskellDepends = [ base containers transformers ]; doHaddock = false; doCheck = false; - description = "Haskell 98 Lens Families"; - license = stdenv.lib.licenses.bsd3; + description = "Haskell 2022 Lens Families"; + license = lib.licenses.bsd3; }) {}; "lens-family-th" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { pname = "lens-family-th"; - version = "0.5.0.2"; - sha256 = "9c275afad37a5064b9a13c6207ee2307f6ccccc3a5517c0fae84524bad65b0e6"; + version = "0.5.2.0"; + sha256 = "eb174411fb69229f057f913106ef6656bfd482f6988ad8b6ac06ff0ae68df401"; libraryHaskellDepends = [ base template-haskell ]; doHaddock = false; doCheck = false; homepage = "http://github.com/DanBurton/lens-family-th#readme"; description = "Generate lens-family style lenses"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "lens-labels" = callPackage - ({ mkDerivation, base, ghc-prim, profunctors, stdenv, tagged }: - mkDerivation { - pname = "lens-labels"; - version = "0.3.0.1"; - sha256 = "e71772f4ad0b6c1c926da9f29257b44f03b8e16ae321b993fd416a3b03e0e27f"; - libraryHaskellDepends = [ base ghc-prim profunctors tagged ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/google/proto-lens#readme"; - description = "Integration of lenses with OverloadedLabels"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "lens-misc" = callPackage - ({ mkDerivation, base, lens, stdenv, tagged, template-haskell }: + ({ mkDerivation, base, lens, lib, tagged, template-haskell }: mkDerivation { pname = "lens-misc"; version = "0.0.2.0"; @@ -20307,31 +23984,46 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/louispan/lens-misc#readme"; description = "Miscellaneous lens utilities"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "lens-process" = callPackage + ({ mkDerivation, base, filepath, lens, lib, process }: + mkDerivation { + pname = "lens-process"; + version = "0.4.0.0"; + sha256 = "0f9ff68da54aa8784e7b40e38686266f423fc3b4e3b1045abccfeba0fa12babe"; + revision = "1"; + editedCabalFile = "0y1ran4pjqr2226rkmiqij0pf980npr7iv88y5bgcg7hs22f3b57"; + libraryHaskellDepends = [ base filepath lens process ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/emilypi/lens-process"; + description = "Optics for system processes"; + license = lib.licenses.bsd3; }) {}; "lens-properties" = callPackage - ({ mkDerivation, base, lens, QuickCheck, stdenv, transformers }: + ({ mkDerivation, base, lens, lib, QuickCheck, transformers }: mkDerivation { pname = "lens-properties"; version = "4.11.1"; sha256 = "4f7c5b75a7204c151dbe62160a6917a22ab9e2a1b2e3848b7043d972ac8f4cb1"; - revision = "2"; - editedCabalFile = "1b14fcncz2yby0d4jhx2h0ma6nx0fd1z7hrg1va4h7zn06m99482"; + revision = "5"; + editedCabalFile = "0zv5r50xz8msrcwrvqym88pwihqcpmlk3vi493jdhik4n70cs0c6"; libraryHaskellDepends = [ base lens QuickCheck transformers ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/lens/"; description = "QuickCheck properties for lens"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "lens-regex" = callPackage - ({ mkDerivation, array, base, lens, regex-base, stdenv + ({ mkDerivation, array, base, lens, lib, regex-base , template-haskell }: mkDerivation { pname = "lens-regex"; - version = "0.1.1"; - sha256 = "0d946baa2be86452fe0a2185575e1d00752a075c92c48acdb3ed7833cd1ec730"; + version = "0.1.3"; + sha256 = "e4d76137b0ce41a799c35cf603608f946d4ede63346e330878434e6dc86cef87"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -20341,57 +24033,47 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/himura/lens-regex"; description = "Lens powered regular expression"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "lens-simple" = callPackage - ({ mkDerivation, base, lens-family, lens-family-core - , lens-family-th, mtl, stdenv, transformers + "lens-regex-pcre" = callPackage + ({ mkDerivation, base, bytestring, containers, lens, lib + , pcre-heavy, pcre-light, template-haskell, text }: mkDerivation { - pname = "lens-simple"; - version = "0.1.0.9"; - sha256 = "613d99b8074197f8a026a641a9940dd188e0d81e808169f420981a9ca15b832a"; + pname = "lens-regex-pcre"; + version = "1.1.0.0"; + sha256 = "b150dc34f9b066ba7e21fac541899f1ea26ddce436b5dd1c6cf7519f0705a418"; libraryHaskellDepends = [ - base lens-family lens-family-core lens-family-th mtl transformers + base bytestring containers lens pcre-heavy pcre-light + template-haskell text ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/michaelt/lens-simple"; - description = "simplified import of elementary lens-family combinators"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "lens-typelevel" = callPackage - ({ mkDerivation, base, singletons, stdenv }: - mkDerivation { - pname = "lens-typelevel"; - version = "0.1.1.0"; - sha256 = "773d07872000869d3fd4b45256e4ce8da16f85754da87bdd084a33f5b2b94d53"; - libraryHaskellDepends = [ base singletons ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/mstksg/lens-typelevel#readme"; - description = "Type-level lenses using singletons"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/ChrisPenner/lens-regex-pcre#readme"; + description = "A lensy interface to regular expressions"; + license = lib.licenses.bsd3; }) {}; "lenz" = callPackage - ({ mkDerivation, base, base-unicode-symbols, hs-functors, stdenv + ({ mkDerivation, base, base-unicode-symbols, hs-functors, lib , transformers }: mkDerivation { pname = "lenz"; - version = "0.3.0.0"; - sha256 = "632232db41f7c49359f37ed541bbbbe99f74d45c1cf583d1081b83af426a439d"; + version = "0.4.2.0"; + sha256 = "8e9a0d55f51eda0683a7b2b4d466bf21a46d57eb6d3fd9ed442251da3b4ddf8f"; + revision = "1"; + editedCabalFile = "0mzvvddl7wwa4z3rxwdwlaazv0wbg7lfynsab7lya6dzkw4nl7m4"; libraryHaskellDepends = [ base base-unicode-symbols hs-functors transformers ]; doHaddock = false; doCheck = false; description = "Van Laarhoven lenses"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "leveldb-haskell" = callPackage ({ mkDerivation, base, bytestring, data-default, exceptions - , filepath, leveldb, resourcet, stdenv, transformers + , filepath, leveldb, lib, resourcet, transformers }: mkDerivation { pname = "leveldb-haskell"; @@ -20408,10 +24090,25 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/kim/leveldb-haskell"; description = "Haskell bindings to LevelDB"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) leveldb;}; + "libBF" = callPackage + ({ mkDerivation, base, deepseq, hashable, lib }: + mkDerivation { + pname = "libBF"; + version = "0.6.2"; + sha256 = "7d035ca04ff4111e70434f0549f6db54dd93666fe1369790aa90e1cf1fbf5d01"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base deepseq hashable ]; + executableHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + description = "A binding to the libBF library"; + license = lib.licenses.mit; + }) {}; "libffi" = callPackage - ({ mkDerivation, base, bytestring, ffi, libffi, stdenv }: + ({ mkDerivation, base, bytestring, ffi, lib, libffi }: mkDerivation { pname = "libffi"; version = "0.1"; @@ -20422,10 +24119,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A binding to libffi"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) ffi; inherit (pkgs) libffi;}; "libgit" = callPackage - ({ mkDerivation, base, mtl, process, stdenv }: + ({ mkDerivation, base, lib, mtl, process }: mkDerivation { pname = "libgit"; version = "0.3.1"; @@ -20435,16 +24132,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/vincenthz/hs-libgit"; description = "Simple Git Wrapper"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "libgraph" = callPackage - ({ mkDerivation, array, base, containers, monads-tf, process - , stdenv, union-find + ({ mkDerivation, array, base, containers, lib, monads-tf, process + , union-find }: mkDerivation { pname = "libgraph"; version = "1.14"; sha256 = "b7978be50d6182101ca79fb3ea83d0621f5394d483d1fa1eb7d590e45f8d3f3f"; + revision = "1"; + editedCabalFile = "12xyrvvyh73b93k74lj55zwaygsvd93p4bm51kcd54m0pv0lclbq"; libraryHaskellDepends = [ array base containers monads-tf process union-find ]; @@ -20452,97 +24151,122 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://maartenfaddegon.nl"; description = "Store and manipulate data in a graph"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "libjwt-typed" = callPackage + ({ mkDerivation, base, bytestring, case-insensitive, casing + , data-default, either, exceptions, extra, lib, monad-time, proxied + , text, time, transformers, unordered-containers, utf8-string, uuid + }: + mkDerivation { + pname = "libjwt-typed"; + version = "0.2"; + sha256 = "050009013647b1c2979fe8b090328efd9c2fb361d6edc0bf7a60aa1c76b99d39"; + libraryHaskellDepends = [ + base bytestring case-insensitive casing data-default either + exceptions extra monad-time proxied text time transformers + unordered-containers utf8-string uuid + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/marcin-rzeznicki/libjwt-typed"; + description = "A Haskell implementation of JSON Web Token (JWT)"; + license = lib.licenses.mpl20; }) {}; "libmpd" = callPackage ({ mkDerivation, attoparsec, base, bytestring, containers - , data-default-class, filepath, mtl, network, old-locale, stdenv + , data-default-class, filepath, lib, mtl, network, safe-exceptions , text, time, utf8-string }: mkDerivation { pname = "libmpd"; - version = "0.9.0.9"; - sha256 = "5b867ee675de1f490e58f5cb3903e1ea7e430ebca4b6d86e6b9c2c1c87a861a4"; + version = "0.10.0.0"; + sha256 = "7062e2ce476c48e9efd75a802d2a93ce067243e9fe355faed0970f0b72a41b21"; libraryHaskellDepends = [ attoparsec base bytestring containers data-default-class filepath - mtl network old-locale text time utf8-string + mtl network safe-exceptions text time utf8-string ]; doHaddock = false; doCheck = false; homepage = "http://github.com/vimus/libmpd-haskell#readme"; description = "An MPD client library"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "libraft" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, cereal, concurrency - , containers, directory, exceptions, haskeline, mtl, network - , network-simple, parsec, protolude, random, repline, stdenv, stm - , text, time, transformers, word8 + "liboath-hs" = callPackage + ({ mkDerivation, base, bytestring, inline-c, lib, liboath, oath + , safe-exceptions, time }: mkDerivation { - pname = "libraft"; - version = "0.1.1.0"; - sha256 = "0cc94b7b17def34206358ec0e7107f1d94decf6d36f77296e6c199c8decd59ce"; - revision = "1"; - editedCabalFile = "0bzfkay18wphlqfm0i6rmr7rm1d6s16nxvrmc4wp0szim1k9k0gh"; + pname = "liboath-hs"; + version = "0.0.1.2"; + sha256 = "318f36795e1c2419749f448aa662e40302ae4c64a169e1dd581e2a81a6fe9623"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - attoparsec base bytestring cereal concurrency containers directory - exceptions haskeline mtl network network-simple parsec protolude - random repline text time transformers word8 - ]; - executableHaskellDepends = [ - attoparsec base bytestring cereal concurrency containers directory - exceptions haskeline mtl network network-simple parsec protolude - random repline stm text time transformers word8 + base bytestring inline-c safe-exceptions time ]; + librarySystemDepends = [ oath ]; + libraryPkgconfigDepends = [ liboath ]; + executableHaskellDepends = [ base bytestring time ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/adjoint-io/raft#readme"; - description = "Raft consensus algorithm"; - license = stdenv.lib.licenses.bsd3; - }) {}; + homepage = "https://github.com/parsonsmatt/liboath-hs#readme"; + description = "Bindings to liboath"; + license = lib.licenses.gpl3Only; + }) {inherit (pkgs) liboath; inherit (pkgs) oath;}; "libyaml" = callPackage - ({ mkDerivation, base, bytestring, conduit, resourcet, stdenv }: + ({ mkDerivation, base, bytestring, conduit, lib, resourcet }: mkDerivation { pname = "libyaml"; - version = "0.1.0.0"; - sha256 = "9cd688e316938d8a80536cb1b329c4b651c845e34e045b0c443b345580fb6f07"; + version = "0.1.2"; + sha256 = "8f42d66f199fcaee255326f8f770d88b0670df56b5eb78002d6058f3a45e97b5"; libraryHaskellDepends = [ base bytestring conduit resourcet ]; doHaddock = false; doCheck = false; homepage = "https://github.com/snoyberg/yaml#readme"; description = "Low-level, streaming YAML interface"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "lift-generics" = callPackage - ({ mkDerivation, base, generic-deriving, ghc-prim, stdenv - , template-haskell + ({ mkDerivation, base, generic-deriving, ghc-prim, lib + , template-haskell, th-compat }: mkDerivation { pname = "lift-generics"; - version = "0.1.2"; - sha256 = "0e9fbd17cd3e1af6ef1e994e7c14cfd42896e56499864e707f72246b6e2b604e"; - revision = "2"; - editedCabalFile = "171f8cpn0kw9psikx3n7cdwyqfwg8rr8gf1hja6g7pnm0683l5l8"; + version = "0.2"; + sha256 = "ca5a639c0a740a9d0da092d704e7ed34062c4bdbffbb3fdf9713aeb781b3b7d4"; + revision = "1"; + editedCabalFile = "0jxqzzspwyv92ji8331r2lqh6igxyh9p70ci90068f3qy9zrgrr4"; libraryHaskellDepends = [ - base generic-deriving ghc-prim template-haskell + base generic-deriving ghc-prim template-haskell th-compat ]; doHaddock = false; doCheck = false; homepage = "https://github.com/RyanGlScott/lift-generics"; description = "GHC.Generics-based Language.Haskell.TH.Syntax.lift implementation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "lift-type" = callPackage + ({ mkDerivation, base, lib, template-haskell }: + mkDerivation { + pname = "lift-type"; + version = "0.1.0.1"; + sha256 = "aeb79e3090a38130fdb1da374e9e50e132e6bf5e20b45de58af5230d9c8f2585"; + libraryHaskellDepends = [ base template-haskell ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/parsonsmatt/lift-type#readme"; + description = "Lift a type from a Typeable constraint to a Template Haskell type"; + license = lib.licenses.bsd3; }) {}; "lifted-async" = callPackage - ({ mkDerivation, async, base, constraints, lifted-base - , monad-control, stdenv, transformers-base + ({ mkDerivation, async, base, constraints, lib, lifted-base + , monad-control, transformers-base }: mkDerivation { pname = "lifted-async"; - version = "0.10.0.3"; - sha256 = "83d09c355cf7c5d35f179f6f084524f451966ed29beac721f0500ee607822b8c"; + version = "0.10.2"; + sha256 = "612893b906840cd1e4a9dd12c6466244ada8f8c8ab604f69d6c491db77de902a"; libraryHaskellDepends = [ async base constraints lifted-base monad-control transformers-base ]; @@ -20550,10 +24274,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/maoe/lifted-async"; description = "Run lifted IO operations asynchronously and wait for their results"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "lifted-base" = callPackage - ({ mkDerivation, base, monad-control, stdenv, transformers-base }: + ({ mkDerivation, base, lib, monad-control, transformers-base }: mkDerivation { pname = "lifted-base"; version = "0.2.3.12"; @@ -20563,11 +24287,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/basvandijk/lifted-base"; description = "lifted IO operations from the base library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "line" = callPackage ({ mkDerivation, aeson, base, base64-bytestring, bytestring - , cryptohash-sha256, http-conduit, http-types, scotty, stdenv, text + , cryptohash-sha256, http-conduit, http-types, lib, scotty, text , time, transformers, wai }: mkDerivation { @@ -20582,34 +24306,73 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/utatti/line"; description = "Haskell SDK for the LINE API"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "linear" = callPackage ({ mkDerivation, adjunctions, base, base-orphans, binary, bytes - , Cabal, cabal-doctest, cereal, containers, deepseq, distributive - , ghc-prim, hashable, lens, reflection, semigroupoids, semigroups - , stdenv, tagged, template-haskell, transformers + , cereal, containers, deepseq, distributive, ghc-prim, hashable + , indexed-traversable, lens, lib, random, reflection, semigroupoids + , semigroups, tagged, template-haskell, transformers , transformers-compat, unordered-containers, vector, void }: mkDerivation { pname = "linear"; - version = "1.20.8"; - sha256 = "5ebd1b99837f2e3c7386bcd2ca425d9c66b09a61409792b141428345fb9edb10"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "1.21.6"; + sha256 = "65ac8c916b30f5379038e5de46f9a92b49993920acb5f229e0a3acc36abea62b"; libraryHaskellDepends = [ adjunctions base base-orphans binary bytes cereal containers - deepseq distributive ghc-prim hashable lens reflection - semigroupoids semigroups tagged template-haskell transformers - transformers-compat unordered-containers vector void + deepseq distributive ghc-prim hashable indexed-traversable lens + random reflection semigroupoids semigroups tagged template-haskell + transformers transformers-compat unordered-containers vector void ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/linear/"; description = "Linear Algebra"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "linear-circuit" = callPackage + ({ mkDerivation, base, comfort-array, comfort-graph, containers + , lapack, lib, netlib-ffi, transformers, utility-ht + }: + mkDerivation { + pname = "linear-circuit"; + version = "0.1.0.2"; + sha256 = "95a67081822068b5973dbbff143369103ee4676e621c8b91b6f77a7111a6c231"; + libraryHaskellDepends = [ + base comfort-array comfort-graph containers lapack netlib-ffi + transformers utility-ht + ]; + doHaddock = false; + doCheck = false; + homepage = "http://hub.darcs.net/thielema/linear-circuit"; + description = "Compute resistance of linear electrical circuits"; + license = lib.licenses.bsd3; + }) {}; + "linenoise" = callPackage + ({ mkDerivation, base, bytestring, exceptions, lib, mtl, text + , unliftio-core + }: + mkDerivation { + pname = "linenoise"; + version = "0.3.2"; + sha256 = "3d3bd156bcba12a390a94240440e1979a88c9c392c571674e8aea23226084943"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base bytestring exceptions mtl text unliftio-core + ]; + executableHaskellDepends = [ + base bytestring exceptions mtl text unliftio-core + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ejconlon/haskell-linenoise#readme"; + description = "A lightweight readline-replacement library for Haskell"; + license = lib.licenses.bsd3; }) {}; "linux-file-extents" = callPackage - ({ mkDerivation, base, stdenv, unix }: + ({ mkDerivation, base, lib, unix }: mkDerivation { pname = "linux-file-extents"; version = "0.2.0.0"; @@ -20621,10 +24384,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/redneb/linux-file-extents"; description = "Retrieve file fragmentation information under Linux"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "linux-namespaces" = callPackage - ({ mkDerivation, base, bytestring, stdenv, unix }: + ({ mkDerivation, base, bytestring, lib, unix }: mkDerivation { pname = "linux-namespaces"; version = "0.1.3.0"; @@ -20634,27 +24397,93 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/redneb/hs-linux-namespaces"; description = "Work with linux namespaces: create new or enter existing ones"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "liquid-fixpoint" = callPackage + ({ mkDerivation, ansi-terminal, array, ascii-progress, async + , attoparsec, base, binary, boxes, cereal, cmdargs, containers + , deepseq, directory, fgl, filepath, hashable, intern, lib, mtl + , ocaml, parallel, parsec, pretty, process, syb, text, text-format + , transformers, unordered-containers + }: + mkDerivation { + pname = "liquid-fixpoint"; + version = "0.8.10.2"; + sha256 = "14e55c33e7cd980ef7d435161f130238b7de231ac1ae9b26763dfd5a2e42ade9"; + configureFlags = [ "-fbuild-external" ]; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + ansi-terminal array ascii-progress async attoparsec base binary + boxes cereal cmdargs containers deepseq directory fgl filepath + hashable intern mtl parallel parsec pretty process syb text + text-format transformers unordered-containers + ]; + executableHaskellDepends = [ base ]; + executableSystemDepends = [ ocaml ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ucsd-progsys/liquid-fixpoint"; + description = "Predicate Abstraction-based Horn-Clause/Implication Constraint Solver"; + license = lib.licenses.bsd3; + }) {inherit (pkgs) ocaml;}; + "list-predicate" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "list-predicate"; + version = "0.1.0.1"; + sha256 = "2dfbb4532921d1b6905210fa675d503d41c8b79337b7c5e73b6a73f2c8c482fe"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/pgujjula/list-utilities#readme"; + description = "Predicates on lists"; + license = lib.licenses.bsd3; + }) {}; + "list-singleton" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "list-singleton"; + version = "1.0.0.5"; + sha256 = "766483d6a3c743872be39f55ea582d597113dff4ac0fe2cc4a85aadc087870ed"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + description = "Easily and clearly create lists with only one element in them"; + license = lib.licenses.isc; }) {}; "list-t" = callPackage - ({ mkDerivation, base, mmorph, monad-control, mtl, stdenv + ({ mkDerivation, base, foldl, lib, mmorph, monad-control, mtl , transformers, transformers-base }: mkDerivation { pname = "list-t"; - version = "1.0.2"; - sha256 = "da6cad360db0ab9d01a37a54aa73c54b29f6088254e0770dc312ebd0d2b39223"; + version = "1.0.4"; + sha256 = "3863844bf18a47997dce5972df30b6a38d257cbc168216be2233a40b33c15577"; libraryHaskellDepends = [ - base mmorph monad-control mtl transformers transformers-base + base foldl mmorph monad-control mtl transformers transformers-base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nikita-volkov/list-t"; description = "ListT done right"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "list-transformer" = callPackage + ({ mkDerivation, base, lib, mtl }: + mkDerivation { + pname = "list-transformer"; + version = "1.0.7"; + sha256 = "08c698b0cf43ee9efb1ea23228ae3078fae2a9739e3d1ff8a2cfbb6374ab1fc5"; + libraryHaskellDepends = [ base mtl ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/Gabriel439/Haskell-List-Transformer-Library"; + description = "List monad transformer"; + license = lib.licenses.bsd3; }) {}; "listsafe" = callPackage - ({ mkDerivation, base, exceptions, stdenv }: + ({ mkDerivation, base, exceptions, lib }: mkDerivation { pname = "listsafe"; version = "0.1.0.1"; @@ -20664,16 +24493,77 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/ombocomp/listsafe"; description = "Safe wrappers for partial list functions, supporting MonadThrow"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; + }) {}; + "literatex" = callPackage + ({ mkDerivation, ansi-wl-pprint, base, bytestring, conduit, lib + , optparse-applicative, text, ttc, unliftio + }: + mkDerivation { + pname = "literatex"; + version = "0.1.0.2"; + sha256 = "3091ee5de59bed61eedabc0e679faf6b08ac4e44ebfb84d89d2ec90d822ab2ab"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base bytestring conduit text ttc unliftio + ]; + executableHaskellDepends = [ + ansi-wl-pprint base optparse-applicative ttc + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ExtremaIS/literatex-haskell#readme"; + description = "transform literate source code to Markdown"; + license = lib.licenses.mit; + }) {}; + "little-rio" = callPackage + ({ mkDerivation, base, deepseq, exceptions, lib, microlens + , microlens-mtl, mtl, primitive, resourcet, unliftio-core + }: + mkDerivation { + pname = "little-rio"; + version = "0.2.2"; + sha256 = "29373fb965cde9ac8554ccd794cddd153ab0c4a044bd67c8359a3e08976e6ab1"; + libraryHaskellDepends = [ + base deepseq exceptions microlens microlens-mtl mtl primitive + resourcet unliftio-core + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ejconlon/little-rio#readme"; + description = "When you need just the RIO monad"; + license = lib.licenses.bsd3; + }) {}; + "llvm-hs" = callPackage + ({ mkDerivation, array, attoparsec, base, bytestring, Cabal + , containers, exceptions, lib, llvm-config, llvm-hs-pure, mtl + , template-haskell, transformers, utf8-string + }: + mkDerivation { + pname = "llvm-hs"; + version = "9.0.1"; + sha256 = "00e0cf4d4b520f8cf751073e4cbca4c1de85aeb67d6b596bf72cc142e0eb431c"; + setupHaskellDepends = [ base Cabal containers ]; + libraryHaskellDepends = [ + array attoparsec base bytestring containers exceptions llvm-hs-pure + mtl template-haskell transformers utf8-string + ]; + libraryToolDepends = [ llvm-config ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/llvm-hs/llvm-hs/"; + description = "General purpose LLVM bindings"; + license = lib.licenses.bsd3; }) {}; "llvm-hs-pure" = callPackage ({ mkDerivation, attoparsec, base, bytestring, containers, fail - , mtl, stdenv, template-haskell, transformers, unordered-containers + , lib, mtl, template-haskell, transformers, unordered-containers }: mkDerivation { pname = "llvm-hs-pure"; - version = "7.0.0"; - sha256 = "af9d7cdd512c4d33f7ad60deb445b72b1ecccff4e3968dd3f51327846c6402ad"; + version = "9.0.0"; + sha256 = "6e8ea5c8b192d58932cfeeaf7b3e592fea185e7a83e315c5bfff968ca02aab5f"; libraryHaskellDepends = [ attoparsec base bytestring containers fail mtl template-haskell transformers unordered-containers @@ -20682,10 +24572,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/llvm-hs/llvm-hs/"; description = "Pure Haskell LLVM functionality (no FFI)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "lmdb" = callPackage - ({ mkDerivation, array, base, lmdb, stdenv }: + ({ mkDerivation, array, base, lib, lmdb }: mkDerivation { pname = "lmdb"; version = "0.2.5"; @@ -20696,49 +24586,52 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/dmbarbour/haskell-lmdb"; description = "Lightning MDB bindings"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; }) {inherit (pkgs) lmdb;}; "load-env" = callPackage - ({ mkDerivation, base, directory, filepath, parsec, stdenv }: + ({ mkDerivation, base, directory, filepath, lib, parsec }: mkDerivation { pname = "load-env"; - version = "0.2.0.2"; - sha256 = "819372c454adb5948329d265e5d7e7293970444f396618bc6bd62fbeac687f18"; + version = "0.2.1.0"; + sha256 = "e3ec6dfafeb9be454d010e1a4330b5a66beb8fb9496a9b70a42e9b18ea0494a0"; libraryHaskellDepends = [ base directory filepath parsec ]; doHaddock = false; doCheck = false; homepage = "https://github.com/pbrisbin/load-env#readme"; description = "Load environment variables from a file"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "loc" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "loc"; - version = "0.1.3.4"; - sha256 = "c263ff5fbbd7d8cb597e617cb4a0cf961cac3b62c64de777e27d784e32b6b8f5"; + version = "0.1.3.10"; + sha256 = "7c5adce61e9535d7a6d4977c0a8ccc0e439d1e7b58d7f628b9f25456a3bf806e"; libraryHaskellDepends = [ base containers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/chris-martin/loc"; description = "Types representing line and column positions and ranges in text files"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; }) {}; "locators" = callPackage - ({ mkDerivation, base, bytestring, containers, cryptohash, stdenv + ({ mkDerivation, base, bytestring, containers, cryptonite, lib + , memory }: mkDerivation { pname = "locators"; - version = "0.2.4.4"; - sha256 = "2d6d0940206e285a086ea66c7b5f8b3a082fa629a8d335323dbbf78547e09aa5"; - libraryHaskellDepends = [ base bytestring containers cryptohash ]; + version = "0.3.0.3"; + sha256 = "b83a414f678ed3e02b05a4eafe6881b44d5a0da2ecf8b308a6aed740aa7c54e6"; + libraryHaskellDepends = [ + base bytestring containers cryptonite memory + ]; doHaddock = false; doCheck = false; description = "Human exchangable identifiers and locators"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; "loch-th" = callPackage - ({ mkDerivation, base, pretty, stdenv, template-haskell }: + ({ mkDerivation, base, lib, pretty, template-haskell }: mkDerivation { pname = "loch-th"; version = "0.2.2"; @@ -20748,11 +24641,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/liskin/loch-th"; description = "Support for precise error locations in source files (Template Haskell version)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "lockfree-queue" = callPackage ({ mkDerivation, abstract-deque, atomic-primops, base, bytestring - , ghc-prim, stdenv + , ghc-prim, lib }: mkDerivation { pname = "lockfree-queue"; @@ -20765,40 +24658,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/rrnewton/haskell-lockfree/wiki"; description = "Michael and Scott lock-free queues"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "log-base" = callPackage - ({ mkDerivation, aeson, aeson-pretty, base, bytestring, deepseq - , exceptions, mmorph, monad-control, monad-time, mtl, semigroups - , stdenv, stm, text, time, transformers-base, unordered-containers - }: - mkDerivation { - pname = "log-base"; - version = "0.7.4.0"; - sha256 = "4067eba80db49eb4509c10770959d0350f9eb9df5e0bde2fbf9024f106dc3f1b"; - libraryHaskellDepends = [ - aeson aeson-pretty base bytestring deepseq exceptions mmorph - monad-control monad-time mtl semigroups stm text time - transformers-base unordered-containers - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/scrive/log"; - description = "Structured logging solution (base package)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "log-domain" = callPackage - ({ mkDerivation, base, binary, bytes, Cabal, cabal-doctest, cereal - , comonad, deepseq, distributive, hashable, semigroupoids - , semigroups, stdenv, vector + ({ mkDerivation, base, binary, bytes, cereal, comonad, deepseq + , distributive, hashable, lib, semigroupoids, semigroups, vector }: mkDerivation { pname = "log-domain"; - version = "0.12"; - sha256 = "7191cba40b9b348c54171f2b86caabb75a30e52b6d7e4c57321bf5dcdf1f367e"; - revision = "3"; - editedCabalFile = "19xc24jwfhzy3v26689sc4ma50w4ylqd378dpxphl0nrxili645z"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "0.13.1"; + sha256 = "5b4b257469ccd6392ea9b6dfa1a76f32274089c52c2d344be52707fda98bf146"; libraryHaskellDepends = [ base binary bytes cereal comonad deepseq distributive hashable semigroupoids semigroups vector @@ -20807,10 +24676,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/log-domain/"; description = "Log-domain arithmetic"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "logfloat" = callPackage - ({ mkDerivation, array, base, stdenv }: + ({ mkDerivation, array, base, lib }: mkDerivation { pname = "logfloat"; version = "0.13.3.3"; @@ -20820,50 +24689,28 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://code.haskell.org/~wren/"; description = "Log-domain floating point numbers"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "logger-thread" = callPackage - ({ mkDerivation, base, fast-logger, protolude, safe-exceptions - , stdenv, stm, text, time - }: - mkDerivation { - pname = "logger-thread"; - version = "0.1.0.2"; - sha256 = "ac0a54001a69cff6f975209c4d9d399fb58ef59bb0ad6ac742c5ffedeac04a2a"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - base fast-logger protolude safe-exceptions stm text time - ]; - executableHaskellDepends = [ base protolude stm ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/joe9/logger-thread#readme"; - description = "Run FastLogger in a thread and direct all queued messages to it"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "logging-effect" = callPackage - ({ mkDerivation, async, base, exceptions, free, monad-control, mtl - , prettyprinter, semigroups, stdenv, stm, stm-delay, text, time - , transformers, transformers-base, unliftio-core + "logging" = callPackage + ({ mkDerivation, base, binary, bytestring, fast-logger, lib + , lifted-base, monad-control, old-locale, regex-compat, text, time + , time-locale-compat, transformers }: mkDerivation { - pname = "logging-effect"; - version = "1.3.3"; - sha256 = "996ae52b545d1e86ffd08c25ace247c90cf437ebdbbafd4879f587ad207cf182"; + pname = "logging"; + version = "3.0.5"; + sha256 = "b12fada1327648ac356840ee39d368ae6da1c3e801a80e8d4d0637d9e505a031"; libraryHaskellDepends = [ - async base exceptions free monad-control mtl prettyprinter - semigroups stm stm-delay text time transformers transformers-base - unliftio-core + base binary bytestring fast-logger lifted-base monad-control + old-locale regex-compat text time time-locale-compat transformers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/ocharles/logging-effect"; - description = "A mtl-style monad transformer for general purpose & compositional logging"; - license = stdenv.lib.licenses.bsd3; + description = "Simplified logging in IO for application writers"; + license = lib.licenses.mit; }) {}; "logging-facade" = callPackage - ({ mkDerivation, base, call-stack, stdenv, transformers }: + ({ mkDerivation, base, call-stack, lib, transformers }: mkDerivation { pname = "logging-facade"; version = "0.3.0"; @@ -20873,10 +24720,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/sol/logging-facade#readme"; description = "Simple logging abstraction that allows multiple back-ends"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "logging-facade-syslog" = callPackage - ({ mkDerivation, base, hsyslog, logging-facade, stdenv }: + ({ mkDerivation, base, hsyslog, lib, logging-facade }: mkDerivation { pname = "logging-facade-syslog"; version = "1"; @@ -20886,38 +24733,46 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/peti/logging-facade-syslog#readme"; description = "A logging back-end to syslog(3) for the logging-facade library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "logict" = callPackage - ({ mkDerivation, base, mtl, stdenv }: + ({ mkDerivation, base, lib, mtl }: mkDerivation { pname = "logict"; - version = "0.6.0.2"; - sha256 = "1182b68e8d00279460c7fb9b8284bf129805c07754c678b2a8de5a6d768e161e"; + version = "0.7.1.0"; + sha256 = "272e4f0ed1a2eb1c09301a8387dc3b9b86b93a3326e8acd02c53598af25942b4"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ base mtl ]; doHaddock = false; doCheck = false; - homepage = "http://code.haskell.org/~dolio/"; + homepage = "https://github.com/Bodigrim/logict#readme"; description = "A backtracking logic-programming monad"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "long-double" = callPackage - ({ mkDerivation, base, integer-gmp, stdenv }: + "logstash" = callPackage + ({ mkDerivation, aeson, async, base, bytestring, data-default-class + , exceptions, lib, monad-control, mtl, network, resource-pool + , resourcet, retry, stm, stm-chans, time, tls, unbounded-delays + , unliftio + }: mkDerivation { - pname = "long-double"; - version = "0.1"; - sha256 = "9218e8175afe5fb69aae72ad65c8b4dfdc943f137a5e95184673a03dc3765e1c"; - revision = "1"; - editedCabalFile = "12vmzzrxgb4yqf9axf1fildl4m0dfm3zqxk4vg6k6m5qi6haz1yn"; - libraryHaskellDepends = [ base integer-gmp ]; + pname = "logstash"; + version = "0.1.0.1"; + sha256 = "d1b951c6d6d4b59a9e10d826b87419eaed00b107d53cb1c7f333cb18493d27c2"; + libraryHaskellDepends = [ + aeson async base bytestring data-default-class exceptions + monad-control mtl network resource-pool resourcet retry stm + stm-chans time tls unbounded-delays unliftio + ]; doHaddock = false; doCheck = false; - homepage = "https://code.mathr.co.uk/long-double"; - description = "FFI bindings for C long double"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/mbg/logstash#readme"; + description = "Logstash client library for Haskell"; + license = lib.licenses.mit; }) {}; "loop" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "loop"; version = "0.3.0"; @@ -20927,18 +24782,31 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/nh2/loop"; description = "Fast loops (for when GHC can't optimize forM_)"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "lrucache" = callPackage + ({ mkDerivation, base, containers, contravariant, lib }: + mkDerivation { + pname = "lrucache"; + version = "1.2.0.1"; + sha256 = "fc1ab2375eeaae181d838095354d3ef77d4072815006a285dd39a165a5855b85"; + libraryHaskellDepends = [ base containers contravariant ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/chowells79/lrucache"; + description = "a simple, pure LRU cache"; + license = lib.licenses.bsd3; }) {}; "lrucaching" = callPackage - ({ mkDerivation, base, base-compat, deepseq, hashable, psqueues - , stdenv, vector + ({ mkDerivation, base, base-compat, deepseq, hashable, lib + , psqueues, vector }: mkDerivation { pname = "lrucaching"; version = "0.3.3"; sha256 = "aa7e5fd27963c70fc1108a7c0526ca0e05f76ccd885844bc50bdae70d5174aa4"; - revision = "5"; - editedCabalFile = "0dfrgg60nd7l7pfjar1s1g380r4591y6ccv9fyh0n34ymhizk84y"; + revision = "10"; + editedCabalFile = "1yzmwvwzby4dx896jlgznlpigqlsl475a57l1npjz0rimlqr71w6"; libraryHaskellDepends = [ base base-compat deepseq hashable psqueues vector ]; @@ -20946,40 +24814,88 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/cocreature/lrucaching#readme"; description = "LRU cache"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "lsp" = callPackage + ({ mkDerivation, aeson, async, attoparsec, base, bytestring + , containers, data-default, dependent-map, directory, filepath + , hashable, hslogger, lens, lib, lsp-types, mtl, network-uri + , random, scientific, sorted-list, stm, text, time, transformers + , unliftio-core, unordered-containers, uuid + }: + mkDerivation { + pname = "lsp"; + version = "1.2.0.0"; + sha256 = "669115cbb0ed0c6a43ecab5e0d063e0231c4c637ed904e43ac3341da09d24831"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson async attoparsec base bytestring containers data-default + dependent-map directory filepath hashable hslogger lens lsp-types + mtl network-uri random scientific sorted-list stm text time + transformers unliftio-core unordered-containers uuid + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell/lsp"; + description = "Haskell library for the Microsoft Language Server Protocol"; + license = lib.licenses.mit; }) {}; "lsp-test" = callPackage - ({ mkDerivation, aeson, aeson-pretty, ansi-terminal, base + ({ mkDerivation, aeson, aeson-pretty, ansi-terminal, async, base , bytestring, conduit, conduit-parse, containers, data-default - , Diff, directory, filepath, haskell-lsp, lens, mtl - , parser-combinators, process, stdenv, text, transformers, unix - , unordered-containers, yi-rope + , Diff, directory, filepath, Glob, lens, lib, lsp-types, mtl + , parser-combinators, process, some, text, time, transformers, unix + , unordered-containers }: mkDerivation { pname = "lsp-test"; - version = "0.5.0.2"; - sha256 = "aa33cf1bd1e68122f86d71147cda41931f0c020a2ef2ff8ffcbead543ce2b33c"; + version = "0.14.0.0"; + sha256 = "99ddd75b9250612342ca87f3485751d17ee725996acca5e66ba60d42556446dd"; libraryHaskellDepends = [ - aeson aeson-pretty ansi-terminal base bytestring conduit - conduit-parse containers data-default Diff directory filepath - haskell-lsp lens mtl parser-combinators process text transformers - unix unordered-containers yi-rope + aeson aeson-pretty ansi-terminal async base bytestring conduit + conduit-parse containers data-default Diff directory filepath Glob + lens lsp-types mtl parser-combinators process some text time + transformers unix unordered-containers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/Bubba/haskell-lsp-test#readme"; + homepage = "https://github.com/haskell/lsp/blob/master/lsp-test/README.md"; description = "Functional test framework for LSP servers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "lucid" = callPackage + "lsp-types" = callPackage + ({ mkDerivation, aeson, base, binary, bytestring, containers + , data-default, deepseq, dependent-sum, dependent-sum-template + , directory, filepath, hashable, hslogger, lens, lib, network-uri + , rope-utf16-splay, scientific, some, template-haskell, temporary + , text, unordered-containers + }: + mkDerivation { + pname = "lsp-types"; + version = "1.2.0.0"; + sha256 = "637a85878d7b8c895311eb6878f19c43038ef93db1e4de4820b04fa7bc30b4ab"; + libraryHaskellDepends = [ + aeson base binary bytestring containers data-default deepseq + dependent-sum dependent-sum-template directory filepath hashable + hslogger lens network-uri rope-utf16-splay scientific some + template-haskell temporary text unordered-containers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell/lsp"; + description = "Haskell library for the Microsoft Language Server Protocol, data types"; + license = lib.licenses.mit; + }) {}; + "lucid" = callPackage ({ mkDerivation, base, blaze-builder, bytestring, containers - , hashable, mmorph, mtl, stdenv, text, transformers + , hashable, lib, mmorph, mtl, text, transformers , unordered-containers }: mkDerivation { pname = "lucid"; - version = "2.9.11"; - sha256 = "8ca524b9ca7984a83b18916b0c9dfb79002cb3bbe88f5139f68bfbe46010bf8f"; + version = "2.9.12.1"; + sha256 = "41e0e76df02737c1ef19dfad88482fbac3918d9e206939de440299d6f1257e5a"; libraryHaskellDepends = [ base blaze-builder bytestring containers hashable mmorph mtl text transformers unordered-containers @@ -20988,62 +24904,94 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/chrisdone/lucid"; description = "Clear to write, read and edit DSL for HTML"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "lucid-cdn" = callPackage + ({ mkDerivation, base, lib, lucid }: + mkDerivation { + pname = "lucid-cdn"; + version = "0.2.2.0"; + sha256 = "ab99d0c064b5a40c9356b36af3659382d9532abd1d5ec02f4af910c0ba482d85"; + libraryHaskellDepends = [ base lucid ]; + doHaddock = false; + doCheck = false; + description = "Curated list of CDN imports for lucid"; + license = lib.licenses.mit; }) {}; "lucid-extras" = callPackage - ({ mkDerivation, aeson, base, blaze-builder, bytestring, lucid - , stdenv, text + ({ mkDerivation, aeson, base, blaze-builder, bytestring, lib, lucid + , text }: mkDerivation { pname = "lucid-extras"; - version = "0.1.0.1"; - sha256 = "5cc5e269c313cba6871b70d48825e6b63ae49db91d507b7f9dccc10bf12dcb73"; - revision = "1"; - editedCabalFile = "030mj3yddbia6dkbl8d6mssi42l3z8gs79z50r78gwiif6mh5dny"; + version = "0.2.2"; + sha256 = "83399f85c9461c44c8dd6d34a076fdefa7f9cb1f92dba5f3d03989233c45247e"; libraryHaskellDepends = [ aeson base blaze-builder bytestring lucid text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/diffusionkinetics/open/lucid-extras"; - description = "Generate more HTML with Lucid"; - license = stdenv.lib.licenses.mit; + description = "Generate more HTML with Lucid - Bootstrap, Rdash, Vega-Lite, Leaflet JS, Email"; + license = lib.licenses.mit; + }) {}; + "lukko" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "lukko"; + version = "0.1.1.3"; + sha256 = "a80efb60cfa3dae18682c01980d76d5f7e413e191cd186992e1bf7388d48ab1f"; + revision = "1"; + editedCabalFile = "0mmq1q82mrbayiij0p8wdnkf0j8drmq1iibg8kn4cak3nrn9pd1d"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + description = "File locking"; + license = "GPL-2.0-or-later AND BSD-3-Clause"; }) {}; - "lxd-client-config" = callPackage - ({ mkDerivation, aeson, base, containers, directory, filepath - , stdenv, text, yaml + "lz4-frame-conduit" = callPackage + ({ mkDerivation, base, bytestring, conduit, conduit-extra + , containers, inline-c, lib, optparse-applicative, raw-strings-qq + , resourcet, template-haskell, text, unliftio, unliftio-core }: mkDerivation { - pname = "lxd-client-config"; + pname = "lz4-frame-conduit"; version = "0.1.0.1"; - sha256 = "903852c99bebc0af3cc3a26734056003f9097ada08eb1f361abce097a120afcf"; + sha256 = "8aaa35bf6c2f4a0dc04a63217b5a29e556f8a485a40c89dfd4b10accdb630758"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - aeson base containers directory filepath text yaml + base bytestring conduit conduit-extra containers inline-c + raw-strings-qq resourcet template-haskell unliftio unliftio-core + ]; + executableHaskellDepends = [ + base bytestring conduit conduit-extra optparse-applicative + resourcet text ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/hverr/haskell-lxd-client-config#readme"; - description = "Read the configuration file of the standard LXD client"; - license = stdenv.lib.licenses.gpl3; + homepage = "https://github.com/nh2/lz4-frame-conduit#readme"; + description = "Conduit implementing the official LZ4 frame streaming format"; + license = lib.licenses.mit; }) {}; "lzma" = callPackage - ({ mkDerivation, base, bytestring, lzma, stdenv }: + ({ mkDerivation, base, bytestring, lib, lzma }: mkDerivation { pname = "lzma"; version = "0.0.0.3"; sha256 = "af8321c3511bde3e2745093fa3bd74c642e386db7d2e7c43b3a54814f1338144"; - revision = "3"; - editedCabalFile = "1sify6gnsalyp6dakfzi0mdy5jcz2kcp9jsdsgkmxd40nfzgd44m"; + revision = "6"; + editedCabalFile = "1sh2g5wkh0m6646cxnii0k20f0crwdcnprfl9jfg7gxn5875bkip"; libraryHaskellDepends = [ base bytestring ]; librarySystemDepends = [ lzma ]; doHaddock = false; doCheck = false; homepage = "https://github.com/hvr/lzma"; description = "LZMA/XZ compression and decompression"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) lzma;}; "lzma-conduit" = callPackage - ({ mkDerivation, base, bytestring, conduit, lzma, resourcet, stdenv + ({ mkDerivation, base, bytestring, conduit, lib, lzma, resourcet , transformers }: mkDerivation { @@ -21057,19 +25005,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/alphaHeavy/lzma-conduit"; description = "Conduit interface for lzma/xz compression"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "machines" = callPackage - ({ mkDerivation, adjunctions, base, Cabal, cabal-doctest, comonad - , containers, distributive, mtl, pointed, profunctors - , semigroupoids, semigroups, stdenv, transformers - , transformers-compat, void + ({ mkDerivation, adjunctions, base, comonad, containers + , distributive, lib, mtl, pointed, profunctors, semigroupoids + , semigroups, transformers, transformers-compat, void }: mkDerivation { pname = "machines"; - version = "0.6.4"; - sha256 = "72de2b2e27cb36832ec4a66de36f1ba6c53d2abd197b7f0351865b4567db7768"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "0.7.2"; + sha256 = "796b8d8bf6f363c6e381d1233cb7f3336accc6e365354cbfaa3fd0248f51fa5d"; libraryHaskellDepends = [ adjunctions base comonad containers distributive mtl pointed profunctors semigroupoids semigroups transformers @@ -21079,78 +25025,73 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/machines/"; description = "Networked stream transducers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "machines-binary" = callPackage - ({ mkDerivation, base, binary, bytestring, machines, stdenv }: + ({ mkDerivation, base, binary, bytestring, lib, machines }: mkDerivation { pname = "machines-binary"; - version = "0.3.0.3"; - sha256 = "60ff456d658ea1a427f32ee5ae1c726e2e7703942bd33edf28b457d753c20652"; + version = "7.0.0.0"; + sha256 = "6825e14d01b872e552cafc2536c29e519af8da0954ba35279bc5b2901ed0ed97"; libraryHaskellDepends = [ base binary bytestring machines ]; doHaddock = false; doCheck = false; homepage = "http://github.com/aloiscochard/machines-binary"; description = "Binary utilities for the machines library"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; }) {}; - "machines-directory" = callPackage - ({ mkDerivation, base, directory, filepath, machines, machines-io - , stdenv, transformers - }: + "magic" = callPackage + ({ mkDerivation, base, file, lib }: mkDerivation { - pname = "machines-directory"; - version = "0.2.1.0"; - sha256 = "849c07db6ff6cfd88348d228a7a3f8ccb16e99568230ee0d20faa5670474deb4"; - libraryHaskellDepends = [ - base directory filepath machines machines-io transformers - ]; + pname = "magic"; + version = "1.1"; + sha256 = "b21c3b69f57b64199c1d7be0ac8ea1d02d698be59943058f6a2d642ea57ce082"; + libraryHaskellDepends = [ base ]; + librarySystemDepends = [ file ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/aloiscochard/machines-directory"; - description = "Directory (system) utilities for the machines library"; - license = stdenv.lib.licenses.asl20; - }) {}; - "machines-io" = callPackage - ({ mkDerivation, base, bytestring, chunked-data, machines, stdenv - , transformers + description = "Interface to C file/magic library"; + license = lib.licenses.bsd3; + }) {inherit (pkgs) file;}; + "magico" = callPackage + ({ mkDerivation, base, comfort-array, lapack, lib, transformers + , utility-ht }: mkDerivation { - pname = "machines-io"; - version = "0.2.0.13"; - sha256 = "4d579d5e9e94fafcfca91322734263498999d2e2af45c40ff0d1db78f4a8f5d4"; - libraryHaskellDepends = [ - base bytestring chunked-data machines transformers + pname = "magico"; + version = "0.0.2.1"; + sha256 = "9d744003a09cfb119dcda858300e2b92c7ca9e1def7a85b6c1e88ccffa5198cd"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ + base comfort-array lapack transformers utility-ht ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/aloiscochard/machines-io"; - description = "IO utilities for the machines library"; - license = stdenv.lib.licenses.asl20; + homepage = "http://hub.darcs.net/thielema/magico"; + description = "Compute solutions for Magico puzzle"; + license = lib.licenses.bsd3; }) {}; "main-tester" = callPackage - ({ mkDerivation, base, bytestring, directory, stdenv }: + ({ mkDerivation, base, bytestring, directory, lib }: mkDerivation { pname = "main-tester"; - version = "0.2.0.0"; - sha256 = "ccb278588b0d68eb98626acc5e588348cdae5acffbb6e699becf6b08d23d0b47"; + version = "0.2.0.1"; + sha256 = "cf06f5934e374e1972f2cc76701c03d67c5536034d9ad32cace4e03819a57842"; libraryHaskellDepends = [ base bytestring directory ]; doHaddock = false; doCheck = false; homepage = "https://gitlab.com/igrep/main-tester#readme"; description = "Capture stdout/stderr/exit code, and replace stdin of your main function"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; }) {}; "mainland-pretty" = callPackage - ({ mkDerivation, base, containers, srcloc, stdenv, text - , transformers + ({ mkDerivation, base, containers, lib, srcloc, text, transformers }: mkDerivation { pname = "mainland-pretty"; - version = "0.7"; - sha256 = "11777bd365251813c512a3e17e0303b30f2a86411a12118751858cbb20dbeaf7"; - revision = "1"; - editedCabalFile = "1apyqnbcsbjfkqc1d6mk74pxl12130r6ijwhj555gddls9g0qdf3"; + version = "0.7.1"; + sha256 = "e1a62188ff030f4cbc1b5e92b37995a96c81dd122e0a1af5e6d3cc989339e2a7"; libraryHaskellDepends = [ base containers srcloc text transformers ]; @@ -21158,10 +25099,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mainland/mainland-pretty"; description = "Pretty printing designed for printing source code"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "makefile" = callPackage - ({ mkDerivation, attoparsec, base, stdenv, text }: + ({ mkDerivation, attoparsec, base, lib, text }: mkDerivation { pname = "makefile"; version = "1.1.0.0"; @@ -21171,40 +25112,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/nmattia/mask"; description = "Simple Makefile parser and generator"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "managed" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "managed"; - version = "1.0.6"; - sha256 = "f1a70a23c0866b75d609b2c818b426712d7a2b4256f43a3d5da517e853e279cd"; + version = "1.0.8"; + sha256 = "687c9bc525c4500afd731fc1310e083c9dfca2eaeb7c1a738d8f33e592779f03"; libraryHaskellDepends = [ base transformers ]; doHaddock = false; doCheck = false; description = "A monad for managed values"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "mapquest-api" = callPackage - ({ mkDerivation, aeson, base, bytestring, exceptions, goggles, mtl - , req, stdenv, text - }: - mkDerivation { - pname = "mapquest-api"; - version = "0.3.1"; - sha256 = "43339221b91816e8f793a98a4d281285e8e9de8788f13bb30ec345ef855a7b85"; - libraryHaskellDepends = [ - aeson base bytestring exceptions goggles mtl req text - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/ocramz/mapquest-api"; - description = "Bindings to the MapQuest API"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "markdown" = callPackage ({ mkDerivation, attoparsec, base, blaze-html, blaze-markup - , conduit, conduit-extra, containers, data-default, stdenv, text + , conduit, conduit-extra, containers, data-default, lib, text , transformers, xml-conduit, xml-types, xss-sanitize }: mkDerivation { @@ -21220,14 +25144,14 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/snoyberg/markdown"; description = "Convert Markdown to HTML, with XSS protection"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "markdown-unlit" = callPackage - ({ mkDerivation, base, base-compat, stdenv }: + ({ mkDerivation, base, base-compat, lib }: mkDerivation { pname = "markdown-unlit"; - version = "0.5.0"; - sha256 = "e72d0d7b82525e2a2c664012ce9dc35835b3fff91040d9f20897ed82f24ec7bf"; + version = "0.5.1"; + sha256 = "c70ef68ca9a9513ce26eba6dd4cf7ce1cb6b17f5ab47dfc1a9d47c544db15f5a"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base base-compat ]; @@ -21236,10 +25160,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/sol/markdown-unlit#readme"; description = "Literate Haskell support for Markdown"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "markov-chain" = callPackage - ({ mkDerivation, base, containers, random, stdenv, transformers }: + ({ mkDerivation, base, containers, lib, random, transformers }: mkDerivation { pname = "markov-chain"; version = "0.0.3.4"; @@ -21252,60 +25176,123 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; license = "GPL"; }) {}; "massiv" = callPackage - ({ mkDerivation, base, bytestring, data-default-class, deepseq - , ghc-prim, primitive, stdenv, vector + ({ mkDerivation, base, bytestring, deepseq, exceptions, lib + , primitive, scheduler, unliftio-core, vector }: mkDerivation { pname = "massiv"; - version = "0.2.6.0"; - sha256 = "4e10b3617ce46385067ef4c2827e8ea8a8331657f86209d04ed8ef899dd1b61e"; + version = "0.6.1.0"; + sha256 = "3b25d023d194a498071c0cee141f60543444910384b8560b0ecbf73e47ca6b48"; libraryHaskellDepends = [ - base bytestring data-default-class deepseq ghc-prim primitive - vector + base bytestring deepseq exceptions primitive scheduler + unliftio-core vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/lehins/massiv"; description = "Massiv (Массив) is an Array Library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "massiv-io" = callPackage - ({ mkDerivation, base, bytestring, data-default, deepseq, directory - , filepath, JuicyPixels, massiv, netpbm, process, stdenv, vector + ({ mkDerivation, base, bytestring, Color, data-default-class + , deepseq, exceptions, filepath, JuicyPixels, lib, massiv, netpbm + , unliftio, vector }: mkDerivation { pname = "massiv-io"; - version = "0.1.5.0"; - sha256 = "dc89ab0f965adec0c16784f6feec75903b99b8366426c85e167b405b5b36f8ed"; + version = "0.4.1.0"; + sha256 = "871506435247d2d0af95213da151353957eac52ea61965063e71801e20b140bc"; libraryHaskellDepends = [ - base bytestring data-default deepseq directory filepath JuicyPixels - massiv netpbm process vector + base bytestring Color data-default-class deepseq exceptions + filepath JuicyPixels massiv netpbm unliftio vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/lehins/massiv"; + homepage = "https://github.com/lehins/massiv-io"; description = "Import/export of Image files into massiv Arrays"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "massiv-persist" = callPackage + ({ mkDerivation, base, bytestring, deepseq, lib, massiv, persist + , primitive + }: + mkDerivation { + pname = "massiv-persist"; + version = "0.1.0.0"; + sha256 = "c11ca6614afc1578bf4d0b271fd6c9d00b3a190b549fe92b687a8bf92baa7070"; + libraryHaskellDepends = [ + base bytestring deepseq massiv persist primitive + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/lehins/massiv-compat"; + description = "Compatibility of 'massiv' with 'persist'"; + license = lib.licenses.bsd3; + }) {}; + "massiv-serialise" = callPackage + ({ mkDerivation, base, deepseq, lib, massiv, serialise, vector }: + mkDerivation { + pname = "massiv-serialise"; + version = "0.1.0.0"; + sha256 = "03b18f5d3f0105facdefb7eced7e9af5813e27fc47b0012f31739061dfa3001d"; + libraryHaskellDepends = [ base deepseq massiv serialise vector ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/lehins/massiv-compat"; + description = "Compatibility of 'massiv' with 'serialise'"; + license = lib.licenses.bsd3; + }) {}; + "massiv-test" = callPackage + ({ mkDerivation, base, bytestring, data-default-class, deepseq + , exceptions, hspec, lib, massiv, primitive, QuickCheck, scheduler + , unliftio, vector + }: + mkDerivation { + pname = "massiv-test"; + version = "0.1.6.1"; + sha256 = "a7b4f9e67d5bd461d190912cba3d157ff5063284ef53cc83d46046ea02204e38"; + libraryHaskellDepends = [ + base bytestring data-default-class deepseq exceptions hspec massiv + primitive QuickCheck scheduler unliftio vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/lehins/massiv"; + description = "Library that contains generators, properties and tests for Massiv Array Library"; + license = lib.licenses.bsd3; + }) {}; + "math-extras" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "math-extras"; + version = "0.1.1.0"; + sha256 = "894c0dac5fb53ef41e47cad8e1ae0531b420904b178dd2a9852ac1a1ce11f343"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/zliu41/math-extras"; + description = "A variety of mathematical utilities"; + license = lib.licenses.bsd3; }) {}; "math-functions" = callPackage - ({ mkDerivation, base, data-default-class, deepseq, primitive - , stdenv, vector, vector-th-unbox + ({ mkDerivation, base, data-default-class, deepseq, lib, primitive + , vector }: mkDerivation { pname = "math-functions"; - version = "0.3.1.0"; - sha256 = "3340ebec0ab91444f86ce3f785db920b8acfd5fbad70d38abcb02b77ac0f6655"; + version = "0.3.4.2"; + sha256 = "c1e50ac0d23492b684cce33a9a979e1315ac144175b54f82eade9b8b1885c1a3"; libraryHaskellDepends = [ - base data-default-class deepseq primitive vector vector-th-unbox + base data-default-class deepseq primitive vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/bos/math-functions"; description = "Collection of tools for numeric computations"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; }) {}; "mathexpr" = callPackage - ({ mkDerivation, base, data-default-class, stdenv }: + ({ mkDerivation, base, data-default-class, lib }: mkDerivation { pname = "mathexpr"; version = "0.3.0.0"; @@ -21315,22 +25302,40 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mdibaiee/mathexpr"; description = "Parse and evaluate math expressions with variables and functions"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; + }) {}; + "matplotlib" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers, deepseq + , filepath, lib, process, split, temporary + }: + mkDerivation { + pname = "matplotlib"; + version = "0.7.5"; + sha256 = "9a05e177ce4a0d39f117e89af2390c42a09ec7ef1be39c66c6f45c59a4c9d247"; + libraryHaskellDepends = [ + aeson base bytestring containers deepseq filepath process split + temporary + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/abarbu/matplotlib-haskell"; + description = "Bindings to Matplotlib; a Python plotting library"; + license = lib.licenses.bsd3; }) {}; "matrices" = callPackage - ({ mkDerivation, base, deepseq, primitive, stdenv, vector }: + ({ mkDerivation, base, deepseq, lib, primitive, vector }: mkDerivation { pname = "matrices"; - version = "0.4.5"; - sha256 = "2d396f130d675eabaa435caba122fe2b2c1d2dfc5343471131b7392e479b7397"; + version = "0.5.0"; + sha256 = "fd013f0b061f7fd006242340fb6bc936114c8fc7d255ba58bd54cd1d66391d4d"; libraryHaskellDepends = [ base deepseq primitive vector ]; doHaddock = false; doCheck = false; description = "native matrix based on vector"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "matrix" = callPackage - ({ mkDerivation, base, deepseq, loop, primitive, semigroups, stdenv + ({ mkDerivation, base, deepseq, lib, loop, primitive, semigroups , vector }: mkDerivation { @@ -21345,16 +25350,31 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A native implementation of matrix operations"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "matrix-as-xyz" = callPackage + ({ mkDerivation, base, lib, matrix, parsec }: + mkDerivation { + pname = "matrix-as-xyz"; + version = "0.1.2.2"; + sha256 = "fc48410defd37497865f91c2d77f5cab8c3ece0b678b3b65f2e68f84ccfe74e1"; + revision = "2"; + editedCabalFile = "01r2n4ys2z92wkdpky171dbxklynvp5cjf7vi61sf4hjdqih17nf"; + libraryHaskellDepends = [ base matrix parsec ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/narumij/matrix-as-xyz#readme"; + description = "Read and Display Jones-Faithful notation for spacegroup and planegroup"; + license = lib.licenses.bsd3; }) {}; "matrix-market-attoparsec" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, exceptions - , scientific, stdenv + ({ mkDerivation, attoparsec, base, bytestring, exceptions, lib + , scientific }: mkDerivation { pname = "matrix-market-attoparsec"; - version = "0.1.0.8"; - sha256 = "5e41aa81abdfd6062dc4607ea7c684b9ac09a286d2ebf76829504acf09260a77"; + version = "0.1.1.3"; + sha256 = "32b79a75c8cf5b21a40ea51bc091ee5fd4809483d933b0dbc578528ccf8e924d"; enableSeparateDataOutput = true; libraryHaskellDepends = [ attoparsec base bytestring exceptions scientific @@ -21363,28 +25383,27 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/ocramz/matrix-market-attoparsec"; description = "Parsing and serialization functions for the NIST Matrix Market format"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; }) {}; "matrix-static" = callPackage - ({ mkDerivation, base, deepseq, ghc-typelits-knownnat - , ghc-typelits-natnormalise, matrix, stdenv, vector + ({ mkDerivation, base, deepseq, ghc-typelits-natnormalise, lib + , matrix, vector }: mkDerivation { pname = "matrix-static"; - version = "0.2"; - sha256 = "07e46233ba35c0f8fcb14af7863cfd728895b603a2196495e89a7069d89f9b3c"; + version = "0.3"; + sha256 = "bb2a25faf407554a50707d7a65918f0d0c182ef3b06a730408145123b98cfb3c"; libraryHaskellDepends = [ - base deepseq ghc-typelits-knownnat ghc-typelits-natnormalise matrix - vector + base deepseq ghc-typelits-natnormalise matrix vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/wchresta/matrix-static#readme"; description = "Type-safe matrix operations"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "maximal-cliques" = callPackage - ({ mkDerivation, base, containers, stdenv, vector }: + ({ mkDerivation, base, containers, lib, vector }: mkDerivation { pname = "maximal-cliques"; version = "0.1.1"; @@ -21393,11 +25412,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Enumerate all maximal cliques of a graph"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "mbox" = callPackage - ({ mkDerivation, base, safe, stdenv, text, time, time-locale-compat - }: + ({ mkDerivation, base, lib, safe, text, time, time-locale-compat }: mkDerivation { pname = "mbox"; version = "0.3.4"; @@ -21408,92 +25426,112 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Read and write standard mailbox files"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "mbox-utility" = callPackage - ({ mkDerivation, base, bytestring, hsemail, non-empty, old-time - , parsec, spreadsheet, stdenv, utility-ht + ({ mkDerivation, base, bytestring, hsemail, lib, non-empty, parsec + , spreadsheet, time, utility-ht }: mkDerivation { pname = "mbox-utility"; - version = "0.0.1"; - sha256 = "e5e009f83c95b20d85c4b39d233b2f32ee15eae08d54edbaa7928848ae15e9f8"; + version = "0.0.3.1"; + sha256 = "22a938ab138641477017bfd2237219934c6d8a52357f2713d6da8d47e08a096e"; isLibrary = false; isExecutable = true; executableHaskellDepends = [ - base bytestring hsemail non-empty old-time parsec spreadsheet + base bytestring hsemail non-empty parsec spreadsheet time utility-ht ]; doHaddock = false; doCheck = false; description = "List contents of an mbox file containing e-mails"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "mbtiles" = callPackage - ({ mkDerivation, base, bytestring, directory, monad-control, mtl - , resource-pool, sqlite-simple, stdenv, text, transformers - , unordered-containers + "mcmc" = callPackage + ({ mkDerivation, aeson, base, bytestring, circular, containers + , data-default, deepseq, directory, dirichlet, double-conversion + , lib, log-domain, microlens, monad-parallel, mwc-random + , pretty-show, primitive, statistics, time, transformers, vector + , zlib }: mkDerivation { - pname = "mbtiles"; - version = "0.6.0.0"; - sha256 = "b8a82f0a1c551a59961449587f031f679dd2f5f082ce45b6f7d88d81f99ad62f"; + pname = "mcmc"; + version = "0.5.0.0"; + sha256 = "517b5e8c16337848b8735b2fc664c0afd3beea00b9e3e028b0eaf17ce65fcb6d"; + libraryHaskellDepends = [ + aeson base bytestring circular containers data-default deepseq + directory dirichlet double-conversion log-domain microlens + monad-parallel mwc-random pretty-show primitive statistics time + transformers vector zlib + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/dschrempf/mcmc#readme"; + description = "Sample from a posterior using Markov chain Monte Carlo"; + license = lib.licenses.gpl3Plus; + }) {}; + "mcmc-types" = callPackage + ({ mkDerivation, base, containers, lib, mwc-probability + , transformers + }: + mkDerivation { + pname = "mcmc-types"; + version = "1.0.3"; + sha256 = "3c4b25030b05567694ddc313ca808a32133ad5433b4d89837e1ed00bbfcefc6e"; libraryHaskellDepends = [ - base bytestring directory monad-control mtl resource-pool - sqlite-simple text transformers unordered-containers + base containers mwc-probability transformers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/caneroj1/mbtiles#readme"; - description = "Haskell MBTiles client"; - license = stdenv.lib.licenses.bsd3; + homepage = "http://github.com/jtobin/mcmc-types"; + description = "Common types for sampling"; + license = lib.licenses.mit; }) {}; - "mbug" = callPackage - ({ mkDerivation, base, bytestring, directory, extra, formatting - , http-client, http-client-tls, mtl, optparse-applicative, process - , scalpel-core, stdenv, tagsoup, text, time, xdg-basedir + "med-module" = callPackage + ({ mkDerivation, base, bytestring, lib, storable-endian + , transformers, utility-ht }: mkDerivation { - pname = "mbug"; - version = "1.3.2"; - sha256 = "cd0e82e9470616bdcd03a32f0f4cb7204cca554310893ca5548149beb9fd9e15"; + pname = "med-module"; + version = "0.1.2.1"; + sha256 = "f782cfad5cba28e87a24e61c4553e9205689108e08c817a7f8e625d463933e38"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - base bytestring directory extra formatting http-client - http-client-tls mtl optparse-applicative process scalpel-core - tagsoup text time xdg-basedir - ]; - executableHaskellDepends = [ - base bytestring directory extra formatting http-client - http-client-tls mtl optparse-applicative process scalpel-core - tagsoup text time xdg-basedir + base bytestring storable-endian transformers utility-ht ]; doHaddock = false; doCheck = false; - homepage = "https://gitlab.com/iu-guest/mbug"; - description = "download bugs mailboxes"; - license = stdenv.lib.licenses.gpl3; + description = "Parse song module files from Amiga MED and OctaMED"; + license = lib.licenses.gpl3Only; }) {}; - "mcmc-types" = callPackage - ({ mkDerivation, base, containers, mwc-probability, stdenv - , transformers + "medea" = callPackage + ({ mkDerivation, aeson, algebraic-graphs, base, bytestring + , containers, deepseq, free, hashable, lib, megaparsec + , microlens-ghc, mtl, nonempty-containers, parser-combinators + , scientific, smash, text, unordered-containers, vector + , vector-instances }: mkDerivation { - pname = "mcmc-types"; - version = "1.0.3"; - sha256 = "3c4b25030b05567694ddc313ca808a32133ad5433b4d89837e1ed00bbfcefc6e"; + pname = "medea"; + version = "1.2.0"; + sha256 = "1b187ef6071cb5a36659acffb50d3397a6a3f0f3ee445f96016dfc97c4773205"; + revision = "2"; + editedCabalFile = "18yzwhmvxafxn0zq7pv8dna28qkpr87q35q0sw9907y1iqcixxfh"; libraryHaskellDepends = [ - base containers mwc-probability transformers + aeson algebraic-graphs base bytestring containers deepseq free + hashable megaparsec microlens-ghc mtl nonempty-containers + parser-combinators scientific smash text unordered-containers + vector vector-instances ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/jtobin/mcmc-types"; - description = "Common types for sampling"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/juspay/medea"; + description = "A schema language for JSON"; + license = lib.licenses.mit; }) {}; "median-stream" = callPackage - ({ mkDerivation, base, heap, stdenv }: + ({ mkDerivation, base, heap, lib }: mkDerivation { pname = "median-stream"; version = "0.7.0.0"; @@ -21503,38 +25541,19 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/caneroj1/median-stream#readme"; description = "Constant-time queries for the median of a stream of numeric data"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "mega-sdist" = callPackage - ({ mkDerivation, base, bytestring, conduit, conduit-extra - , http-conduit, optparse-simple, rio, rio-orphans, stdenv - , tar-conduit, yaml - }: - mkDerivation { - pname = "mega-sdist"; - version = "0.3.3.2"; - sha256 = "a4e1c3ba865a59161bf3ef30fa78310201b2d88ff9e72a6691578f723857144a"; - isLibrary = false; - isExecutable = true; - executableHaskellDepends = [ - base bytestring conduit conduit-extra http-conduit optparse-simple - rio rio-orphans tar-conduit yaml - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/snoyberg/mega-sdist#readme"; - description = "Handles uploading to Hackage from mega repos"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.bsd3; }) {}; "megaparsec" = callPackage ({ mkDerivation, base, bytestring, case-insensitive, containers - , deepseq, mtl, parser-combinators, scientific, stdenv, text + , deepseq, lib, mtl, parser-combinators, scientific, text , transformers }: mkDerivation { pname = "megaparsec"; - version = "7.0.4"; - sha256 = "325ba5cee8cdef91e351fb2db0b38562f8345b0bcdfed97045671357501de8c1"; + version = "9.0.1"; + sha256 = "7228bc49d8636632b481eb13f16f2a9633007b8f55ebc0105f517ad7f71f2501"; + revision = "1"; + editedCabalFile = "00vjc5b1x6yd0jqsbcahvghlkwai65dl1ib6744a0lhsa9vsni12"; libraryHaskellDepends = [ base bytestring case-insensitive containers deepseq mtl parser-combinators scientific text transformers @@ -21543,18 +25562,53 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mrkkrp/megaparsec"; description = "Monadic parser combinators"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; + }) {}; + "megaparsec-tests" = callPackage + ({ mkDerivation, base, bytestring, containers, hspec + , hspec-expectations, hspec-megaparsec, lib, megaparsec, mtl + , QuickCheck, text, transformers + }: + mkDerivation { + pname = "megaparsec-tests"; + version = "9.0.1"; + sha256 = "cf8e344c17a6b3c12cabe858bee97982ac923cf841ecda0f2e39cdd049a8d66b"; + revision = "1"; + editedCabalFile = "1iz18gmhqvxwiw6r35nd6p2m3zjpzsy0bzhwgbfxpjbvvcgy8736"; + libraryHaskellDepends = [ + base bytestring containers hspec hspec-expectations + hspec-megaparsec megaparsec mtl QuickCheck text transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/mrkkrp/megaparsec"; + description = "Test utilities and the test suite of Megaparsec"; + license = lib.licenses.bsd2; + }) {}; + "membrain" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "membrain"; + version = "0.0.0.2"; + sha256 = "8c1dc77e506ea096c1cc6d92273da97186609449db703927d25cd4f7e2943fda"; + revision = "1"; + editedCabalFile = "02yayszbb6g7q7cz9gkjbxzn28v4zm1i9svzydzlrzfds9z603r6"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/kowainik/membrain"; + description = "Type-safe memory units"; + license = lib.licenses.mpl20; }) {}; "memory" = callPackage - ({ mkDerivation, base, basement, bytestring, deepseq, ghc-prim - , stdenv + ({ mkDerivation, base, basement, bytestring, deepseq, ghc-prim, lib }: mkDerivation { pname = "memory"; - version = "0.14.18"; - sha256 = "f5458d170a291788ac8da896bb44b0cc84021c99dd596c52adf2f7a7f6c03507"; - revision = "1"; - editedCabalFile = "0h4d0avv8kv3my4rim79lcamv2dyibld7w6ianq46nhwgr0h2lzm"; + version = "0.15.0"; + sha256 = "e3ff892c1a94708954d0bb2c4f4ab81bc0f505352d95095319c462db1aeb3529"; + revision = "2"; + editedCabalFile = "0fd40y5byy4cq4x6m66zxadxbw96gzswplgfyvdqnjlasq28xw68"; libraryHaskellDepends = [ base basement bytestring deepseq ghc-prim ]; @@ -21562,16 +25616,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/vincenthz/hs-memory"; description = "memory and related abstraction stuff"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "mercury-api" = callPackage ({ mkDerivation, ansi-terminal, base, bytestring, clock, hashable - , optparse-applicative, stdenv, text, unordered-containers + , lib, optparse-applicative, text, unordered-containers }: mkDerivation { pname = "mercury-api"; version = "0.1.0.2"; sha256 = "0f4ed76a96029413aef856a00defaa5d75be196a12a0dc1e75b9a0a866607779"; + revision = "6"; + editedCabalFile = "03d71mfq8nvqjr7hcpkh1q25fi1avqj35mfrrf7rkm13fr49bi7i"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -21585,27 +25641,56 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/ppelleti/hs-mercury-api"; description = "Haskell binding to Mercury API for ThingMagic RFID readers"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "merkle-tree" = callPackage - ({ mkDerivation, base, bytestring, cereal, cryptonite, memory - , protolude, random, stdenv + "mergeful" = callPackage + ({ mkDerivation, aeson, base, containers, deepseq, lib, mtl, text + , time, validity, validity-containers, validity-time }: mkDerivation { - pname = "merkle-tree"; - version = "0.1.1"; - sha256 = "215a62476230374b8bbf2f7a0a3e88345a18cf9c6f672ef7d422c3f6bd5ba2aa"; + pname = "mergeful"; + version = "0.2.0.0"; + sha256 = "8a7b135c5ed58f35d99a1b83cf0b6e282b76626c43fc567e554b1e4934067d33"; + libraryHaskellDepends = [ + aeson base containers deepseq mtl text time validity + validity-containers validity-time + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/mergeful#readme"; + license = lib.licenses.mit; + }) {}; + "mergeless" = callPackage + ({ mkDerivation, aeson, base, containers, deepseq, lib, mtl + , validity, validity-containers + }: + mkDerivation { + pname = "mergeless"; + version = "0.3.0.0"; + sha256 = "24756fde5c0a19bb55b43c9b2008c19d82c06d867fa6f565dedc3b710c746f92"; libraryHaskellDepends = [ - base bytestring cereal cryptonite memory protolude random + aeson base containers deepseq mtl validity validity-containers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/adjoint-io/merkle-tree#readme"; - description = "An implementation of a Merkle tree and merkle tree proofs of inclusion"; - license = stdenv.lib.licenses.asl20; + homepage = "https://github.com/NorfairKing/mergeless#readme"; + license = lib.licenses.mit; + }) {}; + "mersenne-random" = callPackage + ({ mkDerivation, base, lib, old-time }: + mkDerivation { + pname = "mersenne-random"; + version = "1.0.0.1"; + sha256 = "bcee8af246b6967b0c4326f3eec57611818dacc729b7c6bd42e1d363f9f878a4"; + libraryHaskellDepends = [ base old-time ]; + doHaddock = false; + doCheck = false; + homepage = "http://code.haskell.org/~dons/code/mersenne-random"; + description = "Generate high quality pseudorandom numbers using a SIMD Fast Mersenne Twister"; + license = lib.licenses.bsd3; }) {}; "mersenne-random-pure64" = callPackage - ({ mkDerivation, base, random, stdenv, time }: + ({ mkDerivation, base, lib, random, time }: mkDerivation { pname = "mersenne-random-pure64"; version = "0.2.2.0"; @@ -21618,11 +25703,29 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://code.haskell.org/~dons/code/mersenne-random-pure64/"; description = "Generate high quality pseudorandom numbers purely using a Mersenne Twister"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "messagepack" = callPackage + ({ mkDerivation, base, bytestring, cereal, containers, deepseq, lib + }: + mkDerivation { + pname = "messagepack"; + version = "0.5.4"; + sha256 = "939590c05d5b0831b3b4796f2e1a070e290982c92b2009f2aa1ef5f4b05b5d7c"; + revision = "2"; + editedCabalFile = "199x0hqa6h6wqysaip1wc7kivc26f3wkb8y4il70mzmz80skmm29"; + libraryHaskellDepends = [ + base bytestring cereal containers deepseq + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/rodrigosetti/messagepack"; + description = "Serialize instance for Message Pack Object"; + license = lib.licenses.mit; }) {}; "metrics" = callPackage ({ mkDerivation, ansi-terminal, base, bytestring, containers, lens - , mwc-random, primitive, stdenv, text, time, transformers + , lib, mwc-random, primitive, text, time, transformers , transformers-base, unix-compat, unordered-containers, vector , vector-algorithms }: @@ -21638,10 +25741,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "High-performance application metric tracking"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "mfsolve" = callPackage - ({ mkDerivation, base, hashable, mtl, mtl-compat, stdenv + ({ mkDerivation, base, hashable, lib, mtl, mtl-compat , unordered-containers }: mkDerivation { @@ -21654,76 +25757,30 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Equation solver and calculator à la metafont"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "microbench" = callPackage - ({ mkDerivation, base, stdenv, time }: - mkDerivation { - pname = "microbench"; - version = "0.1"; - sha256 = "6fee3c592c9afb72bd7b5574872119464055b717491c612ffee7f57c8e85d717"; - libraryHaskellDepends = [ base time ]; - doHaddock = false; - doCheck = false; - homepage = "http://neugierig.org/software/darcs/browse/?r=microbench;a=summary"; - description = "Microbenchmark Haskell code"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "microformats2-parser" = callPackage - ({ mkDerivation, aeson, aeson-pretty, aeson-qq, attoparsec, base - , base-compat, blaze-html, blaze-markup, bytestring, containers - , data-default, either, errors, html-conduit, lens-aeson, network - , network-uri, options, pcre-heavy, safe, scotty, stdenv, tagsoup - , text, time, transformers, unordered-containers, vector, wai-cli - , wai-extra, xml-lens, xss-sanitize - }: - mkDerivation { - pname = "microformats2-parser"; - version = "1.0.1.9"; - sha256 = "50c71d9cd57991011855ad16759a6d43f56abc0e7424475db5263c5f04e2abd3"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - aeson aeson-qq attoparsec base base-compat blaze-markup bytestring - containers data-default either errors html-conduit lens-aeson - network-uri pcre-heavy safe tagsoup text time transformers - unordered-containers vector xml-lens xss-sanitize - ]; - executableHaskellDepends = [ - aeson aeson-pretty base base-compat blaze-html blaze-markup - data-default network network-uri options scotty text wai-cli - wai-extra - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/myfreeweb/microformats2-parser"; - description = "A Microformats 2 parser"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.bsd3; }) {}; "microlens" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "microlens"; - version = "0.4.10"; - sha256 = "9c55a89d1c91fddcafca4bb1fa99a3ef29223436d75191fb29385de2bd3f47ec"; + version = "0.4.12.0"; + sha256 = "b5427383c3fe24de378b07b50b0bee3d02e70e8cbfb7ae51b1946de5137d0783"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "http://github.com/monadfix/microlens"; - description = "A tiny lens library with no dependencies. If you're writing an app, you probably want microlens-platform, not this."; - license = stdenv.lib.licenses.bsd3; + description = "A tiny lens library with no dependencies"; + license = lib.licenses.bsd3; }) {}; "microlens-aeson" = callPackage ({ mkDerivation, aeson, attoparsec, base, bytestring, deepseq - , hashable, microlens, scientific, stdenv, text - , unordered-containers, vector + , hashable, lib, microlens, scientific, text, unordered-containers + , vector }: mkDerivation { pname = "microlens-aeson"; - version = "2.3.0.1"; - sha256 = "9acd281091453275bacb8c4e1729332b2242d92030300410e25e980c61038bd9"; - revision = "1"; - editedCabalFile = "18490w9yvsn8rx18wb29bg1wj5vxa7il3gsi3cz2myx9iawhnnxq"; + version = "2.3.1"; + sha256 = "7946e052aa0579acc9dfa1d50210f7954afafe9582f87e5c07d16c75e6fd951c"; libraryHaskellDepends = [ aeson attoparsec base bytestring deepseq hashable microlens scientific text unordered-containers vector @@ -21732,10 +25789,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/fosskers/microlens-aeson/"; description = "Law-abiding lenses for Aeson, using microlens"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "microlens-contra" = callPackage - ({ mkDerivation, base, microlens, stdenv }: + ({ mkDerivation, base, lib, microlens }: mkDerivation { pname = "microlens-contra"; version = "0.1.0.2"; @@ -21745,16 +25802,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/monadfix/microlens"; description = "True folds and getters for microlens"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "microlens-ghc" = callPackage - ({ mkDerivation, array, base, bytestring, containers, microlens - , stdenv, transformers + ({ mkDerivation, array, base, bytestring, containers, lib + , microlens, transformers }: mkDerivation { pname = "microlens-ghc"; - version = "0.4.10"; - sha256 = "63784af17969f63fee64684d7ad43187a0b978d85ba1bee15abda9a65b5e4d80"; + version = "0.4.13"; + sha256 = "462409d859b0e7116b709469f57f6adbd502bd0db33620f5ccc98dbc103adde4"; libraryHaskellDepends = [ array base bytestring containers microlens transformers ]; @@ -21762,34 +25819,33 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/monadfix/microlens"; description = "microlens + array, bytestring, containers, transformers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "microlens-mtl" = callPackage - ({ mkDerivation, base, microlens, mtl, stdenv, transformers + ({ mkDerivation, base, lib, microlens, mtl, transformers , transformers-compat }: mkDerivation { pname = "microlens-mtl"; - version = "0.1.11.1"; - sha256 = "d3e74f46a72aad12b71d8549a98fbc023fb364766f17d75742fb32fee70bdf50"; + version = "0.2.0.1"; + sha256 = "d79de8b228631525da3c17999d3b936eb8f919f2303348151b6cd1d27c3f5e46"; libraryHaskellDepends = [ base microlens mtl transformers transformers-compat ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/aelve/microlens"; + homepage = "http://github.com/monadfix/microlens"; description = "microlens support for Reader/Writer/State from mtl"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "microlens-platform" = callPackage - ({ mkDerivation, base, hashable, microlens, microlens-ghc - , microlens-mtl, microlens-th, stdenv, text, unordered-containers - , vector + ({ mkDerivation, base, hashable, lib, microlens, microlens-ghc + , microlens-mtl, microlens-th, text, unordered-containers, vector }: mkDerivation { pname = "microlens-platform"; - version = "0.3.11"; - sha256 = "8b77f0630d022e42deb8438d8383c361555975d07f44efb79ee5e9fa3a0525a1"; + version = "0.4.2"; + sha256 = "87918a6c5160f99b50750e51d41c998c099e20318ceb4fd9ada6094c1ff8c079"; libraryHaskellDepends = [ base hashable microlens microlens-ghc microlens-mtl microlens-th text unordered-containers vector @@ -21797,29 +25853,47 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; homepage = "http://github.com/monadfix/microlens"; - description = "Feature-complete microlens"; - license = stdenv.lib.licenses.bsd3; + description = "microlens + all batteries included (best for apps)"; + license = lib.licenses.bsd3; + }) {}; + "microlens-process" = callPackage + ({ mkDerivation, base, Cabal, cabal-doctest, filepath, lib + , microlens, process + }: + mkDerivation { + pname = "microlens-process"; + version = "0.2.0.2"; + sha256 = "b7535ba62cb7e1afe677920ccc486f86ed9316ca4b5edb0b5972821d66de7037"; + revision = "2"; + editedCabalFile = "04j2yap3ha45wq0slvxkd3gm7gkx2dks9abxfd6mg3asmdp743gk"; + setupHaskellDepends = [ base Cabal cabal-doctest ]; + libraryHaskellDepends = [ base filepath microlens process ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/emilypi/lens-process/tree/master/microlens"; + description = "Micro-optics for the process library"; + license = lib.licenses.bsd3; }) {}; "microlens-th" = callPackage - ({ mkDerivation, base, containers, microlens, stdenv - , template-haskell, th-abstraction, transformers + ({ mkDerivation, base, containers, lib, microlens, template-haskell + , th-abstraction, transformers }: mkDerivation { pname = "microlens-th"; - version = "0.4.2.3"; - sha256 = "321018c6c0aad3f68eb26f6c7e7a518db43039e3f8f19c4634ceb4c7f8051c8f"; + version = "0.4.3.10"; + sha256 = "2c50100235949c00defcdb8c01d8eb5e2e45e524a9b552d3c0c8bb8224ece2b5"; libraryHaskellDepends = [ base containers microlens template-haskell th-abstraction transformers ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/aelve/microlens"; + homepage = "http://github.com/monadfix/microlens"; description = "Automatic generation of record lenses for microlens"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "microspec" = callPackage - ({ mkDerivation, base, QuickCheck, stdenv, time }: + ({ mkDerivation, base, lib, QuickCheck, time }: mkDerivation { pname = "microspec"; version = "0.2.1.3"; @@ -21828,31 +25902,31 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Tiny QuickCheck test library with minimal dependencies"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "microstache" = callPackage - ({ mkDerivation, aeson, base, bytestring, containers, deepseq - , directory, filepath, parsec, stdenv, text, transformers - , unordered-containers, vector + ({ mkDerivation, aeson, base, containers, deepseq, directory + , filepath, lib, parsec, text, transformers, unordered-containers + , vector }: mkDerivation { pname = "microstache"; - version = "1.0.1.1"; - sha256 = "5de98542313eb75f84961366ff8a70ed632387ba6518215035b2dd1b32d6a120"; - revision = "3"; - editedCabalFile = "1pq0h64vxc7zlncn2ld6k02wi6rfa5ccqc4z0hfkvaldj41y2sb1"; + version = "1.0.1.2"; + sha256 = "336e2505889b9af2ea8939a606ec35bc67bab1c9f0eb26bcdbc7b3f24350acf5"; + revision = "1"; + editedCabalFile = "1l72cfbrr6kxh0z2dx2pghxl7ljlbmbk8s9wlgk35bjm925kkxfl"; libraryHaskellDepends = [ - aeson base bytestring containers deepseq directory filepath parsec - text transformers unordered-containers vector + aeson base containers deepseq directory filepath parsec text + transformers unordered-containers vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/phadej/microstache"; + homepage = "https://github.com/haskellari/microstache"; description = "Mustache templates for Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "midair" = callPackage - ({ mkDerivation, base, containers, safe, stdenv, stm }: + ({ mkDerivation, base, containers, lib, safe, stm }: mkDerivation { pname = "midair"; version = "0.2.0.1"; @@ -21861,12 +25935,12 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Hot-swappable FRP"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; }) {}; "midi" = callPackage ({ mkDerivation, base, binary, bytestring, event-list - , explicit-exception, monoid-transformer, non-negative, QuickCheck - , random, semigroups, stdenv, transformers, utility-ht + , explicit-exception, lib, monoid-transformer, non-negative + , QuickCheck, random, semigroups, transformers, utility-ht }: mkDerivation { pname = "midi"; @@ -21884,13 +25958,13 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; license = "GPL"; }) {}; "mighty-metropolis" = callPackage - ({ mkDerivation, base, kan-extensions, mcmc-types, mwc-probability - , pipes, primitive, stdenv, transformers + ({ mkDerivation, base, kan-extensions, lib, mcmc-types + , mwc-probability, pipes, primitive, transformers }: mkDerivation { pname = "mighty-metropolis"; - version = "1.2.0"; - sha256 = "8d3c0b4b65024846291c4f547c45e5c04f587aefd0e8d041d54679bb519871c0"; + version = "2.0.0"; + sha256 = "64e609ff53bdaab9dfdde83ab8639855224f57759b953ee6f1a6be47b98e3b64"; libraryHaskellDepends = [ base kan-extensions mcmc-types mwc-probability pipes primitive transformers @@ -21899,16 +25973,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/jtobin/mighty-metropolis"; description = "The Metropolis algorithm"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "mime-mail" = callPackage ({ mkDerivation, base, base64-bytestring, blaze-builder, bytestring - , filepath, process, random, stdenv, text + , filepath, lib, process, random, text }: mkDerivation { pname = "mime-mail"; - version = "0.4.14"; - sha256 = "9632c3d54c9741fece0a3ea705d965485a1299ebe5798d2aa7cca2c8e4baaa3e"; + version = "0.5.1"; + sha256 = "af9484b1aa01bb110d95bfa0a38e9a30a654ef4f9b8689491e7cd31e36ba3ce8"; libraryHaskellDepends = [ base base64-bytestring blaze-builder bytestring filepath process random text @@ -21917,31 +25991,38 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/snoyberg/mime-mail"; description = "Compose MIME email messages"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "mime-mail-ses" = callPackage - ({ mkDerivation, base, base64-bytestring, byteable, bytestring - , conduit, cryptohash, http-client, http-client-tls, http-conduit - , http-types, mime-mail, old-locale, stdenv, text, time - , transformers, xml-conduit, xml-types + ({ mkDerivation, base, base16-bytestring, base64-bytestring + , byteable, bytestring, case-insensitive, conduit, cryptohash + , http-client, http-client-tls, http-conduit, http-types, lib + , mime-mail, optparse-applicative, text, time, xml-conduit + , xml-types }: mkDerivation { pname = "mime-mail-ses"; - version = "0.4.1"; - sha256 = "a76f29d1e52d8fbfc7ea8119f6ede5ed87f9e5b9d5587f1e6c69295f2a23d3f0"; + version = "0.4.3"; + sha256 = "1276e1bd7256c8f49265c70923d87cef32a62a17489af001eaf5b88984078b6c"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - base base64-bytestring byteable bytestring conduit cryptohash - http-client http-client-tls http-conduit http-types mime-mail - old-locale text time transformers xml-conduit xml-types + base base16-bytestring base64-bytestring byteable bytestring + case-insensitive conduit cryptohash http-client http-client-tls + http-conduit http-types mime-mail text time xml-conduit xml-types + ]; + executableHaskellDepends = [ + base http-client http-client-tls mime-mail optparse-applicative + text ]; doHaddock = false; doCheck = false; homepage = "http://github.com/snoyberg/mime-mail"; description = "Send mime-mail messages via Amazon SES"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "mime-types" = callPackage - ({ mkDerivation, base, bytestring, containers, stdenv, text }: + ({ mkDerivation, base, bytestring, containers, lib, text }: mkDerivation { pname = "mime-types"; version = "0.1.0.9"; @@ -21951,63 +26032,114 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/yesodweb/wai"; description = "Basic mime-type handling types and functions"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "min-max-pqueue" = callPackage + ({ mkDerivation, base, containers, lib }: + mkDerivation { + pname = "min-max-pqueue"; + version = "0.1.0.2"; + sha256 = "5702bfeb91e7fff3b093568f3fe641b1538ec4c2ddce1fe06a00484e386a7b59"; + libraryHaskellDepends = [ base containers ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/zliu41/min-max-pqueue"; + description = "Double-ended priority queues"; + license = lib.licenses.bsd3; + }) {}; + "mini-egison" = callPackage + ({ mkDerivation, base, egison-pattern-src + , egison-pattern-src-th-mode, haskell-src-exts, haskell-src-meta + , lib, mtl, recursion-schemes, sort, template-haskell + }: + mkDerivation { + pname = "mini-egison"; + version = "1.0.0"; + sha256 = "26aadc9fecc66899f9aeddd0b5888984c39fc256809bc808376b1a70b4b8e8f4"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base egison-pattern-src egison-pattern-src-th-mode haskell-src-exts + haskell-src-meta mtl recursion-schemes template-haskell + ]; + executableHaskellDepends = [ base sort ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/egison/egison-haskell#readme"; + description = "Template Haskell Implementation of Egison Pattern Matching"; + license = lib.licenses.mit; + }) {}; + "minimal-configuration" = callPackage + ({ mkDerivation, base, containers, directory, filepath, lib }: + mkDerivation { + pname = "minimal-configuration"; + version = "0.1.4"; + sha256 = "7c0ed6b0d3737ad1d3738b545aa4dc582d1831cf7d2018c8ead2ace2eb1ebf2f"; + libraryHaskellDepends = [ base containers directory filepath ]; + doHaddock = false; + doCheck = false; + description = "Minimal ini like configuration library with a few extras"; + license = "unknown"; + hydraPlatforms = lib.platforms.none; }) {}; "minimorph" = callPackage - ({ mkDerivation, base, stdenv, text }: + ({ mkDerivation, base, lib, text }: mkDerivation { pname = "minimorph"; - version = "0.2.1.0"; - sha256 = "127eb21b889ca9411bee0612ac8aebac7992b9f790dc94b83e28312441d317de"; + version = "0.3.0.0"; + sha256 = "c47da5c93c3d3e1477c00bf141a4d0c6ee68bd99625a421661cbda0977f602cb"; libraryHaskellDepends = [ base text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/Mikolaj/minimorph"; description = "English spelling functions with an emphasis on simplicity"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "minio-hs" = callPackage - ({ mkDerivation, aeson, base, base64-bytestring, bytestring - , case-insensitive, conduit, conduit-extra, containers, cryptonite - , cryptonite-conduit, directory, filepath, http-client - , http-conduit, http-types, ini, memory, protolude, resourcet - , stdenv, text, time, transformers, unliftio, unliftio-core + ({ mkDerivation, aeson, base, base64-bytestring, binary, bytestring + , case-insensitive, conduit, conduit-extra, connection, cryptonite + , cryptonite-conduit, digest, directory, exceptions, filepath + , http-client, http-client-tls, http-conduit, http-types, ini, lib + , memory, protolude, raw-strings-qq, resourcet, retry, text, time + , transformers, unliftio, unliftio-core, unordered-containers , xml-conduit }: mkDerivation { pname = "minio-hs"; - version = "1.2.0"; - sha256 = "311494977fdab5f112807b13d485542c5b57147039063ad57c09bc1367541093"; - configureFlags = [ "-f-live-test" ]; + version = "1.5.3"; + sha256 = "42babcb33760f11a6fe7241763c95e485a775ce562e2084c1435d986e4dc7959"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - aeson base base64-bytestring bytestring case-insensitive conduit - conduit-extra containers cryptonite cryptonite-conduit directory - filepath http-client http-conduit http-types ini memory protolude - resourcet text time transformers unliftio unliftio-core xml-conduit + aeson base base64-bytestring binary bytestring case-insensitive + conduit conduit-extra connection cryptonite cryptonite-conduit + digest directory exceptions filepath http-client http-client-tls + http-conduit http-types ini memory protolude raw-strings-qq + resourcet retry text time transformers unliftio unliftio-core + unordered-containers xml-conduit ]; doHaddock = false; doCheck = false; homepage = "https://github.com/minio/minio-hs#readme"; - description = "A Minio Haskell Library for Amazon S3 compatible cloud storage"; - license = stdenv.lib.licenses.asl20; + description = "A MinIO Haskell Library for Amazon S3 compatible cloud storage"; + license = lib.licenses.asl20; }) {}; "miniutter" = callPackage - ({ mkDerivation, base, binary, containers, minimorph, stdenv, text - }: + ({ mkDerivation, base, binary, containers, lib, minimorph, text }: mkDerivation { pname = "miniutter"; - version = "0.5.0.0"; - sha256 = "ee30db437e6f7012b8862061c842dfaae7e52ea46832fd743e891ca04999fa41"; + version = "0.5.1.1"; + sha256 = "e4d673d0059e4ea2fd3d4349b9e045ca3763afe21bb103d139124912e3e2cf88"; enableSeparateDataOutput = true; libraryHaskellDepends = [ base binary containers minimorph text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/Mikolaj/miniutter"; description = "Simple English clause creation from arbitrary words"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "mintty" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "mintty"; version = "0.1.2"; @@ -22018,31 +26150,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/RyanGlScott/mintty"; description = "A reliable way to detect the presence of a MinTTY console on Windows"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "miso" = callPackage - ({ mkDerivation, aeson, base, bytestring, containers, http-api-data - , http-types, lucid, network-uri, servant, servant-lucid, stdenv - , text, transformers, vector - }: - mkDerivation { - pname = "miso"; - version = "0.21.2.0"; - sha256 = "d52d7950eba48f88e6fe7a08bb797e36c599aa24f790242182fa1acdfa962b18"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - aeson base bytestring containers http-api-data http-types lucid - network-uri servant servant-lucid text transformers vector - ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/dmjio/miso"; - description = "A tasty Haskell front-end framework"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "missing-foreign" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "missing-foreign"; version = "0.1.1"; @@ -22051,49 +26162,29 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Convenience functions for FFI work"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "mixed-types-num" = callPackage - ({ mkDerivation, base, convertible, hspec, hspec-smallcheck - , QuickCheck, smallcheck, stdenv, template-haskell + ({ mkDerivation, base, collect-errors, hspec, hspec-smallcheck, lib + , mtl, QuickCheck, smallcheck, template-haskell }: mkDerivation { pname = "mixed-types-num"; - version = "0.3.1.5"; - sha256 = "7cf0bf14c2ddc643cfaa0e2526b6c2c0c2b1200f29b6f30b5bd550e377d1c058"; + version = "0.5.8.0"; + sha256 = "275fa4e03396f9383e660c81597add1169614d749c94d74f0cc957e2a67980c4"; libraryHaskellDepends = [ - base convertible hspec hspec-smallcheck QuickCheck smallcheck - template-haskell + base collect-errors hspec hspec-smallcheck mtl QuickCheck + smallcheck template-haskell ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/michalkonecny/mixed-types-num"; + homepage = "https://github.com/michalkonecny/mixed-types-num#readme"; description = "Alternative Prelude with numeric and logic expressions typed bottom-up"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "mixpanel-client" = callPackage - ({ mkDerivation, aeson, base, base64-bytestring, bytestring - , http-client, http-client-tls, servant, servant-client, stdenv - , string-conv, text, time - }: - mkDerivation { - pname = "mixpanel-client"; - version = "0.1.1"; - sha256 = "5525bb5bd0c446f275a211be0a1559884438091e58476bfe5256d7a1358227b7"; - libraryHaskellDepends = [ - aeson base base64-bytestring bytestring http-client http-client-tls - servant servant-client string-conv text time - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/domenkozar/mixpanel-client#readme"; - description = "Mixpanel client"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.bsd3; }) {}; "mltool" = callPackage ({ mkDerivation, ascii-progress, base, deepseq, hmatrix - , hmatrix-gsl, hmatrix-morpheus, MonadRandom, random, stdenv - , vector + , hmatrix-gsl, hmatrix-morpheus, lib, MonadRandom, random, vector }: mkDerivation { pname = "mltool"; @@ -22107,10 +26198,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/aligusnet/mltool"; description = "Machine Learning Toolbox"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "mmap" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "mmap"; version = "0.5.9"; @@ -22121,44 +26212,46 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Memory mapped files for POSIX and Windows"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "mmark" = callPackage - ({ mkDerivation, aeson, base, case-insensitive, containers - , data-default-class, deepseq, dlist, email-validate, foldl - , hashable, html-entity-map, lucid, megaparsec, microlens - , microlens-th, modern-uri, mtl, parser-combinators, stdenv, text - , text-metrics, unordered-containers, yaml + ({ mkDerivation, aeson, base, case-insensitive, containers, deepseq + , dlist, email-validate, foldl, hashable, html-entity-map, lib + , lucid, megaparsec, microlens, microlens-th, modern-uri, mtl + , parser-combinators, text, text-metrics, unordered-containers + , yaml }: mkDerivation { pname = "mmark"; - version = "0.0.6.0"; - sha256 = "bbdf608f3d756a49995e0bd87e704bfe6ac2aa32c490c54e90b4b9b21d20df45"; - revision = "2"; - editedCabalFile = "1nxw8vfqji8x63qkrcjnjc2rq1japrylz2wi1s76dm86pcs6hfw1"; + version = "0.0.7.2"; + sha256 = "b59e3b2502b14d1304953593febb9a16d408b5fa4dfc8249066f3ba3d6ff9af3"; + revision = "3"; + editedCabalFile = "1ffa76pz544pa3s764lnc38rdmfccyn8z6zn1w76pqb01p0f9k9p"; enableSeparateDataOutput = true; libraryHaskellDepends = [ - aeson base case-insensitive containers data-default-class deepseq - dlist email-validate foldl hashable html-entity-map lucid - megaparsec microlens microlens-th modern-uri mtl parser-combinators - text text-metrics unordered-containers yaml + aeson base case-insensitive containers deepseq dlist email-validate + foldl hashable html-entity-map lucid megaparsec microlens + microlens-th modern-uri mtl parser-combinators text text-metrics + unordered-containers yaml ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mmark-md/mmark"; description = "Strict markdown processor for writers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "mmark-cli" = callPackage ({ mkDerivation, aeson, base, bytestring, directory - , ghc-syntax-highlighter, gitrev, lucid, megaparsec, mmark - , mmark-ext, optparse-applicative, stache, stdenv, text + , ghc-syntax-highlighter, gitrev, lib, lucid, megaparsec, mmark + , mmark-ext, optparse-applicative, stache, text , unordered-containers }: mkDerivation { pname = "mmark-cli"; version = "0.0.5.0"; sha256 = "7ec1e69f4ce0ed638f8a979f0da2e3173d2c034ffd23b9b166a95317b0b81997"; + revision = "6"; + editedCabalFile = "1qki0f2iwr9phma4wby3alnsxigzl5qc1ims8cvhszkill9yfi4z"; isLibrary = false; isExecutable = true; executableHaskellDepends = [ @@ -22170,16 +26263,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mmark-md/mmark-cli"; description = "Command line interface to the MMark markdown processor"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "mmark-ext" = callPackage - ({ mkDerivation, base, foldl, ghc-syntax-highlighter, lucid - , microlens, mmark, modern-uri, skylighting, stdenv, text + ({ mkDerivation, base, foldl, ghc-syntax-highlighter, lib, lucid + , microlens, mmark, modern-uri, skylighting, text }: mkDerivation { pname = "mmark-ext"; - version = "0.2.1.1"; - sha256 = "98554e8b04c47e208cb0e3d5a61fb064eb25fbdaf9eb3ebf4faf9663533b5b05"; + version = "0.2.1.3"; + sha256 = "5aa01aa206e79d7c0239b694bc9254a0c9ad3e32915ae285a3d237c2f72b89c1"; enableSeparateDataOutput = true; libraryHaskellDepends = [ base foldl ghc-syntax-highlighter lucid microlens mmark modern-uri @@ -22189,26 +26282,27 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mmark-md/mmark-ext"; description = "Commonly useful extensions for the MMark markdown processor"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "mmorph" = callPackage - ({ mkDerivation, base, mtl, stdenv, transformers - , transformers-compat + ({ mkDerivation, base, lib, mtl, transformers, transformers-compat }: mkDerivation { pname = "mmorph"; - version = "1.1.2"; - sha256 = "c90afd7996c94be2b9a5796a7b94918d198c53b0c1d7a3eaf2982293560c5fbe"; + version = "1.1.5"; + sha256 = "46fb450e3dedab419c47b0f154badb798c9e0e8cd097f78c40a12b47e1a8092f"; + revision = "1"; + editedCabalFile = "087v8ajcfpx4f0v4jxvv16h6jswgnkfnyfn28k406d5w3ihcx1wl"; libraryHaskellDepends = [ base mtl transformers transformers-compat ]; doHaddock = false; doCheck = false; description = "Monad morphisms"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "mnist-idx" = callPackage - ({ mkDerivation, base, binary, bytestring, stdenv, vector }: + ({ mkDerivation, base, binary, bytestring, lib, vector }: mkDerivation { pname = "mnist-idx"; version = "0.1.2.8"; @@ -22218,11 +26312,47 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/kryoxide/mnist-idx/"; description = "Read and write IDX data that is used in e.g. the MNIST database."; - license = stdenv.lib.licenses.lgpl3; + license = lib.licenses.lgpl3Only; + }) {}; + "mnist-idx-conduit" = callPackage + ({ mkDerivation, base, binary, bytestring, conduit, containers + , exceptions, hspec, lib, resourcet, vector + }: + mkDerivation { + pname = "mnist-idx-conduit"; + version = "0.4.0.0"; + sha256 = "1df673586aa58d83656326379f8b85a980ebb920a1a6cfe58e0e0d6e2d8b290c"; + libraryHaskellDepends = [ + base binary bytestring conduit containers exceptions hspec + resourcet vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ocramz/mnist-idx-conduit"; + description = "conduit utilities for MNIST IDX files"; + license = lib.licenses.bsd3; + }) {}; + "mock-time" = callPackage + ({ mkDerivation, base, error-or, exceptions, lib, mtl, primitive + , resourcet, stm, time, unliftio-core + }: + mkDerivation { + pname = "mock-time"; + version = "0.1.0"; + sha256 = "4f02e2c3487318472f8916d4595ce10c41cd7defd5333f08c427ae39dea4963b"; + libraryHaskellDepends = [ + base error-or exceptions mtl primitive resourcet stm time + unliftio-core + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/luntain/error-or-bundle/blob/master/mock-time#readme"; + description = "Mock time in tests"; + license = lib.licenses.bsd3; }) {}; "mockery" = callPackage ({ mkDerivation, base, base-compat, bytestring, directory, filepath - , logging-facade, stdenv, temporary + , lib, logging-facade, temporary }: mkDerivation { pname = "mockery"; @@ -22235,19 +26365,51 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Support functions for automated testing"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "mod" = callPackage + ({ mkDerivation, base, deepseq, integer-gmp, lib, primitive + , semirings, vector + }: + mkDerivation { + pname = "mod"; + version = "0.1.2.2"; + sha256 = "db98ad817c45e89984428cae6b5f88074220955035520cafe552ce2146f32255"; + libraryHaskellDepends = [ + base deepseq integer-gmp primitive semirings vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/Bodigrim/mod"; + description = "Fast type-safe modular arithmetic"; + license = lib.licenses.mit; + }) {}; + "model" = callPackage + ({ mkDerivation, base, containers, convertible, deepseq, either + , lib, pretty, transformers + }: + mkDerivation { + pname = "model"; + version = "0.5"; + sha256 = "0df08b11ddc6ba3d69f882c1e81231135551c30979d24800f506a5f98ddad67b"; + libraryHaskellDepends = [ + base containers convertible deepseq either pretty transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/Quid2/model"; + description = "Derive a model of a data type using Generics"; + license = lib.licenses.bsd3; }) {}; "modern-uri" = callPackage ({ mkDerivation, base, bytestring, containers, contravariant - , deepseq, exceptions, megaparsec, mtl, profunctors, QuickCheck - , reflection, stdenv, tagged, template-haskell, text + , deepseq, exceptions, lib, megaparsec, mtl, profunctors + , QuickCheck, reflection, tagged, template-haskell, text }: mkDerivation { pname = "modern-uri"; - version = "0.3.0.1"; - sha256 = "e8e845837ddc327c027128faf36a76c69e8514a9f8b5a4666282ae89b6954505"; - revision = "1"; - editedCabalFile = "13q0lapxk1v3ci3bqv21942jf2fw87frbbam53apd3i2iv69bqyr"; + version = "0.3.4.1"; + sha256 = "0d43668de83f0f194d165a826beef82574eb11a3bc390a44009b8f1a69b1df27"; libraryHaskellDepends = [ base bytestring containers contravariant deepseq exceptions megaparsec mtl profunctors QuickCheck reflection tagged @@ -22257,10 +26419,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mrkkrp/modern-uri"; description = "Modern library for working with URIs"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "modular" = callPackage - ({ mkDerivation, base, ghc-typelits-knownnat, stdenv }: + ({ mkDerivation, base, ghc-typelits-knownnat, lib }: mkDerivation { pname = "modular"; version = "0.1.0.8"; @@ -22270,10 +26432,30 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/pgujjula/modular#readme"; description = "Type-safe modular arithmetic"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "monad-chronicle" = callPackage + ({ mkDerivation, base, data-default-class, lib, mtl, semigroupoids + , these, transformers, transformers-compat + }: + mkDerivation { + pname = "monad-chronicle"; + version = "1.0.0.1"; + sha256 = "6fd568d01e17e66c0f55d871bba24014b65974df402df772ef4d11ae8b4b3cdd"; + revision = "1"; + editedCabalFile = "097f5wvzx10i9zgx4gn7wm81z7dfyhj9lx8jyy4n90j0adpbjryq"; + libraryHaskellDepends = [ + base data-default-class mtl semigroupoids these transformers + transformers-compat + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskellari/these"; + description = "These as a transformer, ChronicleT"; + license = lib.licenses.bsd3; }) {}; "monad-control" = callPackage - ({ mkDerivation, base, stdenv, stm, transformers, transformers-base + ({ mkDerivation, base, lib, stm, transformers, transformers-base , transformers-compat }: mkDerivation { @@ -22287,10 +26469,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/basvandijk/monad-control"; description = "Lift control operations, like exception catching, through monad transformers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "monad-control-aligned" = callPackage - ({ mkDerivation, base, stdenv, stm, transformers, transformers-base + ({ mkDerivation, base, lib, stm, transformers, transformers-base , transformers-compat }: mkDerivation { @@ -22304,27 +26486,27 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/athanclark/monad-control#readme"; description = "Just like monad-control, except less efficient, and the monadic state terms are all * -> *"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "monad-coroutine" = callPackage - ({ mkDerivation, base, monad-parallel, stdenv, transformers + ({ mkDerivation, base, lib, monad-parallel, transformers , transformers-compat }: mkDerivation { pname = "monad-coroutine"; - version = "0.9.0.4"; - sha256 = "13e0ff12046296390ea69dda5001aa02b1b57e968447d27712a24c8c7cfe5de7"; + version = "0.9.1.2"; + sha256 = "c341c82631367df8e9f5a09bb467ffc221a0da9cbc26eca7166b8819703989e8"; libraryHaskellDepends = [ base monad-parallel transformers transformers-compat ]; doHaddock = false; doCheck = false; - homepage = "http://trac.haskell.org/SCC/wiki/monad-coroutine"; + homepage = "https://hub.darcs.net/blamario/SCC.wiki/"; description = "Coroutine monad transformer for suspending and resuming monadic computations"; license = "GPL"; }) {}; "monad-extras" = callPackage - ({ mkDerivation, base, mmorph, monad-control, stdenv, stm + ({ mkDerivation, base, lib, mmorph, monad-control, stm , transformers, transformers-base }: mkDerivation { @@ -22338,10 +26520,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/jwiegley/monad-extras"; description = "Extra utility functions for working with monads"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "monad-journal" = callPackage - ({ mkDerivation, base, monad-control, mtl, stdenv, transformers + ({ mkDerivation, base, lib, monad-control, mtl, transformers , transformers-base }: mkDerivation { @@ -22355,19 +26537,19 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/phaazon/monad-journal"; description = "Pure logger typeclass and monad transformer"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "monad-logger" = callPackage ({ mkDerivation, base, bytestring, conduit, conduit-extra - , exceptions, fast-logger, lifted-base, monad-control, monad-loops - , mtl, resourcet, stdenv, stm, stm-chans, template-haskell, text - , transformers, transformers-base, transformers-compat + , exceptions, fast-logger, lib, lifted-base, monad-control + , monad-loops, mtl, resourcet, stm, stm-chans, template-haskell + , text, transformers, transformers-base, transformers-compat , unliftio-core }: mkDerivation { pname = "monad-logger"; - version = "0.3.30"; - sha256 = "e7ce990978b7395c615441775b64b487ad6cd6f2e4f9787dae732f58ce065480"; + version = "0.3.36"; + sha256 = "706d403f37a84d87ac83b79320e18f55cf15739daf4327aac411ce17c0043c8b"; libraryHaskellDepends = [ base bytestring conduit conduit-extra exceptions fast-logger lifted-base monad-control monad-loops mtl resourcet stm stm-chans @@ -22378,11 +26560,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/snoyberg/monad-logger#readme"; description = "A class of monads which can log messages"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "monad-logger-json" = callPackage - ({ mkDerivation, aeson, base, monad-logger, stdenv - , template-haskell, text + ({ mkDerivation, aeson, base, lib, monad-logger, template-haskell + , text }: mkDerivation { pname = "monad-logger-json"; @@ -22395,45 +26577,47 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/fpco/monad-logger-json"; description = "JSON-friendly Logging APIs"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "monad-logger-prefix" = callPackage - ({ mkDerivation, base, exceptions, monad-control, monad-logger, mtl - , resourcet, stdenv, text, transformers, transformers-base + "monad-logger-logstash" = callPackage + ({ mkDerivation, aeson, base, lib, logstash, monad-logger, retry + , stm, stm-chans, text, transformers, unliftio }: mkDerivation { - pname = "monad-logger-prefix"; - version = "0.1.10"; - sha256 = "a3ac2d043a13d9e9296692dc729a299361b04757690894cac1b6904510a0d975"; + pname = "monad-logger-logstash"; + version = "0.1.0.0"; + sha256 = "9095c6a8d64b8c9c7e0059df0bf1bb0fe9cf91df8defa52299e24b5b7d2b13cd"; libraryHaskellDepends = [ - base exceptions monad-control monad-logger mtl resourcet text - transformers transformers-base + aeson base logstash monad-logger retry stm stm-chans text + transformers unliftio ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/parsonsmatt/monad-logger-prefix#readme"; - description = "Add prefixes to your monad-logger output"; - license = stdenv.lib.licenses.asl20; + homepage = "https://github.com/mbg/logstash#readme"; + description = "Logstash backend for monad-logger"; + license = lib.licenses.mit; }) {}; - "monad-logger-syslog" = callPackage - ({ mkDerivation, base, bytestring, fast-logger, hsyslog - , monad-logger, stdenv, text, transformers + "monad-logger-prefix" = callPackage + ({ mkDerivation, base, exceptions, lib, monad-control, monad-logger + , mtl, resourcet, text, transformers, transformers-base + , unliftio-core }: mkDerivation { - pname = "monad-logger-syslog"; - version = "0.1.4.0"; - sha256 = "052c3e13e235e7fb31caecc117e3ab4629e85bbfd3b35ec03f74d732acbc9ccb"; + pname = "monad-logger-prefix"; + version = "0.1.12"; + sha256 = "9a6f3cbe4888ab178880c9a4cb4883833755e438f9d172605b6ee30debb9fa01"; libraryHaskellDepends = [ - base bytestring fast-logger hsyslog monad-logger text transformers + base exceptions monad-control monad-logger mtl resourcet text + transformers transformers-base unliftio-core ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/fpco/monad-logger-syslog"; - description = "syslog output for monad-logger"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/parsonsmatt/monad-logger-prefix#readme"; + description = "Add prefixes to your monad-logger output"; + license = lib.licenses.asl20; }) {}; "monad-loops" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "monad-loops"; version = "0.4.3"; @@ -22443,16 +26627,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mokus0/monad-loops"; description = "Monadic loops"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "monad-memo" = callPackage - ({ mkDerivation, array, base, containers, primitive, stdenv + ({ mkDerivation, array, base, containers, lib, primitive , transformers, vector }: mkDerivation { pname = "monad-memo"; - version = "0.5.1"; - sha256 = "c65a4a3c3e05757c251557b392f2cc7edcc09c2c46cbb0e72f4efe291eb85bff"; + version = "0.5.3"; + sha256 = "16f8c46673ac2564cd7d4d7ce901c25ded61d72283a93985db24dc6736c60dbb"; libraryHaskellDepends = [ array base containers primitive transformers vector ]; @@ -22460,17 +26644,37 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/EduardSergeev/monad-memo"; description = "Memoization monad transformer"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "monad-metrics" = callPackage + ({ mkDerivation, base, clock, ekg-core, exceptions, hashable, lib + , microlens, mtl, text, transformers, unordered-containers + }: + mkDerivation { + pname = "monad-metrics"; + version = "0.2.2.0"; + sha256 = "78e3f45eaff888154579c792744291510565e7d941cd29a02e504b0158fa9a8f"; + libraryHaskellDepends = [ + base clock ekg-core exceptions hashable microlens mtl text + transformers unordered-containers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/parsonsmatt/monad-metrics#readme"; + description = "A convenient wrapper around EKG metrics"; + license = lib.licenses.mit; }) {}; "monad-par" = callPackage ({ mkDerivation, abstract-deque, abstract-par, array, base - , containers, deepseq, monad-par-extras, mtl, mwc-random, parallel - , stdenv + , containers, deepseq, lib, monad-par-extras, mtl, mwc-random + , parallel }: mkDerivation { pname = "monad-par"; - version = "0.3.4.8"; - sha256 = "f84cdf51908a1c41c3f672be9520a8fdc028ea39d90a25ecfe5a3b223cfeb951"; + version = "0.3.5"; + sha256 = "823ad5666cbcaefe2c6e0ff131daa0713dff9b3b534fb809643b869e5e4a15a9"; + revision = "1"; + editedCabalFile = "17l7zjykf5iqjmw1pq4iwls7v9x9d3in94iikxabx43q5l2iccsm"; libraryHaskellDepends = [ abstract-deque abstract-par array base containers deepseq monad-par-extras mtl mwc-random parallel @@ -22479,11 +26683,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/simonmar/monad-par"; description = "A library for parallel programming based on a monad"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "monad-par-extras" = callPackage - ({ mkDerivation, abstract-par, base, cereal, deepseq, mtl, random - , stdenv, transformers + ({ mkDerivation, abstract-par, base, cereal, deepseq, lib, mtl + , random, transformers }: mkDerivation { pname = "monad-par-extras"; @@ -22496,28 +26700,27 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/simonmar/monad-par"; description = "Combinators and extra features for Par monads"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "monad-parallel" = callPackage - ({ mkDerivation, base, parallel, stdenv, transformers + ({ mkDerivation, base, lib, parallel, transformers , transformers-compat }: mkDerivation { pname = "monad-parallel"; - version = "0.7.2.3"; - sha256 = "128fb8c36be717f82aa3146d855303f48d04c56ba025078e6cd35d6050b45089"; + version = "0.7.2.4"; + sha256 = "bd974c7207885cacf7645dc6a3b9aa28cf37f6717da22e30031b0034178766c0"; libraryHaskellDepends = [ base parallel transformers transformers-compat ]; doHaddock = false; doCheck = false; - homepage = "http://trac.haskell.org/SCC/wiki/monad-parallel"; + homepage = "https://hub.darcs.net/blamario/SCC.wiki/"; description = "Parallel execution of monadic computations"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "monad-peel" = callPackage - ({ mkDerivation, base, extensible-exceptions, stdenv, transformers - }: + ({ mkDerivation, base, extensible-exceptions, lib, transformers }: mkDerivation { pname = "monad-peel"; version = "0.2.1.2"; @@ -22529,10 +26732,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://andersk.mit.edu/haskell/monad-peel/"; description = "Lift control operations like exception catching through monad transformers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "monad-primitive" = callPackage + ({ mkDerivation, base, lib, primitive, transformers }: + mkDerivation { + pname = "monad-primitive"; + version = "0.1"; + sha256 = "3dc032536e87ca77d9e802d581f036ebbf2e29064fb98a0ede05fb068b7926ee"; + libraryHaskellDepends = [ base primitive transformers ]; + doHaddock = false; + doCheck = false; + homepage = "http://bitbucket.org/Shimuuar/monad-primitive"; + description = "Type class for monad transformers stack with pirimitive base monad"; + license = lib.licenses.bsd3; }) {}; "monad-products" = callPackage - ({ mkDerivation, base, semigroupoids, stdenv }: + ({ mkDerivation, base, lib, semigroupoids }: mkDerivation { pname = "monad-products"; version = "4.0.1"; @@ -22542,10 +26758,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/monad-products"; description = "Monad products"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "monad-resumption" = callPackage + ({ mkDerivation, base, lib, mmorph, mtl, transformers }: + mkDerivation { + pname = "monad-resumption"; + version = "0.1.4.0"; + sha256 = "b442bd7a36bb6b9fd35326dce8531446945221ff45b074eca7099806f16a8941"; + libraryHaskellDepends = [ base mmorph mtl transformers ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/igraves/monad-resumption#readme"; + description = "Resumption and reactive resumption monads for Haskell"; + license = lib.licenses.bsd3; }) {}; "monad-skeleton" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "monad-skeleton"; version = "0.1.5"; @@ -22555,10 +26784,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/fumieval/monad-skeleton"; description = "Monads of program skeleta"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "monad-st" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "monad-st"; version = "0.2.4.1"; @@ -22568,10 +26797,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/monad-st"; description = "Provides a MonadST class"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "monad-time" = callPackage - ({ mkDerivation, base, mtl, stdenv, time }: + ({ mkDerivation, base, lib, mtl, time }: mkDerivation { pname = "monad-time"; version = "0.3.1.0"; @@ -22581,10 +26810,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/scrive/monad-time"; description = "Type class for monads which carry the notion of the current time"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "monad-unlift" = callPackage - ({ mkDerivation, base, constraints, monad-control, stdenv + ({ mkDerivation, base, constraints, lib, monad-control , transformers, transformers-base }: mkDerivation { @@ -22598,11 +26827,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/fpco/monad-unlift"; description = "Typeclasses for representing monad transformer unlifting"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "monad-unlift-ref" = callPackage - ({ mkDerivation, base, constraints, exceptions, monad-control - , monad-unlift, mtl, mutable-containers, resourcet, stdenv, stm + ({ mkDerivation, base, constraints, exceptions, lib, monad-control + , monad-unlift, mtl, mutable-containers, resourcet, stm , transformers, transformers-base }: mkDerivation { @@ -22617,10 +26846,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/fpco/monad-unlift"; description = "Typeclasses for representing monad transformer unlifting"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "monadic-arrays" = callPackage - ({ mkDerivation, array, base, stdenv, stm, transformers + ({ mkDerivation, array, base, lib, stm, transformers , transformers-compat }: mkDerivation { @@ -22634,10 +26863,22 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/monadic-arrays/"; description = "Boxed and unboxed arrays for monad transformers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "monadlist" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "monadlist"; + version = "0.0.2"; + sha256 = "06bbe82c9fc2a35048788367da74bb5f79c7e6be2ae38eca20f332f8cbc5fdfe"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + description = "Monadic versions of list functions"; + license = lib.licenses.bsd3; }) {}; "monads-tf" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "monads-tf"; version = "0.1.0.3"; @@ -22646,44 +26887,44 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Monad classes, using type families"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "mongoDB" = callPackage ({ mkDerivation, array, base, base16-bytestring, base64-bytestring , binary, bson, bytestring, conduit, conduit-extra, containers - , cryptohash, data-default-class, hashtables, lifted-base - , monad-control, mtl, network, nonce, parsec, pureMD5, random - , random-shuffle, resourcet, stdenv, stm, tagged, text, time, tls - , transformers, transformers-base + , cryptohash, data-default-class, dns, fail, hashtables, http-types + , lib, lifted-base, monad-control, mtl, network, network-bsd, nonce + , parsec, pureMD5, random, random-shuffle, resourcet, stm, tagged + , text, time, tls, transformers, transformers-base }: mkDerivation { pname = "mongoDB"; - version = "2.4.0.0"; - sha256 = "fdb80241825c70d795a1e552b25afc916e58d7755ec31feaf7ab7afdd5aee719"; + version = "2.7.1.1"; + sha256 = "e0606e1f7360df1f971c17e97fea41ab867a171eb81af922954993b98999cca0"; + configureFlags = [ "-f-_old-network" ]; libraryHaskellDepends = [ array base base16-bytestring base64-bytestring binary bson bytestring conduit conduit-extra containers cryptohash - data-default-class hashtables lifted-base monad-control mtl network - nonce parsec pureMD5 random random-shuffle resourcet stm tagged - text time tls transformers transformers-base + data-default-class dns fail hashtables http-types lifted-base + monad-control mtl network network-bsd nonce parsec pureMD5 random + random-shuffle resourcet stm tagged text time tls transformers + transformers-base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mongodb-haskell/mongodb"; description = "Driver (client) for MongoDB, a free, scalable, fast, document DBMS"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; }) {}; "mono-traversable" = callPackage - ({ mkDerivation, base, bytestring, containers, hashable, split - , stdenv, text, transformers, unordered-containers, vector + ({ mkDerivation, base, bytestring, containers, hashable, lib, split + , text, transformers, unordered-containers, vector , vector-algorithms }: mkDerivation { pname = "mono-traversable"; - version = "1.0.10.0"; - sha256 = "0096dbf6f3651b3834637a2ba4dcb6fafcd782546a542a286d2ecfae277b8811"; - revision = "1"; - editedCabalFile = "1hgwrmq7r8d1nq9283wis67lg0wlid2sgqnr9vpsv2wpnd4n1rdl"; + version = "1.0.15.1"; + sha256 = "c2df5b79ed2f88f2ee313e57c1d591d4463788e20d39e439297eec5ba5835ddf"; libraryHaskellDepends = [ base bytestring containers hashable split text transformers unordered-containers vector vector-algorithms @@ -22692,17 +26933,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/snoyberg/mono-traversable#readme"; description = "Type classes for mapping, folding, and traversing monomorphic containers"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "mono-traversable-instances" = callPackage ({ mkDerivation, base, comonad, containers, dlist, dlist-instances - , mono-traversable, semigroupoids, semigroups, stdenv, transformers + , lib, mono-traversable, semigroupoids, semigroups, transformers , vector-instances }: mkDerivation { pname = "mono-traversable-instances"; - version = "0.1.0.0"; - sha256 = "b5ff2b8bcebe31ffcc652a8dd3adde6aa7cd7f27a1cf6d058d4c658b370c087e"; + version = "0.1.1.0"; + sha256 = "ebc1ac7835e077473f524985feed6eb0fd90b849be5cd1eba10b7c471bfad3ba"; libraryHaskellDepends = [ base comonad containers dlist dlist-instances mono-traversable semigroupoids semigroups transformers vector-instances @@ -22711,30 +26952,36 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/snoyberg/mono-traversable#readme"; description = "Extra typeclass instances for mono-traversable"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "monoid-extras" = callPackage - ({ mkDerivation, base, groups, semigroupoids, semigroups, stdenv }: + "mono-traversable-keys" = callPackage + ({ mkDerivation, base, bytestring, containers, hashable, keys, lib + , mono-traversable, semigroups, text, transformers + , unordered-containers, vector, vector-instances + }: mkDerivation { - pname = "monoid-extras"; - version = "0.5"; - sha256 = "c6571ab25a24e4300d507beeb8e534c20b3e530c6bd19c82694f1d6d5d0d4d9c"; - revision = "2"; - editedCabalFile = "1q73ghd12fd451zm4m045h8v3y61jmfhj6k890gnv6z7lyb7xwg2"; - libraryHaskellDepends = [ base groups semigroupoids semigroups ]; + pname = "mono-traversable-keys"; + version = "0.1.0"; + sha256 = "bc85929322e287a8d6c4ab2f8beede6d99417fc8c23c519b9719bbe68125d477"; + libraryHaskellDepends = [ + base bytestring containers hashable keys mono-traversable + semigroups text transformers unordered-containers vector + vector-instances + ]; doHaddock = false; doCheck = false; - description = "Various extra monoid-related definitions and utilities"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/recursion-ninja/mono-traversable-keys#readme"; + description = "Type-classes for interacting with monomorphic containers with a key"; + license = lib.licenses.bsd3; }) {}; "monoid-subclasses" = callPackage - ({ mkDerivation, base, bytestring, containers, primes, stdenv, text + ({ mkDerivation, base, bytestring, containers, lib, primes, text , vector }: mkDerivation { pname = "monoid-subclasses"; - version = "0.4.6.1"; - sha256 = "d097876d8778fc550a071fc5fb564e8969903e8022c5f2dc25697bd8269daea6"; + version = "1.1"; + sha256 = "e40effb85b24eb44ac4c2986f6ff952a73373fa3eaa72155106114de6ecc60af"; libraryHaskellDepends = [ base bytestring containers primes text vector ]; @@ -22742,10 +26989,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/blamario/monoid-subclasses/"; description = "Subclasses of Monoid"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "monoid-transformer" = callPackage - ({ mkDerivation, base, semigroups, stdenv }: + ({ mkDerivation, base, lib, semigroups }: mkDerivation { pname = "monoid-transformer"; version = "0.0.4"; @@ -22754,68 +27001,228 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Monoid counterparts to some ubiquitous monad transformers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "more-containers" = callPackage + ({ mkDerivation, base, binary, containers, lib }: + mkDerivation { + pname = "more-containers"; + version = "0.2.2.2"; + sha256 = "fdeb2354cf103554d1ab7a9679993008a9bb3e8d34480ab6f8410c322cc37c7d"; + libraryHaskellDepends = [ base binary containers ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/mtth/more-containers"; + description = "A few more collections"; + license = lib.licenses.mit; }) {}; - "monoidal-containers" = callPackage - ({ mkDerivation, aeson, base, containers, deepseq, hashable, lens - , newtype, semigroups, stdenv, unordered-containers + "morpheus-graphql" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers, lib + , morpheus-graphql-app, morpheus-graphql-core, mtl, relude + , template-haskell, text, transformers, unordered-containers + , vector }: mkDerivation { - pname = "monoidal-containers"; - version = "0.4.0.0"; - sha256 = "a132b8adc82cd132ffdf1079b137176a2ccb9c80603cb17ec92f0c753a14b096"; + pname = "morpheus-graphql"; + version = "0.17.0"; + sha256 = "1a332470b0692ff13d0c5bd8972311a037a5282faa85712a712e445c66a4364d"; + enableSeparateDataOutput = true; libraryHaskellDepends = [ - aeson base containers deepseq hashable lens newtype semigroups - unordered-containers + aeson base bytestring containers morpheus-graphql-app + morpheus-graphql-core mtl relude template-haskell text transformers + unordered-containers vector ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/bgamari/monoidal-containers"; - description = "Containers with monoidal accumulation"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://morpheusgraphql.com"; + description = "Morpheus GraphQL"; + license = lib.licenses.mit; }) {}; - "mountpoints" = callPackage - ({ mkDerivation, base, stdenv }: + "morpheus-graphql-app" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers, hashable, lib + , megaparsec, morpheus-graphql-core, mtl, relude, scientific + , template-haskell, text, th-lift-instances, transformers + , unordered-containers, vector + }: mkDerivation { - pname = "mountpoints"; - version = "1.0.2"; - sha256 = "67fcdf64fdb8111f58939c64b168a9dfa519d7068e0f439887d739866f18d5c2"; - libraryHaskellDepends = [ base ]; + pname = "morpheus-graphql-app"; + version = "0.17.0"; + sha256 = "bf275750262a0d193012b909bc18c1526d8836796d851dfd40cfaab3d9ce6b50"; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + aeson base bytestring containers hashable megaparsec + morpheus-graphql-core mtl relude scientific template-haskell text + th-lift-instances transformers unordered-containers vector + ]; doHaddock = false; doCheck = false; - description = "list mount points"; - license = "LGPL"; + homepage = "https://morpheusgraphql.com"; + description = "Morpheus GraphQL Core"; + license = lib.licenses.mit; }) {}; - "mtl" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + "morpheus-graphql-client" = callPackage + ({ mkDerivation, aeson, base, bytestring, lib + , morpheus-graphql-core, mtl, relude, template-haskell, text + , transformers, unordered-containers + }: mkDerivation { - pname = "mtl"; - version = "2.2.2"; - sha256 = "8803f48a8ed33296c3a3272f448198737a287ec31baa901af09e2118c829bef6"; - libraryHaskellDepends = [ base transformers ]; + pname = "morpheus-graphql-client"; + version = "0.17.0"; + sha256 = "034f79a5e87e3274393749cd2f0cb28843890d50e50a14745016259d8aef4fb6"; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + aeson base bytestring morpheus-graphql-core mtl relude + template-haskell text transformers unordered-containers + ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/haskell/mtl"; - description = "Monad classes, using functional dependencies"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://morpheusgraphql.com"; + description = "Morpheus GraphQL Client"; + license = lib.licenses.mit; }) {}; - "mtl-compat" = callPackage - ({ mkDerivation, base, mtl, stdenv }: + "morpheus-graphql-core" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers, hashable, lib + , megaparsec, mtl, relude, scientific, template-haskell, text + , th-lift-instances, transformers, unordered-containers, vector + }: mkDerivation { - pname = "mtl-compat"; - version = "0.2.1.3"; - sha256 = "6458ca53593a31ebce1d94ef8dd4f6a06d050dd7ed32335f6cc6b6e5d3456894"; - revision = "4"; - editedCabalFile = "1mfrx8cpx0502sjv0bmlfkl0h46c4krldg8m89k4fj6iawwg2ab5"; - libraryHaskellDepends = [ base mtl ]; + pname = "morpheus-graphql-core"; + version = "0.17.0"; + sha256 = "e882fb841cb1dfdc4d1d1fbc81e71b5c8ea3cf061bf8b2122b1716330a784466"; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + aeson base bytestring containers hashable megaparsec mtl relude + scientific template-haskell text th-lift-instances transformers + unordered-containers vector + ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/haskell-compat/mtl-compat"; - description = "Backported Control.Monad.Except module from mtl"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://morpheusgraphql.com"; + description = "Morpheus GraphQL Core"; + license = lib.licenses.mit; }) {}; - "mtl-prelude" = callPackage - ({ mkDerivation, base, mtl, stdenv, transformers }: + "morpheus-graphql-subscriptions" = callPackage + ({ mkDerivation, aeson, base, bytestring, lib, morpheus-graphql-app + , morpheus-graphql-core, mtl, relude, text, transformers + , unliftio-core, unordered-containers, uuid, websockets + }: + mkDerivation { + pname = "morpheus-graphql-subscriptions"; + version = "0.17.0"; + sha256 = "0619b33d0fe459327897f331dd1f3d15e68c16b728baf2052aa5c5d8fbb77791"; + libraryHaskellDepends = [ + aeson base bytestring morpheus-graphql-app morpheus-graphql-core + mtl relude text transformers unliftio-core unordered-containers + uuid websockets + ]; + doHaddock = false; + doCheck = false; + homepage = "https://morpheusgraphql.com"; + description = "Morpheus GraphQL Subscriptions"; + license = lib.licenses.mit; + }) {}; + "moss" = callPackage + ({ mkDerivation, base, bytestring, conduit-extra, lib, mtl, network + , network-simple, unix-compat + }: + mkDerivation { + pname = "moss"; + version = "0.2.0.0"; + sha256 = "80ffcfd268fa0e4b9b0238110fd8f94bf8ece93865363c6e6b1f312372184c9d"; + libraryHaskellDepends = [ + base bytestring conduit-extra mtl network network-simple + unix-compat + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/mbg/moss#readme"; + description = "Haskell client for Moss"; + license = lib.licenses.mit; + }) {}; + "mountpoints" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "mountpoints"; + version = "1.0.2"; + sha256 = "67fcdf64fdb8111f58939c64b168a9dfa519d7068e0f439887d739866f18d5c2"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + description = "list mount points"; + license = "LGPL"; + }) {}; + "mpi-hs" = callPackage + ({ mkDerivation, base, bytestring, c2hs, lib, monad-loops, mpich }: + mkDerivation { + pname = "mpi-hs"; + version = "0.7.2.0"; + sha256 = "25bbf1b14a919be4342ce30f5fdbef5338a11f33a6d3913fd43801188cbfc8b4"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base bytestring monad-loops ]; + librarySystemDepends = [ mpich ]; + libraryToolDepends = [ c2hs ]; + executableHaskellDepends = [ base ]; + executableSystemDepends = [ mpich ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/eschnett/mpi-hs#readme"; + description = "MPI bindings for Haskell"; + license = lib.licenses.asl20; + }) {inherit (pkgs) mpich;}; + "mpi-hs-binary" = callPackage + ({ mkDerivation, base, binary, bytestring, lib, monad-loops, mpi-hs + }: + mkDerivation { + pname = "mpi-hs-binary"; + version = "0.1.1.0"; + sha256 = "63ab2460dd004570ddeae1076247a434d81aa4a57deb8fe36e4fe61646cd9483"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base binary bytestring monad-loops mpi-hs + ]; + executableHaskellDepends = [ base mpi-hs ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/eschnett/mpi-hs-binary#readme"; + description = "MPI bindings for Haskell"; + license = lib.licenses.asl20; + }) {}; + "mpi-hs-cereal" = callPackage + ({ mkDerivation, base, bytestring, cereal, lib, monad-loops, mpi-hs + }: + mkDerivation { + pname = "mpi-hs-cereal"; + version = "0.1.0.0"; + sha256 = "eb80bf4edb693dd9790541271624be570981a19c2ce970608382dd4ea6fcb1e9"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base bytestring cereal monad-loops mpi-hs + ]; + executableHaskellDepends = [ base mpi-hs ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/eschnett/mpi-hs-cereal#readme"; + description = "MPI bindings for Haskell"; + license = lib.licenses.asl20; + }) {}; + "mtl-compat" = callPackage + ({ mkDerivation, base, lib, mtl }: + mkDerivation { + pname = "mtl-compat"; + version = "0.2.2"; + sha256 = "1955398fe2115674f47f553b2caaf928c6aa3424271a5cd13bc191e54bfe3a9e"; + libraryHaskellDepends = [ base mtl ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell-compat/mtl-compat"; + description = "Backported Control.Monad.Except module from mtl"; + license = lib.licenses.bsd3; + }) {}; + "mtl-prelude" = callPackage + ({ mkDerivation, base, lib, mtl, transformers }: mkDerivation { pname = "mtl-prelude"; version = "2.0.3.1"; @@ -22825,10 +27232,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/nikita-volkov/mtl-prelude"; description = "Reexports of most definitions from \"mtl\" and \"transformers\""; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "multi-containers" = callPackage + ({ mkDerivation, base, containers, lib }: + mkDerivation { + pname = "multi-containers"; + version = "0.1.1"; + sha256 = "664db68258c3ef46a7376182e5c30b9e58828fded6eadeb854e77f9a14c2f86a"; + libraryHaskellDepends = [ base containers ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/zliu41/multi-containers#readme"; + description = "A few multimap variants"; + license = lib.licenses.bsd3; }) {}; "multiarg" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "multiarg"; version = "0.30.0.10"; @@ -22840,10 +27260,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/massysett/multiarg"; description = "Command lines for options that take multiple arguments"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "multimap" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "multimap"; version = "1.2.1"; @@ -22853,35 +27273,54 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://hub.darcs.net/scravy/multimap"; description = "A multimap"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "multipart" = callPackage - ({ mkDerivation, base, bytestring, parsec, stdenv, stringsearch }: + ({ mkDerivation, base, bytestring, lib, parsec, stringsearch }: mkDerivation { pname = "multipart"; - version = "0.1.3"; - sha256 = "9f60512e7b04c78442bd7c9de621597f6f2c4288b3bc1bb2834d08b5bd2796f4"; + version = "0.2.1"; + sha256 = "76470ab73c1767b700f8ee284f2e965ab6f94e37ad3243970567cbdbed24d65c"; libraryHaskellDepends = [ base bytestring parsec stringsearch ]; doHaddock = false; doCheck = false; homepage = "http://www.github.com/silkapp/multipart"; - description = "HTTP multipart split out of the cgi package"; - license = stdenv.lib.licenses.bsd3; + description = "Parsers for the HTTP multipart format"; + license = lib.licenses.bsd3; }) {}; "multiset" = callPackage - ({ mkDerivation, base, containers, deepseq, stdenv }: + ({ mkDerivation, base, containers, deepseq, lib }: mkDerivation { pname = "multiset"; - version = "0.3.4.1"; - sha256 = "b0ff7deec3dcb65145dd2368dadcf8bb2c087345d106440f8ddcbd4acab63e16"; + version = "0.3.4.3"; + sha256 = "79fcae15a5d3ce28f0b973ad90290f7451396e81cc92007456ce2bb49b9415c4"; libraryHaskellDepends = [ base containers deepseq ]; doHaddock = false; doCheck = false; description = "The Data.MultiSet container type"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "multistate" = callPackage + ({ mkDerivation, base, lib, monad-control, mtl, tagged + , transformers, transformers-base + }: + mkDerivation { + pname = "multistate"; + version = "0.8.0.3"; + sha256 = "0f597aee4fdd243751a9f2d935156960c437252527818bec7d98709991a87969"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base monad-control mtl tagged transformers transformers-base + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/lspitzner/multistate"; + description = "like mtl's ReaderT / WriterT / StateT, but more than one contained value/type"; + license = lib.licenses.bsd3; }) {}; "murmur-hash" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "murmur-hash"; version = "0.1.0.9"; @@ -22891,31 +27330,33 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/nominolo/murmur-hash"; description = "MurmurHash2 implementation for Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "murmur3" = callPackage - ({ mkDerivation, base, bytestring, cereal, stdenv }: + ({ mkDerivation, base, bytestring, cereal, lib }: mkDerivation { pname = "murmur3"; - version = "1.0.3"; - sha256 = "102c81e0e6ae604f51bccced6d2d493f4de0b65e856cd0492a17f9f8e4d51f2a"; + version = "1.0.4"; + sha256 = "15ae8d079e9128a2fcc03621d69ababc373b8f9f6ff2cc50ff8b7b0b7b535a08"; + revision = "1"; + editedCabalFile = "130ign0n566nsrzfp4ipb2sy5hq1ymxdlmqb80zbpdc0rdkqh0x0"; libraryHaskellDepends = [ base bytestring cereal ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/plaprade/murmur3"; + homepage = "http://github.com/haskoin/murmur3"; description = "Pure Haskell implementation of the MurmurHash3 x86_32 algorithm"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.mit; }) {}; "mustache" = callPackage ({ mkDerivation, aeson, base, bytestring, cmdargs, containers - , directory, either, filepath, mtl, parsec, scientific, stdenv + , directory, either, filepath, lib, mtl, parsec, scientific , template-haskell, text, th-lift, unordered-containers, vector , yaml }: mkDerivation { pname = "mustache"; - version = "2.3.0"; - sha256 = "018863e578e971e393edc65dd7e0ed92a0e37fc152a47bb379fd8abd59537be0"; + version = "2.3.1"; + sha256 = "ac8bf93d36fc766f54a54b72ddf71d1ab90864ca86bdce3415d2e69823fdb348"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -22930,11 +27371,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/JustusAdam/mustache"; description = "A mustache template parser library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "mutable-containers" = callPackage - ({ mkDerivation, base, containers, ghc-prim, mono-traversable - , primitive, stdenv, vector + ({ mkDerivation, base, containers, ghc-prim, lib, mono-traversable + , primitive, vector }: mkDerivation { pname = "mutable-containers"; @@ -22947,66 +27388,79 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/snoyberg/mono-traversable#readme"; description = "Abstactions and concrete implementations of mutable containers"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "mwc-probability" = callPackage - ({ mkDerivation, base, mwc-random, primitive, stdenv, transformers + ({ mkDerivation, base, containers, lib, mwc-random, primitive + , transformers }: mkDerivation { pname = "mwc-probability"; - version = "2.0.4"; - sha256 = "9fe9ed0e264bf85420a3086a1af9d6e749ff33c9c59428891dfaaa72b1385157"; - revision = "1"; - editedCabalFile = "1b4wbxkxx0szjgzgn5jc1qap80zx6ispxrd51yxs4z7llv15w5k6"; - libraryHaskellDepends = [ base mwc-random primitive transformers ]; + version = "2.3.1"; + sha256 = "3f8d997c6552786a87bfe4d7cc4af50fda2d5ef2feb96be4fe44649843dff795"; + libraryHaskellDepends = [ + base containers mwc-random primitive transformers + ]; doHaddock = false; doCheck = false; homepage = "http://github.com/jtobin/mwc-probability"; description = "Sampling function-based probability distributions"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "mwc-probability-transition" = callPackage - ({ mkDerivation, base, exceptions, ghc-prim, hspec, logging-effect - , mtl, mwc-probability, primitive, QuickCheck, stdenv, transformers + "mwc-random" = callPackage + ({ mkDerivation, base, lib, math-functions, primitive, random, time + , vector }: mkDerivation { - pname = "mwc-probability-transition"; - version = "0.4"; - sha256 = "3e44b6f3f3b2a739776484e7d4ab98ab1d5c7e50bcba53a40d2f0ac96003e768"; + pname = "mwc-random"; + version = "0.15.0.1"; + sha256 = "030b05f658f2f574dd073e50338c8982a4cc8cbd2fa7111548539c05c92b0cdd"; + revision = "2"; + editedCabalFile = "0si7d23ycyg1072w10v06zh1xx4yy5jxwmrrs65inrs7fhdb1r28"; libraryHaskellDepends = [ - base exceptions ghc-prim hspec logging-effect mtl mwc-probability - primitive QuickCheck transformers + base math-functions primitive random time vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/ocramz/mwc-probability-transition"; - description = "A Markov stochastic transition operator with logging"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/bos/mwc-random"; + description = "Fast, high quality pseudo random number generation"; + license = lib.licenses.bsd3; }) {}; - "mwc-random" = callPackage - ({ mkDerivation, base, math-functions, primitive, stdenv, time - , vector + "mwc-random-monad" = callPackage + ({ mkDerivation, base, lib, monad-primitive, mwc-random, primitive + , transformers, vector }: mkDerivation { - pname = "mwc-random"; - version = "0.14.0.0"; - sha256 = "00370edaa60a51c86663868ecc2b1995824970001875cec458e9acc13511efa2"; + pname = "mwc-random-monad"; + version = "0.7.3.1"; + sha256 = "d0f37917e646c9610dcbee4173c4ac50e054418f62623a42f19e3c0c39979440"; libraryHaskellDepends = [ - base math-functions primitive time vector + base monad-primitive mwc-random primitive transformers vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/bos/mwc-random"; - description = "Fast, high quality pseudo random number generation"; - license = stdenv.lib.licenses.bsd3; + description = "Monadic interface for mwc-random"; + license = lib.licenses.bsd3; + }) {}; + "mx-state-codes" = callPackage + ({ mkDerivation, aeson, base, lib, text }: + mkDerivation { + pname = "mx-state-codes"; + version = "1.0.0.0"; + sha256 = "06abe94b48c2c24f13ee31039bb37e0373b629adeb2ce20b0b1a6722203cbccb"; + libraryHaskellDepends = [ aeson base text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/prikhi/mx-state-codes#readme"; + description = "ISO 3166-2:MX State Codes and Names"; + license = lib.licenses.bsd3; }) {}; "mysql" = callPackage - ({ mkDerivation, base, bytestring, Cabal, containers, mysql, stdenv - }: + ({ mkDerivation, base, bytestring, Cabal, containers, lib, mysql }: mkDerivation { pname = "mysql"; - version = "0.1.6"; - sha256 = "9e549f61c9259ba82405b5dab2d00f010de720edc30cf4ce5a51a367c72799ee"; + version = "0.2.0.1"; + sha256 = "4d23573547cebd39a2b88bbfc1d6d4ff0a3bca4fd63cfcb824ce0aefd386a89a"; setupHaskellDepends = [ base Cabal ]; libraryHaskellDepends = [ base bytestring containers ]; librarySystemDepends = [ mysql ]; @@ -23014,55 +27468,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/paul-rouse/mysql"; description = "A low-level MySQL client library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) mysql;}; - "mysql-haskell" = callPackage - ({ mkDerivation, base, binary, binary-ieee754, binary-parsers - , blaze-textual, bytestring, bytestring-lexing, cryptonite - , io-streams, memory, monad-loops, network, scientific, stdenv - , tcp-streams, text, time, tls, vector, wire-streams, word24 - }: - mkDerivation { - pname = "mysql-haskell"; - version = "0.8.4.1"; - sha256 = "9da45fb74c7bacbf4a56ba6493f8d77592fac5ee7ac0f5c07e87f8464bc57354"; - libraryHaskellDepends = [ - base binary binary-ieee754 binary-parsers blaze-textual bytestring - bytestring-lexing cryptonite io-streams memory monad-loops network - scientific tcp-streams text time tls vector wire-streams word24 - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/winterland1989/mysql-haskell"; - description = "pure haskell MySQL driver"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "mysql-haskell-nem" = callPackage - ({ mkDerivation, base, bytestring, io-streams, mysql-haskell - , scientific, stdenv, text, time - }: - mkDerivation { - pname = "mysql-haskell-nem"; - version = "0.1.0.0"; - sha256 = "7a0868b76edc96a7aff7860f96436b9040f6cb9319dd67f68bfd700948721f0d"; - libraryHaskellDepends = [ - base bytestring io-streams mysql-haskell scientific text time - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/lorenzo/mysql-haskell-nem#readme"; - description = "Adds a interface like mysql-simple to mysql-haskell"; - license = stdenv.lib.licenses.bsd3; - }) {}; "mysql-simple" = callPackage ({ mkDerivation, attoparsec, base, base16-bytestring, blaze-builder - , blaze-textual, bytestring, containers, mysql, old-locale - , pcre-light, stdenv, text, time + , blaze-textual, bytestring, containers, lib, mysql, old-locale + , pcre-light, text, time }: mkDerivation { pname = "mysql-simple"; - version = "0.4.5"; - sha256 = "b03c422ed8a62fa7f98b62634a06da8454980c6a733e275020ca7cedbb6e7cb1"; + version = "0.4.6"; + sha256 = "7ee571fc8542026c095d12e2c2d19d5fd14a68a46a55153ad92c6991c064a8aa"; libraryHaskellDepends = [ attoparsec base base16-bytestring blaze-builder blaze-textual bytestring containers mysql old-locale pcre-light text time @@ -23071,11 +27487,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/paul-rouse/mysql-simple"; description = "A mid-level MySQL client library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "n2o" = callPackage - ({ mkDerivation, base, binary, bytestring, containers, stdenv, text - }: + ({ mkDerivation, base, binary, bytestring, containers, lib, text }: mkDerivation { pname = "n2o"; version = "0.11.1"; @@ -23085,10 +27500,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/xafizoff/n2o#readme"; description = "Abstract Protocol Loop"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "nagios-check" = callPackage - ({ mkDerivation, base, bifunctors, exceptions, mtl, stdenv, text }: + ({ mkDerivation, base, bifunctors, exceptions, lib, mtl, text }: mkDerivation { pname = "nagios-check"; version = "0.3.2"; @@ -23098,37 +27513,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/olorin/haskell-nagios-check"; description = "Package for writing monitoring plugins"; - license = stdenv.lib.licenses.mit; - }) {}; - "named" = callPackage - ({ mkDerivation, base, stdenv }: - mkDerivation { - pname = "named"; - version = "0.2.0.0"; - sha256 = "c01a5bb4cf36082da40a90880fbf8fbe72f7ab57027e788be42901777ddf8d9e"; - revision = "2"; - editedCabalFile = "0h9d74h6g685g1g0ylqf7kws1ancdy3q6fi39vinf5alkqa7kxwd"; - libraryHaskellDepends = [ base ]; - doHaddock = false; - doCheck = false; - description = "Named parameters (keyword arguments) for Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; "names-th" = callPackage - ({ mkDerivation, base, containers, stdenv, template-haskell }: + ({ mkDerivation, base, containers, lib, template-haskell }: mkDerivation { pname = "names-th"; - version = "0.3.0.0"; - sha256 = "0be38f6a22afb69ddda5a3cae095b51835bdae853256403e97078679a9fba526"; + version = "0.3.0.1"; + sha256 = "4a89a14828aa30d074a1a6650037bc49f4d5d2207c2ffe81ecba476381a75489"; libraryHaskellDepends = [ base containers template-haskell ]; doHaddock = false; doCheck = false; homepage = "http://khibino.github.io/haskell-relational-record/"; description = "Manipulate name strings for TH"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "nano-erl" = callPackage - ({ mkDerivation, base, stdenv, stm }: + ({ mkDerivation, base, lib, stm }: mkDerivation { pname = "nano-erl"; version = "0.1.0.1"; @@ -23137,10 +27538,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Small library for Erlang-style actor semantics"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "nanospec" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "nanospec"; version = "0.2.2"; @@ -23150,36 +27551,38 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/hspec/nanospec#readme"; description = "A lightweight implementation of a subset of Hspec's API"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "nats" = callPackage - ({ mkDerivation, stdenv }: + ({ mkDerivation, lib }: mkDerivation { pname = "nats"; version = "1.1.2"; sha256 = "b9d2d85d8612f9b06f8c9bfd1acecd848e03ab82cfb53afe1d93f5086b6e80ec"; - revision = "1"; - editedCabalFile = "1jzyysf758lfindlclqpzqcd0lrgrdv0rnz2lg8g1rvv07x2n7zh"; + revision = "3"; + editedCabalFile = "02ww45nskca28fsbh74iy0z4rm0yshws7lrxld45y053hrn1jdzc"; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/nats/"; description = "Natural numbers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "natural-induction" = callPackage - ({ mkDerivation, base, peano, stdenv }: + ({ mkDerivation, base, lib, peano }: mkDerivation { pname = "natural-induction"; version = "0.2.0.0"; sha256 = "99aa944a9bf54f549a867b73de56e56adf95d67408822054ee1abfcbe7ae33af"; + revision = "1"; + editedCabalFile = "012kjygd54rxinmaplqnbw0hkfm4wp829j0afjxr6h40x22gwzn5"; libraryHaskellDepends = [ base peano ]; doHaddock = false; doCheck = false; description = "Induction over natural numbers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "natural-sort" = callPackage - ({ mkDerivation, base, bytestring, parsec, stdenv, text }: + ({ mkDerivation, base, bytestring, lib, parsec, text }: mkDerivation { pname = "natural-sort"; version = "0.1.2"; @@ -23189,26 +27592,25 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://john-millikin.com/software/natural-sort/"; description = "User-friendly text collation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "natural-transformation" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "natural-transformation"; version = "0.4"; sha256 = "aac28e2c1147ed77c1ec0f0eb607a577fa26d0fd67474293ba860ec124efc8af"; - revision = "7"; - editedCabalFile = "03nkhdrwki9j81clgfck4yl7ylv6dwa7gi77kknzq3s3nqlp728v"; + revision = "9"; + editedCabalFile = "1db5ln24wcn4fcf92096iff8jp7q531ccm8pgbqincrbxayahl1s"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/ku-fpg/natural-transformation"; description = "A natural transformation package"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "ndjson-conduit" = callPackage - ({ mkDerivation, aeson, attoparsec, base, bytestring, conduit - , stdenv + ({ mkDerivation, aeson, attoparsec, base, bytestring, conduit, lib }: mkDerivation { pname = "ndjson-conduit"; @@ -23221,27 +27623,112 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/srijs/haskell-ndjson-conduit"; description = "Conduit-based parsing and serialization for newline delimited JSON"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "neat-interpolation" = callPackage - ({ mkDerivation, base, base-prelude, megaparsec, stdenv - , template-haskell, text - }: + ({ mkDerivation, base, lib, megaparsec, template-haskell, text }: mkDerivation { pname = "neat-interpolation"; - version = "0.3.2.4"; - sha256 = "de7370d938ffd8c7b52d732f4f088387ed8216cf9767d818e99b7ec827931752"; - libraryHaskellDepends = [ - base base-prelude megaparsec template-haskell text - ]; + version = "0.5.1.2"; + sha256 = "962a4a92da4911c8e5b784ed43200b764ea8c6b3add032a09c57658e4b4684a1"; + libraryHaskellDepends = [ base megaparsec template-haskell text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nikita-volkov/neat-interpolation"; description = "A quasiquoter for neat and simple multiline text interpolation"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "net-mqtt" = callPackage + ({ mkDerivation, async, attoparsec, attoparsec-binary, base, binary + , bytestring, conduit, conduit-extra, connection, containers + , deepseq, lib, network-conduit-tls, network-uri + , optparse-applicative, QuickCheck, stm, text, websockets + }: + mkDerivation { + pname = "net-mqtt"; + version = "0.7.1.1"; + sha256 = "db6e285758c9f016491978f734af4afdbd17eb7cda4a7d8bd34a319b854ac347"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + async attoparsec attoparsec-binary base binary bytestring conduit + conduit-extra connection containers deepseq network-conduit-tls + network-uri QuickCheck stm text websockets + ]; + executableHaskellDepends = [ + async attoparsec attoparsec-binary base binary bytestring conduit + conduit-extra connection containers deepseq network-conduit-tls + network-uri optparse-applicative QuickCheck stm text websockets + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/dustin/mqtt-hs#readme"; + description = "An MQTT Protocol Implementation"; + license = lib.licenses.bsd3; + }) {}; + "net-mqtt-lens" = callPackage + ({ mkDerivation, base, lens, lib, net-mqtt }: + mkDerivation { + pname = "net-mqtt-lens"; + version = "0.1.1.0"; + sha256 = "9879a6db01f3bd1d96480249efca5055aa6141321ec97845909151ec0b599166"; + libraryHaskellDepends = [ base lens net-mqtt ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/dustin/net-mqtt-lens#readme"; + description = "Optics for net-mqtt"; + license = lib.licenses.bsd3; + }) {}; + "netcode-io" = callPackage + ({ mkDerivation, base, bindings-DSL, lib, libsodium }: + mkDerivation { + pname = "netcode-io"; + version = "0.0.2"; + sha256 = "445fc993ae65ae909f251adb66201563fba26dcf14af1fc9d750d2dd59f2c658"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base bindings-DSL ]; + librarySystemDepends = [ libsodium ]; + doHaddock = false; + doCheck = false; + homepage = "http://www.github.com/Mokosha/netcode-io"; + description = "Bindings to the low-level netcode.io library."; + license = lib.licenses.bsd3; + }) {inherit (pkgs) libsodium;}; + "netlib-carray" = callPackage + ({ mkDerivation, array, base, carray, lib, netlib-ffi, transformers + }: + mkDerivation { + pname = "netlib-carray"; + version = "0.1"; + sha256 = "a577d19a79f7360d7916185e92feabdc42723a130ac3794e011655de3ba90466"; + libraryHaskellDepends = [ + array base carray netlib-ffi transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "http://hub.darcs.net/thielema/netlib-carray/"; + description = "Helper modules for CArray wrappers to BLAS and LAPACK"; + license = lib.licenses.bsd3; + }) {}; + "netlib-comfort-array" = callPackage + ({ mkDerivation, base, comfort-array, lib, netlib-ffi, transformers + }: + mkDerivation { + pname = "netlib-comfort-array"; + version = "0.0.0.1"; + sha256 = "e32e5eabca4549cdd8dbd71c58acf14377d389317b999b25b37d62f9100d976c"; + libraryHaskellDepends = [ + base comfort-array netlib-ffi transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "http://hub.darcs.net/thielema/netlib-comfort-array/"; + description = "Helper modules for comfort-array wrappers to BLAS and LAPACK"; + license = lib.licenses.bsd3; }) {}; "netlib-ffi" = callPackage - ({ mkDerivation, base, guarded-allocation, stdenv, storable-complex + ({ mkDerivation, base, guarded-allocation, lib, storable-complex , transformers }: mkDerivation { @@ -23255,19 +27742,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://hub.darcs.net/thielema/netlib-ffi/"; description = "Helper modules for FFI to BLAS and LAPACK"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "netpbm" = callPackage ({ mkDerivation, attoparsec, attoparsec-binary, base, bytestring - , stdenv, storable-record, unordered-containers, vector + , lib, storable-record, unordered-containers, vector , vector-th-unbox }: mkDerivation { pname = "netpbm"; - version = "1.0.2"; - sha256 = "846a04bca94be31c779888febc390c64cfba93e40f3a7a2f80ff6a6e44fcc2d7"; - revision = "1"; - editedCabalFile = "1vhwjv5c5gxn9l9982da54nzczbmj8rl09xn8ac7rix0zmmyvl50"; + version = "1.0.4"; + sha256 = "d7208ba271ab1d4ce87426e6fea23d392cca10a4c75297cdcec39180c998481c"; libraryHaskellDepends = [ attoparsec attoparsec-binary base bytestring storable-record unordered-containers vector vector-th-unbox @@ -23276,16 +27761,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/nh2/haskell-netpbm"; description = "Loading PBM, PGM, PPM image files"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "nettle" = callPackage ({ mkDerivation, base, byteable, bytestring, crypto-cipher-types - , nettle, securemem, stdenv, tagged + , lib, nettle, securemem, tagged }: mkDerivation { pname = "nettle"; version = "0.3.0"; sha256 = "cf3f08980e8e52190301d33db3b1fe7f02bcf5d276a74a8b8283b79e72bf7d5d"; + revision = "1"; + editedCabalFile = "1j8h6m4cj1ykxrsxmjiyb1c4mv6cawssgb8phl0aijrjn3b79f2b"; libraryHaskellDepends = [ base byteable bytestring crypto-cipher-types securemem tagged ]; @@ -23294,11 +27781,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/stbuehler/haskell-nettle"; description = "safe nettle binding"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {inherit (pkgs) nettle;}; "netwire" = callPackage - ({ mkDerivation, base, containers, deepseq, parallel, profunctors - , random, semigroups, stdenv, time, transformers + ({ mkDerivation, base, containers, deepseq, lib, parallel + , profunctors, random, semigroups, time, transformers }: mkDerivation { pname = "netwire"; @@ -23312,10 +27799,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/esoeylemez/netwire"; description = "Functional reactive programming library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "netwire-input" = callPackage - ({ mkDerivation, base, deepseq, netwire, stdenv }: + ({ mkDerivation, base, deepseq, lib, netwire }: mkDerivation { pname = "netwire-input"; version = "0.0.7"; @@ -23325,16 +27812,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://www.github.com/Mokosha/netwire-input"; description = "Input handling abstractions for netwire"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "netwire-input-glfw" = callPackage - ({ mkDerivation, base, containers, deepseq, GLFW-b, mtl - , netwire-input, stdenv, stm + ({ mkDerivation, base, containers, deepseq, GLFW-b, lib, mtl + , netwire-input, stm }: mkDerivation { pname = "netwire-input-glfw"; - version = "0.0.10"; - sha256 = "1ea458273055fa2f82451b889b9a2c54e0b5bbdf55a16c35d0ccd392793728e4"; + version = "0.0.11"; + sha256 = "e8b32df1e2b95c9e6afe10cd14f96be4ad00c7484e3d825253a6ae8a18983fea"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -23344,102 +27831,54 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://www.github.com/Mokosha/netwire-input-glfw"; description = "GLFW instance of netwire-input"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "network" = callPackage - ({ mkDerivation, base, bytestring, stdenv, unix }: + ({ mkDerivation, base, bytestring, deepseq, lib }: mkDerivation { pname = "network"; - version = "2.8.0.0"; - sha256 = "c8905268b7e3b4cf624a40245bf11b35274a6dd836a5d4d531b5760075645303"; - libraryHaskellDepends = [ base bytestring unix ]; + version = "3.1.1.1"; + sha256 = "d7ef590173fff2ab522fbc167f3fafb867e4ecfca279eb3ef0d137b51f142c9a"; + libraryHaskellDepends = [ base bytestring deepseq ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell/network"; description = "Low-level networking interface"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "network-anonymous-i2p" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, exceptions, mtl - , network, network-attoparsec, network-simple, stdenv, text - , transformers, uuid - }: - mkDerivation { - pname = "network-anonymous-i2p"; - version = "0.10.0"; - sha256 = "cff5796c36c1ebbb969e5433538eb3f3979acef9825a7bfb683ed002023fff2c"; - enableSeparateDataOutput = true; - libraryHaskellDepends = [ - attoparsec base bytestring exceptions mtl network - network-attoparsec network-simple text transformers uuid - ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/solatis/haskell-network-anonymous-i2p"; - description = "Haskell API for I2P anonymous networking"; - license = stdenv.lib.licenses.mit; - }) {}; - "network-anonymous-tor" = callPackage - ({ mkDerivation, attoparsec, base, base32string, bytestring - , exceptions, hexstring, network, network-attoparsec - , network-simple, socks, splice, stdenv, text, transformers - }: - mkDerivation { - pname = "network-anonymous-tor"; - version = "0.11.0"; - sha256 = "41aee5b34aaaec6fa47a56cca61fafec22097bda25d13d5baef6b7924e127549"; - isLibrary = true; - isExecutable = true; - enableSeparateDataOutput = true; - libraryHaskellDepends = [ - attoparsec base base32string bytestring exceptions hexstring - network network-attoparsec network-simple socks text transformers - ]; - executableHaskellDepends = [ - base exceptions network network-simple splice - ]; - doHaddock = false; - doCheck = false; - homepage = "http://www.leonmergen.com/opensource.html"; - description = "Haskell API for Tor anonymous networking"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.bsd3; }) {}; - "network-attoparsec" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, enclosed-exceptions - , exceptions, lifted-base, monad-control, mtl, network, stdenv - , transformers - }: + "network-bsd" = callPackage + ({ mkDerivation, base, deepseq, lib, network }: mkDerivation { - pname = "network-attoparsec"; - version = "0.12.2"; - sha256 = "9790a9bad286ab1474dadbece3e4b2e1dd068d4ede3847cb73bcd66386bf08f0"; - enableSeparateDataOutput = true; - libraryHaskellDepends = [ - attoparsec base bytestring enclosed-exceptions exceptions - lifted-base monad-control mtl network transformers - ]; + pname = "network-bsd"; + version = "2.8.1.0"; + sha256 = "d94961ca15c42c798d19cde540ec12b25cc43435fb95e682399d6c1a02022d4e"; + revision = "4"; + editedCabalFile = "1gd9a8j7fwg0jz0s6il5fk9sl0hm19ja1w56ix51wa0qi2h5x56d"; + libraryHaskellDepends = [ base deepseq network ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/solatis/haskell-network-attoparsec"; - description = "Utility functions for running a parser against a socket"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/haskell/network-bsd"; + description = "POSIX network database () API"; + license = lib.licenses.bsd3; }) {}; "network-byte-order" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "network-byte-order"; - version = "0.0.0.0"; - sha256 = "3bb6f1110d9ac16a18f0c2d5921af584044e667e46fcfbdebd7a1e74e329de71"; + version = "0.1.6"; + sha256 = "f2b0ccc9b759d686af30aac874fc394c13c1fc8a3db00fac401c9339c263dc5e"; + revision = "1"; + editedCabalFile = "0fpyfd1adg9fr7w6afxkx306c0kaz3ji3x78sl29v9j3mh4vdn13"; libraryHaskellDepends = [ base bytestring ]; doHaddock = false; doCheck = false; description = "Network byte order utilities"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "network-conduit-tls" = callPackage ({ mkDerivation, base, bytestring, conduit, conduit-extra - , connection, data-default-class, network, stdenv - , streaming-commons, tls, transformers, unliftio-core + , connection, data-default-class, lib, network, streaming-commons + , tls, transformers, unliftio-core }: mkDerivation { pname = "network-conduit-tls"; @@ -23453,43 +27892,32 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/snoyberg/conduit"; description = "Create TLS-aware network code with conduits"; - license = stdenv.lib.licenses.mit; - }) {}; - "network-house" = callPackage - ({ mkDerivation, array, base, containers, mtl, stdenv }: - mkDerivation { - pname = "network-house"; - version = "0.1.0.2"; - sha256 = "071fbc22fc516175e78235d9e29ccefd8eec7c3caa2e6de74dddf62cdbffab43"; - libraryHaskellDepends = [ array base containers mtl ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/nh2/network-house"; - description = "data and parsers for Ethernet, TCP, UDP, IPv4, IPv6, ICMP, DHCP, TFTP"; - license = stdenv.lib.licenses.gpl2; + license = lib.licenses.mit; }) {}; "network-info" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "network-info"; version = "0.2.0.10"; sha256 = "5680f6975d34cf4f81fa7ca0c8efd682261d6a1119e06dece0f67c7bd97fd52a"; + revision = "1"; + editedCabalFile = "07kiw56lhc56kqrnvpa11f5nnnid6by3aq00jrkcbbg7w0q71a6d"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/jystic/network-info"; + homepage = "http://github.com/jacobstanley/network-info"; description = "Access the local computer's basic network configuration"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "network-ip" = callPackage ({ mkDerivation, base, data-default-class, data-dword, data-endian - , data-serializer, data-textual, hashable, parsers, stdenv + , data-serializer, data-textual, hashable, lib, parsers , text-printer, type-hint }: mkDerivation { pname = "network-ip"; - version = "0.3.0.2"; - sha256 = "ee259d236312aafc4bd08dfeff2ebe4b4f930b2f5879764e1a6d5675c5105efe"; + version = "0.3.0.3"; + sha256 = "e01dcc4389f3800536066ca150b6b5130d9d4b7fe7ed8e98ae7d92f3f7b1955c"; libraryHaskellDepends = [ base data-default-class data-dword data-endian data-serializer data-textual hashable parsers text-printer type-hint @@ -23498,16 +27926,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mvv/network-ip"; description = "Internet Protocol data structures"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "network-messagepack-rpc" = callPackage - ({ mkDerivation, base, bytestring, data-msgpack, safe-exceptions - , stdenv, text, unordered-containers + ({ mkDerivation, base, bytestring, data-msgpack, lib + , safe-exceptions, text, unordered-containers }: mkDerivation { pname = "network-messagepack-rpc"; - version = "0.1.1.0"; - sha256 = "10640121caf2f8b9e8e02d90baf6e1ac4f83b82d502c389269bea842416e038f"; + version = "0.1.2.0"; + sha256 = "7ed2442333de97512d92cd029bf802fc68a0d757df9787cdb4debbbde67c0a85"; libraryHaskellDepends = [ base bytestring data-msgpack safe-exceptions text unordered-containers @@ -23516,66 +27944,83 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/iij-ii/direct-hs/tree/master/network-messagepack-rpc"; description = "MessagePack RPC"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "network-multicast" = callPackage - ({ mkDerivation, base, network, stdenv }: + "network-messagepack-rpc-websocket" = callPackage + ({ mkDerivation, base, lib, network-messagepack-rpc, text + , websockets, wss-client + }: mkDerivation { - pname = "network-multicast"; - version = "0.2.0"; - sha256 = "0f3b50abc3a401c20cc6a0ec51a49d2a48e5b467d9fbd63b7cf803165fe975f2"; - libraryHaskellDepends = [ base network ]; + pname = "network-messagepack-rpc-websocket"; + version = "0.1.1.1"; + sha256 = "066cc9346ebe4fbb2329fa0cae3a65278d6ae21ca8b793455ff01d6ac756b329"; + libraryHaskellDepends = [ + base network-messagepack-rpc text websockets wss-client + ]; doHaddock = false; doCheck = false; - description = "Simple multicast library"; - license = stdenv.lib.licenses.publicDomain; + homepage = "https://github.com/iij-ii/direct-hs/tree/master/network-messagepack-rpc-websocket"; + description = "WebSocket backend for MessagePack RPC"; + license = lib.licenses.bsd3; + }) {}; + "network-run" = callPackage + ({ mkDerivation, base, bytestring, lib, network }: + mkDerivation { + pname = "network-run"; + version = "0.2.4"; + sha256 = "f415c619eeb34a18493dfcd634049c7a1da1b02615e1387b0096c80126af6d70"; + libraryHaskellDepends = [ base bytestring network ]; + doHaddock = false; + doCheck = false; + description = "Simple network runner library"; + license = lib.licenses.bsd3; }) {}; "network-simple" = callPackage - ({ mkDerivation, base, bytestring, network, safe-exceptions, socks - , stdenv, transformers + ({ mkDerivation, base, bytestring, lib, network, network-bsd + , safe-exceptions, socks, transformers }: mkDerivation { pname = "network-simple"; - version = "0.4.3"; - sha256 = "0dd5cf1ed308bbe9601dc39026419151f552f386ec5e82417ad4f86cc4539028"; - revision = "1"; - editedCabalFile = "1xyz4b24vgnidvd43cfmf0k6090dayhfcp6n8x894ibd2mq3vash"; + version = "0.4.5"; + sha256 = "07a0bf25972a5fb42ab68f71db00b2758c6b15f09f73b1324550749d397b179e"; libraryHaskellDepends = [ - base bytestring network safe-exceptions socks transformers + base bytestring network network-bsd safe-exceptions socks + transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/k0001/network-simple"; description = "Simple network sockets usage patterns"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "network-simple-tls" = callPackage - ({ mkDerivation, base, bytestring, data-default, network - , network-simple, safe-exceptions, stdenv, tls, transformers, x509 - , x509-store, x509-system, x509-validation + ({ mkDerivation, base, bytestring, data-default, lib, network + , network-simple, safe-exceptions, tls, tls-session-manager + , transformers, x509, x509-store, x509-system, x509-validation }: mkDerivation { pname = "network-simple-tls"; - version = "0.3.1"; - sha256 = "d25f5b0ecf1d11755e01c23b60714910f6091d14d8fac33307613cc4a4887c8a"; + version = "0.4"; + sha256 = "c156bb400474049f7bcf0d559e548dc0be73b97da53dab0d0138f02e2eeebd30"; libraryHaskellDepends = [ base bytestring data-default network network-simple safe-exceptions - tls transformers x509 x509-store x509-system x509-validation + tls tls-session-manager transformers x509 x509-store x509-system + x509-validation ]; doHaddock = false; doCheck = false; homepage = "https://github.com/k0001/network-simple-tls"; description = "Simple interface to TLS secured network sockets"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "network-transport" = callPackage - ({ mkDerivation, base, binary, bytestring, deepseq, hashable - , stdenv, transformers + ({ mkDerivation, base, binary, bytestring, deepseq, hashable, lib + , transformers }: mkDerivation { pname = "network-transport"; - version = "0.5.2"; - sha256 = "e795672b43d67ac7bfade72173548ae6bf8208c1890e22aba7809098558f9054"; + version = "0.5.4"; + sha256 = "5b870bffb4a61b29616bf9520733c7f16fd455ac2e678cc156d61ffa47c4ec47"; libraryHaskellDepends = [ base binary bytestring deepseq hashable transformers ]; @@ -23583,10 +28028,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://haskell-distributed.github.com"; description = "Network abstraction layer"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "network-transport-composed" = callPackage - ({ mkDerivation, base, bytestring, network-transport, stdenv }: + ({ mkDerivation, base, bytestring, lib, network-transport }: mkDerivation { pname = "network-transport-composed"; version = "0.2.1"; @@ -23596,52 +28041,54 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://haskell-distributed.github.com"; description = "Compose network transports"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "network-uri" = callPackage - ({ mkDerivation, base, deepseq, parsec, stdenv }: + ({ mkDerivation, base, deepseq, lib, parsec, template-haskell + , th-compat + }: mkDerivation { pname = "network-uri"; - version = "2.6.1.0"; - sha256 = "423e0a2351236f3fcfd24e39cdbc38050ec2910f82245e69ca72a661f7fc47f0"; - revision = "1"; - editedCabalFile = "141nj7q0p9wkn5gr41ayc63cgaanr9m59yym47wpxqr3c334bk32"; - libraryHaskellDepends = [ base deepseq parsec ]; + version = "2.6.4.1"; + sha256 = "57856db93608a4d419f681b881c9b8d4448800d5a687587dc37e8a9e0b223584"; + libraryHaskellDepends = [ + base deepseq parsec template-haskell th-compat + ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell/network-uri"; description = "URI manipulation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "newtype" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "newtype"; - version = "0.2"; - sha256 = "b714033abd9a8b0903bcef0d36d0913de2a5003c852f43f97fa688717289e459"; + version = "0.2.2.0"; + sha256 = "3a00ffd1bb48a81e09f8be6510fa4c642ba1482b2f8d4777af1b5dd06c55ebac"; + revision = "1"; + editedCabalFile = "0261ljw57c7l7mw3z553s6ak8lmgyqwmfhk1m2jv6snra2i5shs4"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; description = "A typeclass and set of functions for working with newtypes"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "newtype-generics" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "newtype-generics"; - version = "0.5.3"; - sha256 = "f295f001a86bdbcf759d6b91b9e7ae27cd431ccf41d9b9d34ee1c926b88efe45"; - revision = "1"; - editedCabalFile = "1glnwq1lw7780qgahqvh1qfx6k2ciwmbhc2wcc78v3aa3s954c8v"; + version = "0.6"; + sha256 = "8a8bace7786b33fe9d356a05b407b41db89f9bad60980d9a664fd33d21af7e11"; libraryHaskellDepends = [ base transformers ]; doHaddock = false; doCheck = false; homepage = "http://github.com/sjakobi/newtype-generics"; description = "A typeclass and set of functions for working with newtypes"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "nicify-lib" = callPackage - ({ mkDerivation, base, parsec, stdenv, transformers }: + ({ mkDerivation, base, lib, parsec, transformers }: mkDerivation { pname = "nicify-lib"; version = "1.0.1"; @@ -23650,10 +28097,29 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Pretty print the standard output of default `Show` instances"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "nix-derivation" = callPackage + ({ mkDerivation, attoparsec, base, containers, deepseq, filepath + , lib, pretty-show, text, vector + }: + mkDerivation { + pname = "nix-derivation"; + version = "1.1.2"; + sha256 = "c7ff162f245021d7ba8ea24b993b1df2241744f6e0a78b0783092182fbea8808"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + attoparsec base containers deepseq filepath text vector + ]; + executableHaskellDepends = [ attoparsec base pretty-show text ]; + doHaddock = false; + doCheck = false; + description = "Parse and render *.drv files"; + license = lib.licenses.bsd3; }) {}; "nix-paths" = callPackage - ({ mkDerivation, base, process, stdenv }: + ({ mkDerivation, base, lib, process }: mkDerivation { pname = "nix-paths"; version = "1.0.1"; @@ -23664,43 +28130,53 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/peti/nix-paths"; description = "Knowledge of Nix's installation directories"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "no-value" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "no-value"; + version = "1.0.0.0"; + sha256 = "8ed237efdab93eb273596e03cc391803640acb189b35a863e4e440451aea9fc9"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/cdornan/no-value#readme"; + description = "A type class for choosing sentinel-like values"; + license = lib.licenses.bsd3; }) {}; "non-empty" = callPackage - ({ mkDerivation, base, containers, deepseq, QuickCheck, stdenv + ({ mkDerivation, base, containers, deepseq, lib, QuickCheck , utility-ht }: mkDerivation { pname = "non-empty"; - version = "0.3.0.1"; - sha256 = "3fbd074804df96f307ae60a67b13e215b635e80a3505ee5f5b0bb26ad9b5eb03"; - revision = "1"; - editedCabalFile = "1628z42q77xjvwpyx3rifqf6mh4y6ivdl0lkhngxwz8c21bnf7d3"; + version = "0.3.3"; + sha256 = "ef02585128dfc4649ef44701fd4963f9dbde9f8543e6fa43a1f5bdd7939c7007"; libraryHaskellDepends = [ base containers deepseq QuickCheck utility-ht ]; doHaddock = false; doCheck = false; - homepage = "http://hub.darcs.net/thielema/non-empty/"; + homepage = "https://hub.darcs.net/thielema/non-empty/"; description = "List-like structures with static restrictions on the number of elements"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "non-empty-sequence" = callPackage - ({ mkDerivation, base, containers, semigroups, stdenv }: + ({ mkDerivation, base, containers, lib, semigroups }: mkDerivation { pname = "non-empty-sequence"; - version = "0.2.0.2"; - sha256 = "d9a3604c0c140197731895af56413edbf1cf6866f9c0636ece9d8314366dd1e1"; + version = "0.2.0.4"; + sha256 = "8071a8680bd44f81e7660c74c495302a34344a42d8ccdc3e869f0e29a398dd28"; libraryHaskellDepends = [ base containers semigroups ]; doHaddock = false; doCheck = false; homepage = "http://www.github.com/massysett/non-empty-sequence"; description = "Non-empty sequence"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "non-negative" = callPackage - ({ mkDerivation, base, QuickCheck, semigroups, stdenv, utility-ht - }: + ({ mkDerivation, base, lib, QuickCheck, semigroups, utility-ht }: mkDerivation { pname = "non-negative"; version = "0.1.2"; @@ -23713,13 +28189,15 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; license = "GPL"; }) {}; "nonce" = callPackage - ({ mkDerivation, base, base64-bytestring, bytestring, entropy - , stdenv, text, transformers, unliftio, unliftio-core + ({ mkDerivation, base, base64-bytestring, bytestring, entropy, lib + , text, transformers, unliftio, unliftio-core }: mkDerivation { pname = "nonce"; version = "1.0.7"; sha256 = "4b4f6232b2cb07a6de47a838b4dc35c346a745683866dbfc6ebb8682158037e1"; + revision = "2"; + editedCabalFile = "09xvg4lpmb1hw153afhbjrdg9v3npfwpdfhpv5y8b0qvb4zi3n9q"; libraryHaskellDepends = [ base base64-bytestring bytestring entropy text transformers unliftio unliftio-core @@ -23728,10 +28206,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/prowdsponsor/nonce"; description = "Generate cryptographic nonces"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "nondeterminism" = callPackage - ({ mkDerivation, base, containers, mtl, stdenv }: + ({ mkDerivation, base, containers, lib, mtl }: mkDerivation { pname = "nondeterminism"; version = "1.4"; @@ -23743,24 +28221,54 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; license = "LGPL"; }) {}; "nonempty-containers" = callPackage - ({ mkDerivation, base, comonad, containers, deepseq, semigroupoids - , stdenv, these + ({ mkDerivation, aeson, base, comonad, containers, deepseq, lib + , nonempty-vector, semigroupoids, these, vector }: mkDerivation { pname = "nonempty-containers"; - version = "0.1.1.0"; - sha256 = "33981526acb8b0d3b8aa2e787e50e6e56497ee4c2ef6691093d41d5bbe5517ee"; + version = "0.3.4.1"; + sha256 = "03d5038a3137a8d58fd934e76c00f3a563138601497068cce02947fb8003f632"; libraryHaskellDepends = [ - base comonad containers deepseq semigroupoids these + aeson base comonad containers deepseq nonempty-vector semigroupoids + these vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mstksg/nonempty-containers#readme"; description = "Non-empty variants of containers data types, with full API"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "nonempty-vector" = callPackage + ({ mkDerivation, base, Cabal, cabal-doctest, deepseq, lib + , primitive, vector + }: + mkDerivation { + pname = "nonempty-vector"; + version = "0.2.1.0"; + sha256 = "3e88159a1ad63039aba427597ea9d7eaf6e86789279d92e16214391b1bb2ce70"; + setupHaskellDepends = [ base Cabal cabal-doctest ]; + libraryHaskellDepends = [ base deepseq primitive vector ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/emilypi/nonempty-vector"; + description = "Non-empty vectors"; + license = lib.licenses.bsd3; + }) {}; + "nonempty-zipper" = callPackage + ({ mkDerivation, base, comonad, deepseq, lib, safe }: + mkDerivation { + pname = "nonempty-zipper"; + version = "1.0.0.2"; + sha256 = "5246c7cea39d7acb06ea85092d2831a7c3c974582ff199e1bc3614e4b329d281"; + libraryHaskellDepends = [ base comonad deepseq safe ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/freckle/nonempty-zipper#readme"; + description = "A non-empty comonadic list zipper"; + license = lib.licenses.mit; }) {}; "nonemptymap" = callPackage - ({ mkDerivation, base, containers, semigroupoids, stdenv }: + ({ mkDerivation, base, containers, lib, semigroupoids }: mkDerivation { pname = "nonemptymap"; version = "0.0.6.0"; @@ -23770,10 +28278,27 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/ChristopherDavenport/nonemptymap#readme"; description = "A NonEmptyMap Implementation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "not-gloss" = callPackage + ({ mkDerivation, base, binary, bmp, bytestring, GLUT, lib, OpenGL + , OpenGLRaw, spatial-math, time, vector, vector-binary-instances + }: + mkDerivation { + pname = "not-gloss"; + version = "0.7.7.0"; + sha256 = "4740d1ee04015bca98092f72c11414326d1bd08473aead61f6678773fb8b835f"; + libraryHaskellDepends = [ + base binary bmp bytestring GLUT OpenGL OpenGLRaw spatial-math time + vector vector-binary-instances + ]; + doHaddock = false; + doCheck = false; + description = "Painless 3D graphics, no affiliation with gloss"; + license = lib.licenses.bsd3; }) {}; "nowdoc" = callPackage - ({ mkDerivation, base, bytestring, stdenv, template-haskell }: + ({ mkDerivation, base, bytestring, lib, template-haskell }: mkDerivation { pname = "nowdoc"; version = "0.1.1.0"; @@ -23785,16 +28310,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/YoshikuniJujo/nowdoc#readme"; description = "Here document without variable expansion like PHP Nowdoc"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "nqe" = callPackage - ({ mkDerivation, base, conduit, containers, hashable, mtl, stdenv - , stm, unique, unliftio + ({ mkDerivation, base, conduit, containers, hashable, lib, mtl, stm + , unique, unliftio }: mkDerivation { pname = "nqe"; - version = "0.6.1"; - sha256 = "adf772bca05f8445e585537e3807df394a8d7c7e3a095fd532ee55cc60f30dd0"; + version = "0.6.3"; + sha256 = "f83c2523fef55ab4f6c37b8568e48883341c29c3378852cf91cd0cf9be63e971"; libraryHaskellDepends = [ base conduit containers hashable mtl stm unique unliftio ]; @@ -23802,23 +28327,85 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/xenog/nqe#readme"; description = "Concurrency library in the style of Erlang/OTP"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.mit; + }) {}; + "nri-env-parser" = callPackage + ({ mkDerivation, base, lib, modern-uri, network-uri, nri-prelude + , text + }: + mkDerivation { + pname = "nri-env-parser"; + version = "0.1.0.7"; + sha256 = "d3aa603c517ca1685f2b0c05fb59511167b84a958c27742e2080be8b6b3aa8d6"; + libraryHaskellDepends = [ + base modern-uri network-uri nri-prelude text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NoRedInk/haskell-libraries#readme"; + description = "Read environment variables as settings to build 12-factor apps"; + license = lib.licenses.bsd3; + }) {}; + "nri-observability" = callPackage + ({ mkDerivation, aeson, aeson-pretty, async, base, bugsnag-hs + , bytestring, conduit, directory, hostname, http-client + , http-client-tls, lib, nri-env-parser, nri-prelude, random + , safe-exceptions, stm, text, time, unordered-containers, uuid + }: + mkDerivation { + pname = "nri-observability"; + version = "0.1.1.1"; + sha256 = "a59551218e085d35ee5f16a5d27bb9643e086d6f509c8c08ef9a232a53997497"; + libraryHaskellDepends = [ + aeson aeson-pretty async base bugsnag-hs bytestring conduit + directory hostname http-client http-client-tls nri-env-parser + nri-prelude random safe-exceptions stm text time + unordered-containers uuid + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NoRedInk/haskell-libraries/tree/trunk/nri-observability#readme"; + description = "Report log spans collected by nri-prelude"; + license = lib.licenses.bsd3; + }) {}; + "nri-prelude" = callPackage + ({ mkDerivation, aeson, aeson-pretty, async, auto-update, base + , bytestring, containers, directory, exceptions, filepath, ghc + , hedgehog, junit-xml, lib, pretty-diff, pretty-show + , safe-coloured-text, safe-coloured-text-terminfo, safe-exceptions + , terminal-size, text, time, vector + }: + mkDerivation { + pname = "nri-prelude"; + version = "0.6.0.2"; + sha256 = "7c5e883586f312bc9c0010a4ddb08a4969b12f7af01cb3c0d88447c5b1c14b00"; + libraryHaskellDepends = [ + aeson aeson-pretty async auto-update base bytestring containers + directory exceptions filepath ghc hedgehog junit-xml pretty-diff + pretty-show safe-coloured-text safe-coloured-text-terminfo + safe-exceptions terminal-size text time vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NoRedInk/haskell-libraries/tree/trunk/nri-prelude#readme"; + description = "A Prelude inspired by the Elm programming language"; + license = lib.licenses.bsd3; }) {}; "nsis" = callPackage - ({ mkDerivation, base, stdenv, transformers, uniplate }: + ({ mkDerivation, base, lib, transformers, uniplate }: mkDerivation { pname = "nsis"; - version = "0.3.2"; - sha256 = "b9985b8d62569c192d89b20965eed2b98186a67148b667202823c6389b8f15ca"; + version = "0.3.3"; + sha256 = "bda68ef2893202432be55a7749269ec7660781cba5e2049f9ad474531e21778b"; libraryHaskellDepends = [ base transformers uniplate ]; doHaddock = false; doCheck = false; homepage = "https://github.com/ndmitchell/nsis#readme"; description = "DSL for producing Windows Installer using NSIS"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "numbers" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "numbers"; version = "3000.2.0.2"; @@ -23828,10 +28415,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/jwiegley/numbers#readme"; description = "Various number types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "numeric-extras" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "numeric-extras"; version = "0.1"; @@ -23841,17 +28428,29 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/numeric-extras"; description = "Useful tools from the C standard library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "numeric-limits" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "numeric-limits"; + version = "0.1.0.0"; + sha256 = "8b956ce9ecf6465e19068885b77da623a3af23fcabf1253718edd2427c055153"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + description = "Various floating point limit related constants"; + license = lib.licenses.bsd3; }) {}; "numeric-prelude" = callPackage - ({ mkDerivation, array, base, containers, deepseq, non-negative - , parsec, QuickCheck, random, semigroups, stdenv, storable-record - , utility-ht + ({ mkDerivation, array, base, containers, deepseq, lib + , non-negative, parsec, QuickCheck, random, semigroups + , storable-record, utility-ht }: mkDerivation { pname = "numeric-prelude"; - version = "0.4.3.1"; - sha256 = "c9e4b6f20c47ab38faea9a6a230a722f3b50462989d1b0ad1e7bfd1cb8f46114"; + version = "0.4.3.3"; + sha256 = "8d46031a17339057f447da971fc9dd9198020f79f5b7daa2c26c48f07e1f1f4f"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -23862,27 +28461,42 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Numeric_Prelude"; description = "An experimental alternative hierarchy of numeric type classes"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "numhask" = callPackage + ({ mkDerivation, base, bifunctors, lib, mmorph, protolude, random + , text, transformers + }: + mkDerivation { + pname = "numhask"; + version = "0.7.1.0"; + sha256 = "9d258bc7f73d2461c0477df2b8389cdb9765c8047fe35b8bbdb57e71feaa79e2"; + libraryHaskellDepends = [ + base bifunctors mmorph protolude random text transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/tonyday567/numhask#readme"; + description = "A numeric class hierarchy"; + license = lib.licenses.bsd3; }) {}; "numtype-dk" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "numtype-dk"; - version = "0.5.0.2"; - sha256 = "98787dc0dd1757e6ed9c37e7d735b448fb9a9281988d97625292c9d8e16a732b"; - revision = "1"; - editedCabalFile = "0892xm8vyyvl1glg4vniz8r5ydg1nz3zmbpgk5mxdih6wi6nmpy4"; + version = "0.5.0.3"; + sha256 = "f49351544dfc7920df46d24f3734f116f32ded5add7bb950b0e00e2a10c7bd9e"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/bjornbm/numtype-dk"; description = "Type-level integers, using TypeNats, Data Kinds, and Closed Type Families"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "nuxeo" = callPackage ({ mkDerivation, aeson, attoparsec, base, bytestring, conduit - , conduit-extra, http-conduit, http-types, optparse-applicative - , stdenv, text, time, url + , conduit-extra, http-conduit, http-types, lib + , optparse-applicative, text, time, url }: mkDerivation { pname = "nuxeo"; @@ -23898,31 +28512,100 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; homepage = "https://github.com/apeyroux/nuxeo#readme"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "nvvm" = callPackage - ({ mkDerivation, base, bytestring, c2hs, Cabal, cuda, directory - , filepath, stdenv, template-haskell + "nvim-hs" = callPackage + ({ mkDerivation, base, bytestring, cereal, cereal-conduit, conduit + , containers, data-default, deepseq, foreign-store, hslogger, lib + , megaparsec, messagepack, mtl, network, optparse-applicative, path + , path-io, prettyprinter, prettyprinter-ansi-terminal, resourcet + , stm, streaming-commons, template-haskell, text, time + , time-locale-compat, transformers, transformers-base + , typed-process, unliftio, unliftio-core, utf8-string, vector, void }: mkDerivation { - pname = "nvvm"; - version = "0.9.0.0"; - sha256 = "0bc2367b662ce414aa5f989cc1d1266daa0c552868cb374f304bfca29957ef01"; - setupHaskellDepends = [ - base Cabal cuda directory filepath template-haskell + pname = "nvim-hs"; + version = "2.1.0.4"; + sha256 = "2e8b51340e3c12a52067c9a57097ac2582755db689a01e36fdbb1b259b22e92d"; + revision = "2"; + editedCabalFile = "0bd90ndkk4lll4rvr87b9vil2h8jlchkh1fag1nrhj90lnczgpnl"; + libraryHaskellDepends = [ + base bytestring cereal cereal-conduit conduit containers + data-default deepseq foreign-store hslogger megaparsec messagepack + mtl network optparse-applicative path path-io prettyprinter + prettyprinter-ansi-terminal resourcet stm streaming-commons + template-haskell text time time-locale-compat transformers + transformers-base typed-process unliftio unliftio-core utf8-string + vector void ]; - libraryHaskellDepends = [ base bytestring cuda template-haskell ]; - libraryToolDepends = [ c2hs ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/tmcdonell/nvvm"; - description = "FFI bindings to NVVM"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/neovimhaskell/nvim-hs"; + description = "Haskell plugin backend for neovim"; + license = lib.licenses.asl20; + }) {}; + "nvim-hs-contrib" = callPackage + ({ mkDerivation, base, bytestring, data-default, directory + , filepath, lib, messagepack, mtl, nvim-hs, prettyprinter + , prettyprinter-ansi-terminal, text, time, utf8-string, yaml + }: + mkDerivation { + pname = "nvim-hs-contrib"; + version = "2.0.0.0"; + sha256 = "f9affcb5770d32479ac8cabb21397569d2d4619c9638db0c09ea2ea1e1de1c77"; + libraryHaskellDepends = [ + base bytestring data-default directory filepath messagepack mtl + nvim-hs prettyprinter prettyprinter-ansi-terminal text time + utf8-string yaml + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/neovimhaskell/nvim-hs-contrib"; + description = "Haskell plugin backend for neovim"; + license = lib.licenses.asl20; + }) {}; + "nvim-hs-ghcid" = callPackage + ({ mkDerivation, base, bytestring, containers, directory, filepath + , ghcid, lib, nvim-hs, nvim-hs-contrib, resourcet, transformers + , unliftio, yaml + }: + mkDerivation { + pname = "nvim-hs-ghcid"; + version = "2.0.0.0"; + sha256 = "8f43101968d8ac55fb35e3c53185d5d87a12c1b171cbaa03affef7feaa613c45"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base bytestring containers directory filepath ghcid nvim-hs + nvim-hs-contrib resourcet transformers unliftio yaml + ]; + executableHaskellDepends = [ base nvim-hs ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/saep/nvim-hs-ghcid"; + description = "Neovim plugin that runs ghcid to update the quickfix list"; + license = lib.licenses.asl20; + }) {}; + "o-clock" = callPackage + ({ mkDerivation, base, ghc-prim, lib }: + mkDerivation { + pname = "o-clock"; + version = "1.2.1"; + sha256 = "df248c02ba588f24636397c9be276c2c6d488d423823236ee0dadf289522c49f"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base ghc-prim ]; + executableHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/serokell/o-clock"; + description = "Type-safe time library"; + license = lib.licenses.mpl20; }) {}; "oauthenticated" = callPackage ({ mkDerivation, aeson, base, base64-bytestring, blaze-builder , bytestring, case-insensitive, cryptonite, exceptions, http-client - , http-types, memory, mtl, network, network-uri, stdenv, text, time + , http-types, lib, memory, mtl, network, network-uri, text, time , transformers }: mkDerivation { @@ -23938,42 +28621,24 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/tel/oauthenticated.git#readme"; description = "Simple OAuth for http-client"; - license = stdenv.lib.licenses.mit; - }) {}; - "oblivious-transfer" = callPackage - ({ mkDerivation, base, bytestring, cryptonite, memory, protolude - , random, stdenv - }: - mkDerivation { - pname = "oblivious-transfer"; - version = "0.1.0"; - sha256 = "5f1fcaf951a7828bbac3aef6ff8c540b187b0117f51b49428d018712eabd05cf"; - revision = "1"; - editedCabalFile = "1v9js45kc94zirg530d0f3r9wwsx60xnz7diqzvfxlbvw01649yk"; - libraryHaskellDepends = [ - base bytestring cryptonite memory protolude random - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/adjoint-io/oblivious-transfer#readme"; - description = "An implementation of the Oblivious Transfer protocol in Haskell"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.mit; }) {}; "odbc" = callPackage - ({ mkDerivation, async, base, bytestring, containers, deepseq - , formatting, optparse-applicative, parsec, semigroups, stdenv - , template-haskell, text, time, transformers, unixODBC + ({ mkDerivation, async, attoparsec, base, bytestring, containers + , deepseq, formatting, hashable, lib, optparse-applicative, parsec + , semigroups, template-haskell, text, time, transformers, unixODBC , unliftio-core }: mkDerivation { pname = "odbc"; - version = "0.2.2"; - sha256 = "659a124883696168daf3cd20403394616a56837c904810073183ce41769e7336"; + version = "0.2.5"; + sha256 = "506c53b0c208b95c59dcfb87be0e74a4abcc2fab595c191823721659b437ef94"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - async base bytestring containers deepseq formatting parsec - semigroups template-haskell text time transformers unliftio-core + async attoparsec base bytestring containers deepseq formatting + hashable parsec semigroups template-haskell text time transformers + unliftio-core ]; librarySystemDepends = [ unixODBC ]; executableHaskellDepends = [ @@ -23983,28 +28648,31 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/fpco/odbc"; description = "Haskell binding to the ODBC API, aimed at SQL Server driver"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) unixODBC;}; - "oeis" = callPackage - ({ mkDerivation, base, HTTP, network, network-uri, stdenv }: + "oeis2" = callPackage + ({ mkDerivation, aeson, base, containers, http-conduit, lens + , lens-aeson, lib, text, vector + }: mkDerivation { - pname = "oeis"; - version = "0.3.9"; - sha256 = "8a692c0b898f5d89e607f9593697a24827981a1cfee53045c192084015061b8e"; - revision = "1"; - editedCabalFile = "0rb6l3qblay8aiwaznp35gj7vwmhm87y57wvf3babwrh91s88jaj"; - libraryHaskellDepends = [ base HTTP network network-uri ]; + pname = "oeis2"; + version = "1.0.5"; + sha256 = "48d9cf4991be58b48aa43e676b40533861396a30bc3928e0d69c9aa88b97ccc6"; + libraryHaskellDepends = [ + aeson base containers http-conduit lens lens-aeson text vector + ]; doHaddock = false; doCheck = false; - description = "Interface to the Online Encyclopedia of Integer Sequences (OEIS)"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/23prime/oeis2#readme"; + description = "Interface for Online Encyclopedia of Integer Sequences (OEIS)"; + license = lib.licenses.bsd3; }) {}; "ofx" = callPackage - ({ mkDerivation, base, parsec, pretty, stdenv, time }: + ({ mkDerivation, base, lib, parsec, pretty, time }: mkDerivation { pname = "ofx"; - version = "0.4.2.0"; - sha256 = "0e22e2269f099603832f666814235051fadf92cbdec3dfacf7d1e8231ccd95f1"; + version = "0.4.4.0"; + sha256 = "798ceb6b799c22811ad40289f0eaa54037028cc637cbd0df35a770bcf2efecf2"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base parsec pretty time ]; @@ -24013,10 +28681,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.github.com/massysett/ofx"; description = "Parser for OFX data"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "old-locale" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "old-locale"; version = "1.0.0.7"; @@ -24027,10 +28695,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "locale library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "old-time" = callPackage - ({ mkDerivation, base, old-locale, stdenv }: + ({ mkDerivation, base, lib, old-locale }: mkDerivation { pname = "old-time"; version = "1.1.0.3"; @@ -24041,11 +28709,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Time library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "once" = callPackage - ({ mkDerivation, base, containers, hashable, stdenv - , template-haskell, unordered-containers + ({ mkDerivation, base, containers, hashable, lib, template-haskell + , unordered-containers }: mkDerivation { pname = "once"; @@ -24058,11 +28726,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://gitlab.com/kaction/haskell-once"; description = "memoization for IO actions and functions"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; }) {}; "one-liner" = callPackage - ({ mkDerivation, base, bifunctors, contravariant, ghc-prim - , profunctors, stdenv, tagged, transformers + ({ mkDerivation, base, bifunctors, contravariant, ghc-prim, lib + , profunctors, tagged, transformers }: mkDerivation { pname = "one-liner"; @@ -24078,23 +28746,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/sjoerdvisscher/one-liner"; description = "Constraint-based generics"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "one-liner-instances" = callPackage - ({ mkDerivation, base, one-liner, random, stdenv }: - mkDerivation { - pname = "one-liner-instances"; - version = "0.1.2.1"; - sha256 = "9384f47a3bdd5be17fa8ac3deca8e406794a1e9e140ec3b173ccd8d22c00c9bf"; - libraryHaskellDepends = [ base one-liner random ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/mstksg/one-liner-instances#readme"; - description = "Generics-based implementations for common typeclasses"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "oo-prototypes" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "oo-prototypes"; version = "0.1.0.0"; @@ -24104,20 +28759,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/yi-editor/oo-prototypes"; description = "Support for OO-like prototypes"; - license = stdenv.lib.licenses.gpl2; + license = lib.licenses.gpl2Only; }) {}; "opaleye" = callPackage ({ mkDerivation, aeson, base, base16-bytestring, bytestring - , case-insensitive, contravariant, postgresql-simple, pretty - , product-profunctors, profunctors, scientific, semigroups, stdenv - , text, time, time-locale-compat, transformers, uuid, void + , case-insensitive, contravariant, lib, postgresql-simple, pretty + , product-profunctors, profunctors, scientific, semigroups, text + , time, time-locale-compat, transformers, uuid, void }: mkDerivation { pname = "opaleye"; - version = "0.6.7003.1"; - sha256 = "5df737b19038efb076f5323044ff9c661fd77592c71756c10a811a51c2df44d2"; - revision = "1"; - editedCabalFile = "0nwyz9s81hfziwy7a18gpi0663xy6cfc6fl4vx8a1vkwdyfcjjli"; + version = "0.7.3.0"; + sha256 = "0809cf07d8aea4d8c855c11560360de6c298f69f6acde383b2f0101fd1844853"; libraryHaskellDepends = [ aeson base base16-bytestring bytestring case-insensitive contravariant postgresql-simple pretty product-profunctors @@ -24128,10 +28781,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/tomjaguarpaw/haskell-opaleye"; description = "An SQL-generating DSL targeting PostgreSQL"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "open-browser" = callPackage - ({ mkDerivation, base, process, stdenv }: + ({ mkDerivation, base, lib, process }: mkDerivation { pname = "open-browser"; version = "0.2.1.0"; @@ -24144,29 +28797,42 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/rightfold/open-browser"; description = "Open a web browser from Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "open-witness" = callPackage - ({ mkDerivation, base, constraints, hashable, random, stdenv - , template-haskell, transformers, witness + "openapi3" = callPackage + ({ mkDerivation, aeson, aeson-pretty, base, base-compat-batteries + , bytestring, Cabal, cabal-doctest, containers, cookie + , generics-sop, hashable, http-media, insert-ordered-containers + , lens, lib, mtl, network, optics-core, optics-th, QuickCheck + , scientific, template-haskell, text, time, transformers + , unordered-containers, uuid-types, vector }: mkDerivation { - pname = "open-witness"; - version = "0.4.0.1"; - sha256 = "0770500d6eeb301fc92d30bec2ccef55b05beb0200125fcbddb6b50836034111"; + pname = "openapi3"; + version = "3.1.0"; + sha256 = "1f05f43dfc267fea4d16cb8b493a51c7b9a83755bd366880ad85f7ee31292704"; + revision = "1"; + editedCabalFile = "1rbsfjwraizp0b6j2zaimz63b46k7d8abfxw7jyb7j1cv6jkcll1"; + isLibrary = true; + isExecutable = true; + setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ - base constraints hashable random template-haskell transformers - witness + aeson aeson-pretty base base-compat-batteries bytestring containers + cookie generics-sop hashable http-media insert-ordered-containers + lens mtl network optics-core optics-th QuickCheck scientific + template-haskell text time transformers unordered-containers + uuid-types vector ]; + executableHaskellDepends = [ aeson base lens text ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/AshleyYakeley/open-witness"; - description = "open witnesses"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/biocad/openapi3"; + description = "OpenAPI 3.0 data model"; + license = lib.licenses.bsd3; }) {}; "openexr-write" = callPackage ({ mkDerivation, base, binary, bytestring, data-binary-ieee754 - , deepseq, split, stdenv, vector, vector-split, zlib + , deepseq, lib, split, vector, vector-split, zlib }: mkDerivation { pname = "openexr-write"; @@ -24180,16 +28846,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "git://klacansky.com/openexr-write.git"; description = "Library for writing images in OpenEXR HDR file format"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "openpgp-asciiarmor" = callPackage ({ mkDerivation, attoparsec, base, base64-bytestring, binary - , bytestring, stdenv + , bytestring, lib }: mkDerivation { pname = "openpgp-asciiarmor"; - version = "0.1.1"; - sha256 = "b92f3f5316f18c9e30a95cd59888658384ddd20b628e4cd5fbb647177f52f607"; + version = "0.1.2"; + sha256 = "5342621eaed3cacada7304aae0e3537e8c18b34d35e1457b00f95c7c27a529bd"; libraryHaskellDepends = [ attoparsec base base64-bytestring binary bytestring ]; @@ -24197,10 +28863,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://floss.scru.org/openpgp-asciiarmor"; description = "OpenPGP (RFC4880) ASCII Armor codec"; - license = stdenv.lib.licenses.isc; + license = lib.licenses.mit; }) {}; "opensource" = callPackage - ({ mkDerivation, aeson, base, http-client, http-client-tls, stdenv + ({ mkDerivation, aeson, base, http-client, http-client-tls, lib , text, transformers }: mkDerivation { @@ -24214,28 +28880,111 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://api.opensource.org/"; description = "Haskell API Wrapper for the Open Source License API"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "openssl-streams" = callPackage - ({ mkDerivation, base, bytestring, HsOpenSSL, io-streams, network - , stdenv + ({ mkDerivation, base, bytestring, HsOpenSSL, io-streams, lib + , network }: mkDerivation { pname = "openssl-streams"; - version = "1.2.1.3"; - sha256 = "dc7170e835cf71a132903e2a6ccc976bd2984f9241ea2e4e99a9ece74f868f5f"; - revision = "2"; - editedCabalFile = "1004kgdryflpkp19dv4ikilhcn0xbfc5dsp6v3ib34580pcfj7wy"; + version = "1.2.3.0"; + sha256 = "55f20bd8970e5ce4d0ff16fae8c584c63e26e0990d27364340b997f5feb5f682"; libraryHaskellDepends = [ base bytestring HsOpenSSL io-streams network ]; doHaddock = false; doCheck = false; description = "OpenSSL network support for io-streams"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "opentelemetry" = callPackage + ({ mkDerivation, base, bytestring, exceptions, ghc-trace-events + , hashable, lib + }: + mkDerivation { + pname = "opentelemetry"; + version = "0.7.0"; + sha256 = "9bfa5ac667d4a80c2787d3ecdb3ff8b932672e7d6fcb5753024c363f868b6982"; + libraryHaskellDepends = [ + base bytestring exceptions ghc-trace-events hashable + ]; + doHaddock = false; + doCheck = false; + license = lib.licenses.asl20; + }) {}; + "opentelemetry-extra" = callPackage + ({ mkDerivation, async, base, binary, bytestring, clock, containers + , directory, exceptions, filepath, ghc-events, hashable, hashtables + , http-client, http-client-tls, http-types, hvega, jsonifier, lib + , opentelemetry, process, random, scientific, splitmix, stm, text + , text-show, typed-process, unordered-containers + }: + mkDerivation { + pname = "opentelemetry-extra"; + version = "0.7.0"; + sha256 = "623c85694b8a38fa75af808db61c52b354959fe5982c390f6455aa9b47859c86"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + async base binary bytestring clock containers directory exceptions + filepath ghc-events hashable http-client http-client-tls http-types + jsonifier opentelemetry random scientific splitmix stm text + text-show unordered-containers + ]; + executableHaskellDepends = [ + async base bytestring clock containers directory exceptions + filepath hashtables http-client http-client-tls hvega opentelemetry + process text typed-process + ]; + doHaddock = false; + doCheck = false; + license = lib.licenses.asl20; + }) {}; + "opentelemetry-lightstep" = callPackage + ({ mkDerivation, async, base, bytestring, clock, containers + , exceptions, filepath, ghc-events, http-client, http-client-tls + , http-types, lib, network, opentelemetry, opentelemetry-extra + , scientific, splitmix, stm, text, typed-process + , unordered-containers + }: + mkDerivation { + pname = "opentelemetry-lightstep"; + version = "0.7.0"; + sha256 = "88679ac89070cb86b3c88a8f486d52101e7bbf8b53fc1b03815256cee17fa6f9"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + async base bytestring exceptions http-client http-client-tls + http-types network opentelemetry opentelemetry-extra scientific stm + text unordered-containers + ]; + executableHaskellDepends = [ + async base bytestring clock containers exceptions filepath + ghc-events http-client http-types opentelemetry opentelemetry-extra + splitmix text typed-process unordered-containers + ]; + doHaddock = false; + doCheck = false; + license = lib.licenses.asl20; + }) {}; + "opentelemetry-wai" = callPackage + ({ mkDerivation, base, bytestring, http-types, lib, opentelemetry + , text, wai + }: + mkDerivation { + pname = "opentelemetry-wai"; + version = "0.7.0"; + sha256 = "353488b70d6fcb69ce75515b9062a93a11a389fe9573a6d5137d2702dd44b026"; + libraryHaskellDepends = [ + base bytestring http-types opentelemetry text wai + ]; + doHaddock = false; + doCheck = false; + license = lib.licenses.asl20; }) {}; "operational" = callPackage - ({ mkDerivation, base, mtl, random, stdenv }: + ({ mkDerivation, base, lib, mtl, random }: mkDerivation { pname = "operational"; version = "0.2.3.5"; @@ -24248,10 +28997,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://wiki.haskell.org/Operational"; description = "Implementation of difficult monads made easy with operational semantics"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "operational-class" = callPackage - ({ mkDerivation, base, operational, stdenv, transformers }: + ({ mkDerivation, base, lib, operational, transformers }: mkDerivation { pname = "operational-class"; version = "0.3.0.0"; @@ -24261,66 +29010,133 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/srijs/haskell-operational-class"; description = "MonadProgram typeclass for the operational package"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "opml-conduit" = callPackage - ({ mkDerivation, base, case-insensitive, conduit - , conduit-combinators, containers, lens-simple, mono-traversable - , monoid-subclasses, safe-exceptions, semigroups, stdenv, text - , time, timerep, uri-bytestring, xml-conduit, xml-types + "optics" = callPackage + ({ mkDerivation, array, base, containers, lib, mtl, optics-core + , optics-extra, optics-th, transformers }: mkDerivation { - pname = "opml-conduit"; - version = "0.6.0.4"; - sha256 = "480b557690aab79e3761ad7f1ba1d44873c3d395d2b27f2d133372a01c535d1d"; - revision = "1"; - editedCabalFile = "160sazqsrmm2755642c5y5i38miiglqb66cy5k0hy4k2jkdmjfbi"; - enableSeparateDataOutput = true; + pname = "optics"; + version = "0.3"; + sha256 = "0260b37f8d9975a25a3ce12777c3686e662a7429bcc8648d2ac52c18937c136c"; libraryHaskellDepends = [ - base case-insensitive conduit conduit-combinators containers - lens-simple mono-traversable monoid-subclasses safe-exceptions - semigroups text time timerep uri-bytestring xml-conduit xml-types + array base containers mtl optics-core optics-extra optics-th + transformers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/k0ral/opml-conduit"; - description = "Streaming parser/renderer for the OPML 2.0 format."; - license = stdenv.lib.licenses.publicDomain; + description = "Optics as an abstract interface"; + license = lib.licenses.bsd3; }) {}; - "optional-args" = callPackage - ({ mkDerivation, base, stdenv }: + "optics-core" = callPackage + ({ mkDerivation, array, base, containers, indexed-profunctors, lib + , transformers + }: mkDerivation { - pname = "optional-args"; - version = "1.0.2"; - sha256 = "2e3454ad77cba80b15c02dbe1915889fafa81a22deb7fe5e7e01b0dd8d85b0e4"; - libraryHaskellDepends = [ base ]; + pname = "optics-core"; + version = "0.3.0.1"; + sha256 = "30115bd9b2adc4e7076ffa881e2fb60d7e45b25641e1e7dd80580e59b3cce107"; + libraryHaskellDepends = [ + array base containers indexed-profunctors transformers + ]; doHaddock = false; doCheck = false; - description = "Optional function arguments"; - license = stdenv.lib.licenses.bsd3; + description = "Optics as an abstract interface: core definitions"; + license = lib.licenses.bsd3; }) {}; - "options" = callPackage - ({ mkDerivation, base, containers, monads-tf, stdenv, transformers + "optics-extra" = callPackage + ({ mkDerivation, array, base, bytestring, containers, hashable + , indexed-profunctors, lib, mtl, optics-core, text, transformers + , unordered-containers, vector }: mkDerivation { - pname = "options"; - version = "1.2.1.1"; - sha256 = "283eea9ae2c539830c6c65f5c03fb00626cfd1274da0526c285c146fc3065a62"; - libraryHaskellDepends = [ base containers monads-tf transformers ]; - doHaddock = false; - doCheck = false; + pname = "optics-extra"; + version = "0.3"; + sha256 = "a4d6155814111a5c6ce89640915ba5987296fec3cecc766ece3d4112abfd7697"; + revision = "2"; + editedCabalFile = "13x3mavf2bi25ns03b93b5ghhkyivwxf6idn0wqs9fdiih1xvhv8"; + libraryHaskellDepends = [ + array base bytestring containers hashable indexed-profunctors mtl + optics-core text transformers unordered-containers vector + ]; + doHaddock = false; + doCheck = false; + description = "Extra utilities and instances for optics-core"; + license = lib.licenses.bsd3; + }) {}; + "optics-th" = callPackage + ({ mkDerivation, base, containers, lib, mtl, optics-core + , template-haskell, th-abstraction, transformers + }: + mkDerivation { + pname = "optics-th"; + version = "0.3.0.2"; + sha256 = "80f0cbb1cda044631ef421a0112e2d9a9868c22d95e845d97902d0fbf822b1d7"; + revision = "1"; + editedCabalFile = "0kr473b0ibxi99fqcg86xl2pq8l2m1yra548v9p278rpqa8g51p7"; + libraryHaskellDepends = [ + base containers mtl optics-core template-haskell th-abstraction + transformers + ]; + doHaddock = false; + doCheck = false; + description = "Optics construction using TemplateHaskell"; + license = lib.licenses.bsd3; + }) {}; + "optics-vl" = callPackage + ({ mkDerivation, base, indexed-profunctors, lib, optics-core + , profunctors + }: + mkDerivation { + pname = "optics-vl"; + version = "0.2.1"; + sha256 = "bb946de3099304986a7bdc8f8a06917e7aeb9ff69f0762327e350acbc05433f7"; + revision = "1"; + editedCabalFile = "0ba6fk4djs3gm305km8c870h76mg8q1dyy899cll0scc6l9jgbyc"; + libraryHaskellDepends = [ + base indexed-profunctors optics-core profunctors + ]; + doHaddock = false; + doCheck = false; + description = "Utilities for compatibility with van Laarhoven optics"; + license = lib.licenses.bsd3; + }) {}; + "optional-args" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "optional-args"; + version = "1.0.2"; + sha256 = "2e3454ad77cba80b15c02dbe1915889fafa81a22deb7fe5e7e01b0dd8d85b0e4"; + revision = "1"; + editedCabalFile = "0fda6mhm44qpbc9hfkf6jxnm3a7qszabywsmxa2iw0dz734a9xl3"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + description = "Optional function arguments"; + license = lib.licenses.bsd3; + }) {}; + "options" = callPackage + ({ mkDerivation, base, containers, lib, monads-tf, transformers }: + mkDerivation { + pname = "options"; + version = "1.2.1.1"; + sha256 = "283eea9ae2c539830c6c65f5c03fb00626cfd1274da0526c285c146fc3065a62"; + libraryHaskellDepends = [ base containers monads-tf transformers ]; + doHaddock = false; + doCheck = false; homepage = "https://john-millikin.com/software/haskell-options/"; description = "A powerful and easy-to-use command-line option parser"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "optparse-applicative" = callPackage - ({ mkDerivation, ansi-wl-pprint, base, process, stdenv - , transformers, transformers-compat + ({ mkDerivation, ansi-wl-pprint, base, lib, process, transformers + , transformers-compat }: mkDerivation { pname = "optparse-applicative"; - version = "0.14.3.0"; - sha256 = "72476302fe555a508917b2d7d6121c7b58ea5434cdc08aeb5d4b652e8f0e7663"; + version = "0.16.1.0"; + sha256 = "6205278362f333c52256b9dd3edf5f8fe0f84f00cb9ee000291089f6eaccd69a"; libraryHaskellDepends = [ ansi-wl-pprint base process transformers transformers-compat ]; @@ -24328,47 +29144,49 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/pcapriotti/optparse-applicative"; description = "Utilities and combinators for parsing command line options"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "optparse-generic" = callPackage - ({ mkDerivation, base, bytestring, Only, optparse-applicative - , semigroups, stdenv, system-filepath, text, time, transformers - , void + ({ mkDerivation, base, bytestring, lib, Only, optparse-applicative + , system-filepath, text, time, transformers, void }: mkDerivation { pname = "optparse-generic"; - version = "1.3.0"; - sha256 = "80929958606e4a73672b570ba1a23493fbf46268666d14ab5af53623301c398f"; + version = "1.4.4"; + sha256 = "e44853c0a3def2556cec31337db411d6404d7f81d505662f8ebac68e119bc077"; + revision = "2"; + editedCabalFile = "172x8990wx4jhyb7yp9k18nd6q4sis8km09x2afr238siqviclrc"; libraryHaskellDepends = [ - base bytestring Only optparse-applicative semigroups - system-filepath text time transformers void + base bytestring Only optparse-applicative system-filepath text time + transformers void ]; doHaddock = false; doCheck = false; description = "Auto-generate a command-line parser for your datatype"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "optparse-simple" = callPackage - ({ mkDerivation, base, githash, optparse-applicative, stdenv - , template-haskell, transformers + ({ mkDerivation, base, githash, lib, optparse-applicative + , template-haskell, th-compat, transformers }: mkDerivation { pname = "optparse-simple"; - version = "0.1.1"; - sha256 = "03d31baa535cecba5761e66adcc9514a6d93875eb956b8e4646c0f62dbe055a4"; + version = "0.1.1.4"; + sha256 = "1d01d85c477b42e5a6ab6595def68c800d5bccbeff5a06ccf63c6a86967a7878"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - base githash optparse-applicative template-haskell transformers + base githash optparse-applicative template-haskell th-compat + transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/fpco/optparse-simple#readme"; description = "Simple interface to optparse-applicative"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "optparse-text" = callPackage - ({ mkDerivation, base, optparse-applicative, stdenv, text }: + ({ mkDerivation, base, lib, optparse-applicative, text }: mkDerivation { pname = "optparse-text"; version = "0.1.1.0"; @@ -24378,10 +29196,49 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/passy/optparse-text#readme"; description = "Data.Text helpers for optparse-applicative"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "ordered-containers" = callPackage + ({ mkDerivation, base, containers, lib }: + mkDerivation { + pname = "ordered-containers"; + version = "0.2.2"; + sha256 = "c75ac7330e70cd5d6ac0062b68033779cf15cd986d4ca20f838e016d466d22c9"; + libraryHaskellDepends = [ base containers ]; + doHaddock = false; + doCheck = false; + description = "Set- and Map-like types that remember the order elements were inserted"; + license = lib.licenses.bsd3; + }) {}; + "ormolu" = callPackage + ({ mkDerivation, ansi-terminal, base, bytestring, containers, Diff + , dlist, exceptions, filepath, ghc-lib-parser, gitrev, lib, mtl + , optparse-applicative, syb, text + }: + mkDerivation { + pname = "ormolu"; + version = "0.1.4.1"; + sha256 = "3ab5bb2e6a9de89cdedd9c2adfab45a0b722d7735225bff83c305959e37f55a9"; + revision = "1"; + editedCabalFile = "1fi8fxyhw9jdwhsbmrikjqd461wrz7h4kdszrahlvdjfdsn4wh7d"; + isLibrary = true; + isExecutable = true; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + ansi-terminal base bytestring containers Diff dlist exceptions + ghc-lib-parser mtl syb text + ]; + executableHaskellDepends = [ + base filepath ghc-lib-parser gitrev optparse-applicative text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/tweag/ormolu"; + description = "A formatter for Haskell source code"; + license = lib.licenses.bsd3; }) {}; "overhang" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "overhang"; version = "1.0.0"; @@ -24391,24 +29248,50 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/jship/overhang#readme"; description = "Hang loose with your lambdas!"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "packcheck" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "packcheck"; - version = "0.4.1"; - sha256 = "be65a4a7c7d6823610966e59e8e12147e2a55e577b2cebfddaaebd708e96da14"; + version = "0.5.1"; + sha256 = "79e7cfc63e70b627be8c084b3223fdd261a5d79ddd797d5ecc2cee635e651c16"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/harendra-kumar/packcheck"; + homepage = "https://github.com/composewell/packcheck"; description = "Universal build and CI testing for Haskell packages"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "packdeps" = callPackage + ({ mkDerivation, base, bytestring, Cabal, containers, directory + , filepath, lib, optparse-applicative, process, semigroups, split + , tar, text, time + }: + mkDerivation { + pname = "packdeps"; + version = "0.6.0.0"; + sha256 = "bf0120b3313ec85ad9559745eed4ca9d744758bbd3f0fbbef4464bfaa1d61982"; + revision = "1"; + editedCabalFile = "02akm54nkfw8jzc8b1b49pkbn4h73s5f968gyafmnq9jla0rcsjg"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base bytestring Cabal containers directory filepath split tar text + time + ]; + executableHaskellDepends = [ + base Cabal containers optparse-applicative process semigroups text + ]; + doHaddock = false; + doCheck = false; + homepage = "http://packdeps.haskellers.com/"; + description = "Check your cabal packages for lagging dependencies"; + license = lib.licenses.bsd3; }) {}; "pager" = callPackage ({ mkDerivation, base, bytestring, conduit, conduit-extra - , directory, process, resourcet, safe, stdenv, terminfo, text + , directory, lib, process, resourcet, safe, terminfo, text , transformers, unix }: mkDerivation { @@ -24427,192 +29310,226 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/pharpend/pager"; description = "Open up a pager, like 'less' or 'more'"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; }) {}; "pagination" = callPackage - ({ mkDerivation, base, deepseq, exceptions, stdenv }: + ({ mkDerivation, base, deepseq, exceptions, lib }: mkDerivation { pname = "pagination"; - version = "0.2.1"; - sha256 = "88dcbae69e830adac0943f24f8ae6915f9e4ba684531a76bce936767cbeb203d"; - revision = "2"; - editedCabalFile = "0wvwi3hymp2vhhpzpycdc65zbsqmi2h0c6r0nf8p5nkgsk4pm1k2"; + version = "0.2.2"; + sha256 = "2f5a5f357b59726eb7f4de57b75e342d5cf35502dff2ef36716266ad4b69b94c"; libraryHaskellDepends = [ base deepseq exceptions ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mrkkrp/pagination"; description = "Framework-agnostic pagination boilerplate"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "pairing" = callPackage - ({ mkDerivation, base, bytestring, cryptonite, memory, protolude - , QuickCheck, random, stdenv, wl-pprint-text + "pagure-cli" = callPackage + ({ mkDerivation, aeson, base, bytestring, filepath, http-conduit + , lens, lens-aeson, lib, optparse-applicative, simple-cmd-args + , text }: mkDerivation { - pname = "pairing"; - version = "0.1.4"; - sha256 = "cc8c5a39e27b8fb17b2107f81e2777958e9c5f1d1e0a9a29267e89b1b0e2e18d"; - libraryHaskellDepends = [ - base bytestring cryptonite memory protolude QuickCheck random - wl-pprint-text + pname = "pagure-cli"; + version = "0.2"; + sha256 = "f978e8458feeb575084662ed7f18ab28670c2ab6966bb56c68bd743e87a88142"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ + aeson base bytestring filepath http-conduit lens lens-aeson + optparse-applicative simple-cmd-args text ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/adjoint-io/pairing#readme"; - description = "Optimal ate pairing over Barreto-Naehrig curves"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/juhp/pagure-cli"; + description = "Pagure client"; + license = lib.licenses.gpl2Only; }) {}; "pandoc" = callPackage - ({ mkDerivation, aeson, aeson-pretty, base, base64-bytestring - , binary, blaze-html, blaze-markup, bytestring, Cabal - , case-insensitive, cmark-gfm, containers, data-default, deepseq - , directory, doctemplates, exceptions, filepath, Glob - , haddock-library, hslua, hslua-module-text, HsYAML, HTTP - , http-client, http-client-tls, http-types, JuicyPixels, mtl - , network, network-uri, pandoc-types, parsec, process, random, safe - , SHA, skylighting, split, stdenv, syb, tagsoup, temporary, texmath - , text, time, unicode-transforms, unix, unordered-containers - , vector, xml, zip-archive, zlib + ({ mkDerivation, aeson, aeson-pretty, array, attoparsec, base + , base64-bytestring, binary, blaze-html, blaze-markup, bytestring + , case-insensitive, citeproc, commonmark, commonmark-extensions + , commonmark-pandoc, connection, containers, data-default, deepseq + , directory, doclayout, doctemplates, emojis, exceptions + , file-embed, filepath, Glob, haddock-library, hslua + , hslua-module-path, hslua-module-system, hslua-module-text, HsYAML + , HTTP, http-client, http-client-tls, http-types, ipynb + , jira-wiki-markup, JuicyPixels, lib, mtl, network, network-uri + , pandoc-types, parsec, process, random, safe, scientific, SHA + , skylighting, skylighting-core, split, syb, tagsoup, temporary + , texmath, text, text-conversions, time, unicode-collation + , unicode-transforms, unix, unordered-containers, xml, xml-conduit + , zip-archive, zlib }: mkDerivation { pname = "pandoc"; - version = "2.5"; - sha256 = "d57dc5db78a0a304de70436fe59a7599ab0c6d0fb2ab6704eeae498a4536222e"; - revision = "2"; - editedCabalFile = "1z44hcwqqmkmhfak7svrrf950amf008gzhnlxkhwdyjpnpqp21sm"; + version = "2.14.0.3"; + sha256 = "82e3f55bff3059bf30cf532e93d9876c9e3599aa4eafae9c907fe75a4430eddd"; configureFlags = [ "-fhttps" "-f-trypandoc" ]; isLibrary = true; isExecutable = true; enableSeparateDataOutput = true; - setupHaskellDepends = [ base Cabal ]; libraryHaskellDepends = [ - aeson aeson-pretty base base64-bytestring binary blaze-html - blaze-markup bytestring case-insensitive cmark-gfm containers - data-default deepseq directory doctemplates exceptions filepath - Glob haddock-library hslua hslua-module-text HsYAML HTTP - http-client http-client-tls http-types JuicyPixels mtl network - network-uri pandoc-types parsec process random safe SHA skylighting - split syb tagsoup temporary texmath text time unicode-transforms - unix unordered-containers vector xml zip-archive zlib + aeson aeson-pretty array attoparsec base base64-bytestring binary + blaze-html blaze-markup bytestring case-insensitive citeproc + commonmark commonmark-extensions commonmark-pandoc connection + containers data-default deepseq directory doclayout doctemplates + emojis exceptions file-embed filepath Glob haddock-library hslua + hslua-module-path hslua-module-system hslua-module-text HsYAML HTTP + http-client http-client-tls http-types ipynb jira-wiki-markup + JuicyPixels mtl network network-uri pandoc-types parsec process + random safe scientific SHA skylighting skylighting-core split syb + tagsoup temporary texmath text text-conversions time + unicode-collation unicode-transforms unix unordered-containers xml + xml-conduit zip-archive zlib ]; executableHaskellDepends = [ base ]; doHaddock = false; doCheck = false; + postInstall = '' + mkdir -p $out/share/man/man1 + mv "man/"*.1 $out/share/man/man1/ + ''; homepage = "https://pandoc.org"; description = "Conversion between markup formats"; - license = stdenv.lib.licenses.gpl2; + license = lib.licenses.gpl2Plus; }) {}; - "pandoc-citeproc" = callPackage - ({ mkDerivation, aeson, aeson-pretty, attoparsec, base, bytestring - , Cabal, containers, data-default, directory, filepath, hs-bibutils - , mtl, old-locale, pandoc, pandoc-types, parsec, rfc5051, setenv - , split, stdenv, syb, tagsoup, text, time, unordered-containers - , vector, xml-conduit, yaml + "pandoc-dhall-decoder" = callPackage + ({ mkDerivation, base, dhall, either, lib, pandoc, text }: + mkDerivation { + pname = "pandoc-dhall-decoder"; + version = "0.1.0.1"; + sha256 = "40a08677750b93c2a8475960c02645784f79d829ac78109ef6908ce01dea4e0c"; + libraryHaskellDepends = [ base dhall either pandoc text ]; + doHaddock = false; + doCheck = false; + description = "Decodes pandoc to dhall"; + license = lib.licenses.bsd3; + }) {}; + "pandoc-plot" = callPackage + ({ mkDerivation, base, bytestring, containers, data-default + , directory, filepath, gitrev, hashable, lib, lifted-async + , lifted-base, mtl, optparse-applicative, pandoc, pandoc-types + , shakespeare, tagsoup, template-haskell, text, typed-process, unix + , yaml }: mkDerivation { - pname = "pandoc-citeproc"; - version = "0.15.0.1"; - sha256 = "29db5f2aad3225859727271855461724574f3695ab3856ceac33b24a55ae92f8"; + pname = "pandoc-plot"; + version = "1.2.3"; + sha256 = "e83e6cbb2dd79d23fc714729406696630aba78937493e95a758389395ff5fd64"; isLibrary = true; isExecutable = true; - enableSeparateDataOutput = true; - setupHaskellDepends = [ base Cabal ]; libraryHaskellDepends = [ - aeson base bytestring containers data-default directory filepath - hs-bibutils mtl old-locale pandoc pandoc-types parsec rfc5051 - setenv split syb tagsoup text time unordered-containers vector - xml-conduit yaml + base bytestring containers data-default directory filepath hashable + lifted-async lifted-base mtl pandoc pandoc-types shakespeare + tagsoup template-haskell text typed-process unix yaml ]; executableHaskellDepends = [ - aeson aeson-pretty attoparsec base bytestring filepath pandoc - pandoc-types syb text yaml + base containers directory filepath gitrev optparse-applicative + pandoc pandoc-types template-haskell text typed-process ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/jgm/pandoc-citeproc"; - description = "Supports using pandoc with citeproc"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/LaurentRDC/pandoc-plot#readme"; + description = "A Pandoc filter to include figures generated from code blocks using your plotting toolkit of choice"; + license = lib.licenses.gpl2Plus; }) {}; - "pandoc-pyplot" = callPackage - ({ mkDerivation, base, containers, directory, filepath - , pandoc-types, stdenv, temporary, typed-process - }: + "pandoc-throw" = callPackage + ({ mkDerivation, base, exceptions, lib, pandoc }: mkDerivation { - pname = "pandoc-pyplot"; - version = "1.0.3.0"; - sha256 = "e24d112d80ecc46915244d4a31fe2d62e06faa29c8082c380f3a1d1904e7f75b"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - base containers directory filepath pandoc-types temporary - typed-process - ]; - executableHaskellDepends = [ base pandoc-types ]; + pname = "pandoc-throw"; + version = "0.1.0.0"; + sha256 = "a84ea9857fd8daf0d683b62c388bf24e24f598b63dbf370a2ba63e2d763de3c4"; + libraryHaskellDepends = [ base exceptions pandoc ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/LaurentRDC/pandoc-pyplot#readme"; - description = "A Pandoc filter for including figures generated from Matplotlib"; - license = stdenv.lib.licenses.mit; + description = "MonadThrow behaviour for Pandoc"; + license = lib.licenses.mit; }) {}; "pandoc-types" = callPackage ({ mkDerivation, aeson, base, bytestring, containers, deepseq - , ghc-prim, QuickCheck, stdenv, syb, transformers + , ghc-prim, lib, QuickCheck, syb, text, transformers }: mkDerivation { pname = "pandoc-types"; - version = "1.17.5.4"; - sha256 = "32aca86c510bd23c6bd54ce1a37ca005f4b84f077ab8e835a522833cf5179327"; + version = "1.22"; + sha256 = "380175de810d6715d021335f136cbe00c752342e86c92cf81da1a4c27db2254f"; libraryHaskellDepends = [ aeson base bytestring containers deepseq ghc-prim QuickCheck syb - transformers + text transformers ]; doHaddock = false; doCheck = false; - homepage = "http://johnmacfarlane.net/pandoc"; + homepage = "https://pandoc.org/"; description = "Types for representing a structured document"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "parallel" = callPackage - ({ mkDerivation, array, base, containers, deepseq, ghc-prim, stdenv + "pantry" = callPackage + ({ mkDerivation, aeson, ansi-terminal, base, bytestring, Cabal + , casa-client, casa-types, conduit, conduit-extra, containers + , cryptonite, cryptonite-conduit, digest, filelock + , generic-deriving, hackage-security, hpack, http-client + , http-client-tls, http-conduit, http-download, http-types, lib + , memory, mtl, network-uri, path, path-io, persistent + , persistent-sqlite, persistent-template, primitive, resourcet, rio + , rio-orphans, rio-prettyprint, tar-conduit, text, text-metrics + , time, transformers, unix-compat, unliftio, unordered-containers + , vector, yaml, zip-archive }: + mkDerivation { + pname = "pantry"; + version = "0.5.2.3"; + sha256 = "2f89669ec1daebd7e3b22dddf4d86988da5ddc8605938079d2e0b681f473299f"; + libraryHaskellDepends = [ + aeson ansi-terminal base bytestring Cabal casa-client casa-types + conduit conduit-extra containers cryptonite cryptonite-conduit + digest filelock generic-deriving hackage-security hpack http-client + http-client-tls http-conduit http-download http-types memory mtl + network-uri path path-io persistent persistent-sqlite + persistent-template primitive resourcet rio rio-orphans + rio-prettyprint tar-conduit text text-metrics time transformers + unix-compat unliftio unordered-containers vector yaml zip-archive + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/commercialhaskell/pantry#readme"; + description = "Content addressable Haskell package management"; + license = lib.licenses.bsd3; + }) {}; + "parallel" = callPackage + ({ mkDerivation, array, base, containers, deepseq, ghc-prim, lib }: mkDerivation { pname = "parallel"; version = "3.2.2.0"; sha256 = "170453a71a2a8b31cca63125533f7771d7debeb639700bdabdd779c34d8a6ef6"; + revision = "3"; + editedCabalFile = "1lv3y3zrdfc09nsiqxg7mzcahgnqi6z9caspd4lvifhhfrqy2722"; libraryHaskellDepends = [ array base containers deepseq ghc-prim ]; doHaddock = false; doCheck = false; description = "Parallel programming library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "parallel-io" = callPackage - ({ mkDerivation, base, containers, extensible-exceptions, random - , stdenv - }: + "parameterized" = callPackage + ({ mkDerivation, base, data-diverse, lib, transformers }: mkDerivation { - pname = "parallel-io"; - version = "0.3.3"; - sha256 = "3a14c02b9b8b7c72577eb90a8dd72de75d99192def87d7aa79545ee4d6e80645"; - revision = "2"; - editedCabalFile = "0mggzni708nzxlsjbibdzf03s3b5lnqj2zi1hnbh1rd4j4jr07ym"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - base containers extensible-exceptions random - ]; + pname = "parameterized"; + version = "0.5.0.0"; + sha256 = "d76bc473c671f3c448cc0683ec44f4495cb21938ab27a8e2c35a94683a373346"; + libraryHaskellDepends = [ base data-diverse transformers ]; doHaddock = false; doCheck = false; - homepage = "http://batterseapower.github.com/parallel-io"; - description = "Combinators for executing IO actions in parallel on a thread pool"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/louispan/parameterized#readme"; + description = "Parameterized/indexed monoids and monads using only a single parameter type variable"; + license = lib.licenses.bsd3; }) {}; "paripari" = callPackage - ({ mkDerivation, base, bytestring, parser-combinators, stdenv, text - }: + ({ mkDerivation, base, bytestring, lib, parser-combinators, text }: mkDerivation { pname = "paripari"; - version = "0.6.0.0"; - sha256 = "2114cfd4f91c5f58f52b0e350927276fe8e5ba291db7ae77859d045d8bbf0498"; + version = "0.7.0.0"; + sha256 = "256f4bfcc81cadef0f9ecd23c8bc10da020129f0aed0c0956699e1fabe7dbb30"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -24625,14 +29542,14 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/minad/paripari#readme"; description = "Parser combinators with fast-path and slower fallback for error reporting"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "parseargs" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "parseargs"; - version = "0.2.0.8"; - sha256 = "7b789204c15d0c478db3d133f349a6970b5509fc6af655faedc03c7426dcf7d6"; + version = "0.2.0.9"; + sha256 = "3c469ddcee3a63ef790d88f676dcf99b9d90b8815112f18c17febafc9e8025a9"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base containers ]; @@ -24640,26 +29557,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; homepage = "http://github.com/BartMassey/parseargs"; - description = "Full-featured command-line argument parsing library"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "parsec" = callPackage - ({ mkDerivation, base, bytestring, mtl, stdenv, text }: - mkDerivation { - pname = "parsec"; - version = "3.1.13.0"; - sha256 = "7861ae437a6177ee7c08899432fd8c062e7c110361da48a9f9e88263fd4d80f1"; - revision = "2"; - editedCabalFile = "032sizm03m2vdqshkv4sdviyka05gqf8gs6r4hqf9did177i0qnm"; - libraryHaskellDepends = [ base bytestring mtl text ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/hvr/parsec"; - description = "Monadic parser combinators"; - license = stdenv.lib.licenses.bsd3; + description = "Parse command-line arguments"; + license = lib.licenses.bsd3; }) {}; "parsec-class" = callPackage - ({ mkDerivation, base, parsec, stdenv }: + ({ mkDerivation, base, lib, parsec }: mkDerivation { pname = "parsec-class"; version = "1.0.0.0"; @@ -24669,10 +29571,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/peti/parsec-class"; description = "Class of types that can be constructed from their text representation"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "parsec-numbers" = callPackage - ({ mkDerivation, base, parsec, stdenv }: + ({ mkDerivation, base, lib, parsec }: mkDerivation { pname = "parsec-numbers"; version = "0.1.0"; @@ -24681,10 +29583,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Utilities for parsing numbers from strings"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "parsec-numeric" = callPackage - ({ mkDerivation, base, parsec, stdenv }: + ({ mkDerivation, base, lib, parsec }: mkDerivation { pname = "parsec-numeric"; version = "0.1.0.0"; @@ -24695,30 +29597,48 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; homepage = "https://github.com/AndrewRademacher/parsec-numeric"; description = "Parsec combinators for parsing Haskell numeric types"; license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; + hydraPlatforms = lib.platforms.none; }) {}; "parser-combinators" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "parser-combinators"; - version = "1.0.1"; - sha256 = "edf5ab8fa69a04334baa8707252036563a8339a96a86956c90febe93830cea32"; + version = "1.2.1"; + sha256 = "03162e40cde50253529fa452165b681d5064d03ad07992800702156adfb6254d"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mrkkrp/parser-combinators"; description = "Lightweight package providing commonly useful parser combinators"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "parser-combinators-tests" = callPackage + ({ mkDerivation, lib }: + mkDerivation { + pname = "parser-combinators-tests"; + version = "1.2.1"; + sha256 = "a86ba485c7ba19013bddb5f1ad87e38d4e04ebaea303637c6c414d79a58ac447"; + revision = "2"; + editedCabalFile = "07j1y8iqljaqyqhy37db2xvs7y9z91r3sndzmz4gga7w2jpkhq2b"; + isLibrary = false; + isExecutable = false; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/mrkkrp/parser-combinators"; + description = "Test suite of parser-combinators"; + license = lib.licenses.bsd3; }) {}; "parsers" = callPackage ({ mkDerivation, attoparsec, base, base-orphans, binary, charset - , containers, mtl, parsec, scientific, semigroups, stdenv, text + , containers, lib, mtl, parsec, scientific, semigroups, text , transformers, unordered-containers }: mkDerivation { pname = "parsers"; - version = "0.12.9"; - sha256 = "81e52fc9d71b587a8034015344e9162c59975750094f930a47933e5603d305e4"; + version = "0.12.10"; + sha256 = "17b91f1318ca54679395b382a056df633fdb44fbb962eca66b1787f957af1a6c"; + revision = "1"; + editedCabalFile = "15pcq6iz3mbcwlknzxxfgd1myhyl41fs4j3m80pkif6dm5g18rv3"; libraryHaskellDepends = [ attoparsec base base-orphans binary charset containers mtl parsec scientific semigroups text transformers unordered-containers @@ -24727,10 +29647,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/parsers/"; description = "Parsing combinators"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "partial-handler" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "partial-handler"; version = "1.0.3"; @@ -24740,10 +29660,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/nikita-volkov/partial-handler"; description = "A composable exception handler"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "partial-isomorphisms" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { pname = "partial-isomorphisms"; version = "0.2.2.1"; @@ -24753,41 +29673,123 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.informatik.uni-marburg.de/~rendel/unparse"; description = "Partial isomorphisms"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "partial-semigroup" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "partial-semigroup"; - version = "0.5.0.0"; - sha256 = "15f7e8941d848a85a0b6fef85f27d2414b7544dd42562ca2d8f65235fd8f8e0f"; + version = "0.5.1.12"; + sha256 = "108c09122850d062154e09afb6aa44cfa2f6d290fc5836d983183f6646e06b36"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/chris-martin/partial-semigroup"; description = "A partial binary associative operator"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; + }) {}; + "password" = callPackage + ({ mkDerivation, base, base64, bytestring, Cabal, cabal-doctest + , cryptonite, lib, memory, password-types, template-haskell, text + }: + mkDerivation { + pname = "password"; + version = "3.0.0.0"; + sha256 = "cb46a1d90fc3d08d1a7009dec17fc278e27b1c90baf8dd4adc46698ce727ce74"; + revision = "1"; + editedCabalFile = "0083j7wnq6dv663i22n0lmrgq8df5pl96xlyad3jv9l27r4z4gdk"; + setupHaskellDepends = [ base Cabal cabal-doctest ]; + libraryHaskellDepends = [ + base base64 bytestring cryptonite memory password-types + template-haskell text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/cdepillabout/password/tree/master/password#readme"; + description = "Hashing and checking of passwords"; + license = lib.licenses.bsd3; + }) {}; + "password-instances" = callPackage + ({ mkDerivation, aeson, base, Cabal, cabal-doctest, http-api-data + , lib, password-types, persistent, text + }: + mkDerivation { + pname = "password-instances"; + version = "3.0.0.0"; + sha256 = "92bed2922aec17b1b086923b73ba77104e856c6d1998e0333d6dd8624216c423"; + setupHaskellDepends = [ base Cabal cabal-doctest ]; + libraryHaskellDepends = [ + aeson base http-api-data password-types persistent text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/cdepillabout/password/tree/master/password-instances#readme"; + description = "typeclass instances for password package"; + license = lib.licenses.bsd3; + }) {}; + "password-types" = callPackage + ({ mkDerivation, base, bytestring, Cabal, cabal-doctest, lib + , memory, text + }: + mkDerivation { + pname = "password-types"; + version = "1.0.0.0"; + sha256 = "6551d60c61c90509592e32ee021a927539d5f391cdfd94b76ca51add05c60a24"; + revision = "1"; + editedCabalFile = "1nw1fskhr42xmhdc1bp290333vzgmc3fkfvydfwjvlw0962lxzvy"; + setupHaskellDepends = [ base Cabal cabal-doctest ]; + libraryHaskellDepends = [ base bytestring memory text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/cdepillabout/password/tree/master/password-types#readme"; + description = "Types for handling passwords"; + license = lib.licenses.bsd3; }) {}; "path" = callPackage ({ mkDerivation, aeson, base, deepseq, exceptions, filepath - , hashable, stdenv, template-haskell + , hashable, lib, template-haskell, text }: mkDerivation { pname = "path"; - version = "0.6.1"; - sha256 = "4b8bd85a13395b4240c639b9cf804371854d5dac69158f661068bd3089a25e59"; + version = "0.8.0"; + sha256 = "24cb49bb585f33a3b334ab55cb9bac251b66afdb617b71a20dbaeb820351fa6f"; revision = "1"; - editedCabalFile = "05b1zwx2a893h4h5wvgpc5g5pyx71hfmx409rqisd8s1bq1hn463"; + editedCabalFile = "02vhx94mqapyigvayb6cj7p7snn354pb542n3qyvsm0gih52wlja"; libraryHaskellDepends = [ aeson base deepseq exceptions filepath hashable template-haskell + text ]; doHaddock = false; doCheck = false; description = "Support for well-typed paths"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "path-binary-instance" = callPackage + ({ mkDerivation, base, binary, lib, path }: + mkDerivation { + pname = "path-binary-instance"; + version = "0.1.0.1"; + sha256 = "1eac7d0c32db5415d9935d1f2d5fda6d8202454bd970cf41a28f6d63941c93a5"; + libraryHaskellDepends = [ base binary path ]; + doHaddock = false; + doCheck = false; + description = "Binary instance for Path"; + license = lib.licenses.mit; + }) {}; + "path-extensions" = callPackage + ({ mkDerivation, base, exceptions, lib, path }: + mkDerivation { + pname = "path-extensions"; + version = "0.1.1.0"; + sha256 = "45da3ba08eda4a8726385b997e10a43a2a8bb6113dc5d6944848eaac8c58725f"; + libraryHaskellDepends = [ base exceptions path ]; + doHaddock = false; + doCheck = false; + description = "Enumeration of common filetype extensions for use with the path library"; + license = lib.licenses.mit; }) {}; "path-extra" = callPackage - ({ mkDerivation, attoparsec, base, path, stdenv, text }: + ({ mkDerivation, attoparsec, base, lib, path, text }: mkDerivation { pname = "path-extra"; version = "0.2.0"; @@ -24797,19 +29799,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/athanclark/path-extra#readme"; description = "URLs without host information"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "path-io" = callPackage ({ mkDerivation, base, containers, directory, dlist, exceptions - , filepath, path, stdenv, temporary, time, transformers - , unix-compat + , filepath, lib, path, temporary, time, transformers, unix-compat }: mkDerivation { pname = "path-io"; - version = "1.4.1"; - sha256 = "57cce9e14b56fed60071bdb0f3c27c54eeeb38ca5954d9a2a4a235e475e3bf6c"; + version = "1.6.3"; + sha256 = "b604737dd6949cddb44e145bae41f1babafa90441117e025b80375e42022ccb6"; revision = "1"; - editedCabalFile = "1qb9b3rvzpdm6xp2xljmp2izz0x26bj3zvai22iyl914pzph3181"; + editedCabalFile = "0hzpwyxyj332mq09vgf06vfsga9b0q711fr52x3xswcmhvvsv60g"; libraryHaskellDepends = [ base containers directory dlist exceptions filepath path temporary time transformers unix-compat @@ -24818,10 +29819,22 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mrkkrp/path-io"; description = "Interface to ‘directory’ package for users of ‘path’"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "path-like" = callPackage + ({ mkDerivation, base, lib, path }: + mkDerivation { + pname = "path-like"; + version = "0.2.0.2"; + sha256 = "094f4ead1da08c2192e453c3451b17bf54f62470b368f53f196d79f6d84725c3"; + libraryHaskellDepends = [ base path ]; + doHaddock = false; + doCheck = false; + description = "PathLike, FileLike and DirLike type classes for the Path library"; + license = lib.licenses.mit; }) {}; "path-pieces" = callPackage - ({ mkDerivation, base, stdenv, text, time }: + ({ mkDerivation, base, lib, text, time }: mkDerivation { pname = "path-pieces"; version = "0.2.1"; @@ -24832,16 +29845,15 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Components of paths"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "path-text-utf8" = callPackage - ({ mkDerivation, base, bytestring, path, safe-exceptions, stdenv - , text + ({ mkDerivation, base, bytestring, lib, path, safe-exceptions, text }: mkDerivation { pname = "path-text-utf8"; - version = "0.0.1.2"; - sha256 = "f6c2652d23171ffa87f13d2c804630499b6b2210853aaf8008f4d593b5f41cfd"; + version = "0.0.1.8"; + sha256 = "529a0036f0385f7f98acfcccb6d2f8fd84fcbaebc628f10758f0e372380326f6"; libraryHaskellDepends = [ base bytestring path safe-exceptions text ]; @@ -24849,16 +29861,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/chris-martin/path-text-utf8"; description = "Read and write UTF-8 text files"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; }) {}; "pathtype" = callPackage - ({ mkDerivation, base, deepseq, directory, QuickCheck, semigroups - , stdenv, tagged, time, transformers, utility-ht + ({ mkDerivation, base, deepseq, directory, lib, QuickCheck + , semigroups, tagged, time, transformers, utility-ht }: mkDerivation { pname = "pathtype"; - version = "0.8.1"; - sha256 = "d5e6dc557dcf53e97cc2f7f6d6ee30992920e3ea074042b6ac11f74f2792340f"; + version = "0.8.1.1"; + sha256 = "c7dce1871e65c6447bbe138d6ccecd5abcde84aba6fac7003e7755d238c2420c"; configureFlags = [ "-f-old-time" ]; isLibrary = true; isExecutable = true; @@ -24870,10 +29882,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://hub.darcs.net/thielema/pathtype/"; description = "Type-safe replacement for System.FilePath etc"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pathwalk" = callPackage - ({ mkDerivation, base, directory, filepath, stdenv, transformers }: + ({ mkDerivation, base, directory, filepath, lib, transformers }: mkDerivation { pname = "pathwalk"; version = "0.3.1.2"; @@ -24883,10 +29895,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/Xe/pathwalk"; description = "Path walking utilities for Haskell programs"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "pattern-arrows" = callPackage - ({ mkDerivation, base, mtl, stdenv }: + ({ mkDerivation, base, lib, mtl }: mkDerivation { pname = "pattern-arrows"; version = "0.0.2"; @@ -24896,50 +29908,30 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://blog.functorial.com/posts/2013-10-27-Pretty-Printing-Arrows.html"; description = "Arrows for Pretty Printing"; - license = stdenv.lib.licenses.mit; - }) {}; - "pcf-font" = callPackage - ({ mkDerivation, base, binary, bytestring, containers, stdenv - , vector, zlib - }: - mkDerivation { - pname = "pcf-font"; - version = "0.2.2.0"; - sha256 = "8a67d04240a7668e669414d1b4f531d290c79a63198e0ecf02cb0339bff098ef"; - libraryHaskellDepends = [ - base binary bytestring containers vector zlib - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/michael-swan/pcf-font"; - description = "PCF font parsing and rendering library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; - "pcf-font-embed" = callPackage - ({ mkDerivation, base, bytestring, pcf-font, stdenv - , template-haskell, vector - }: + "pava" = callPackage + ({ mkDerivation, base, lib, vector }: mkDerivation { - pname = "pcf-font-embed"; - version = "0.1.2.0"; - sha256 = "c55d51ee6f959c9c05bb9d9adac3aad1cd87b2bba3cca7d3667d67f1a230fd51"; - libraryHaskellDepends = [ - base bytestring pcf-font template-haskell vector - ]; + pname = "pava"; + version = "0.1.1.1"; + sha256 = "fb2346570a1e159946064a46e2f6c83170a08718cef29505cac06acc02835486"; + libraryHaskellDepends = [ base vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/michael-swan/pcf-font-embed"; - description = "Template Haskell for embedding text rendered using PCF fonts"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/dschrempf/pava#readme"; + description = "Greatest convex majorants and least concave minorants"; + license = lib.licenses.gpl3Plus; }) {}; "pcg-random" = callPackage - ({ mkDerivation, base, bytestring, entropy, primitive, random - , stdenv + ({ mkDerivation, base, bytestring, Cabal, cabal-doctest, entropy + , lib, primitive, random }: mkDerivation { pname = "pcg-random"; - version = "0.1.3.5"; - sha256 = "de43ff8805f9e0ffd4cd6b4f2fed8c9cfa9ab45c0fd42374636ac7a5567840a4"; + version = "0.1.3.7"; + sha256 = "e6c8c26841b5d0d6d9e2816e952e397062730fd1a0bc13cf7c3ebcba6dc1d2d0"; + setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ base bytestring entropy primitive random ]; @@ -24947,11 +29939,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/cchalmers/pcg-random"; description = "Haskell bindings to the PCG random number generator"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pcre-heavy" = callPackage - ({ mkDerivation, base, base-compat, bytestring, pcre-light - , semigroups, stdenv, string-conversions, template-haskell + ({ mkDerivation, base, base-compat, bytestring, lib, pcre-light + , semigroups, string-conversions, template-haskell }: mkDerivation { pname = "pcre-heavy"; @@ -24967,30 +29959,30 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/myfreeweb/pcre-heavy"; description = "A regexp (regex) library on top of pcre-light you can actually use"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "pcre-light" = callPackage - ({ mkDerivation, base, bytestring, pcre, stdenv }: + ({ mkDerivation, base, bytestring, lib, pcre }: mkDerivation { pname = "pcre-light"; - version = "0.4.0.4"; - sha256 = "02c97e39263d18fd26aa63d52c88c4bfbb5c3f66ab40564552e7f11d5d889e75"; + version = "0.4.1.0"; + sha256 = "16f6bfaa320bba91cd0c1a502d871c1c7a3a2de2d58dfaa2d90dba6558d51b53"; libraryHaskellDepends = [ base bytestring ]; - libraryPkgconfigDepends = [ pcre ]; + librarySystemDepends = [ pcre ]; doHaddock = false; doCheck = false; homepage = "https://github.com/Daniel-Diaz/pcre-light"; description = "Portable regex library for Perl 5 compatible regular expressions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) pcre;}; "pcre-utils" = callPackage - ({ mkDerivation, array, attoparsec, base, bytestring, mtl - , regex-pcre-builtin, stdenv, vector + ({ mkDerivation, array, attoparsec, base, bytestring, lib, mtl + , regex-pcre-builtin, vector }: mkDerivation { pname = "pcre-utils"; - version = "0.1.8.1.1"; - sha256 = "1f2a80ca63308e182542534866a844efaf880deac4145213bf1c83a560586df4"; + version = "0.1.8.2"; + sha256 = "54607e11639060893d77f0bc912870fd77b75271b3722537a889f3fef6e78ade"; libraryHaskellDepends = [ array attoparsec base bytestring mtl regex-pcre-builtin vector ]; @@ -24998,11 +29990,27 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/bartavelle/pcre-utils"; description = "Perl-like substitute and split for PCRE regexps"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "pcre2" = callPackage + ({ mkDerivation, base, containers, lib, mtl, template-haskell, text + }: + mkDerivation { + pname = "pcre2"; + version = "1.1.5"; + sha256 = "30b0f7026922e446ce237b2e5bac0094b12e23da7de01147ea1e2298c566944f"; + libraryHaskellDepends = [ + base containers mtl template-haskell text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/sjshuck/hs-pcre2#readme"; + description = "Regular expressions via the PCRE2 C library (included)"; + license = lib.licenses.asl20; }) {}; "pdfinfo" = callPackage - ({ mkDerivation, base, mtl, old-locale, process-extras, stdenv - , text, time, time-locale-compat + ({ mkDerivation, base, lib, mtl, old-locale, process-extras, text + , time, time-locale-compat }: mkDerivation { pname = "pdfinfo"; @@ -25015,42 +30023,25 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/chrisdone/pdfinfo"; description = "Wrapper around the pdfinfo command"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "peano" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "peano"; version = "0.1.0.1"; sha256 = "31fdd23993a76155738224a7b230a1a6fcfde091b2fbc945df4cb54068eeec7b"; - revision = "2"; - editedCabalFile = "10b0vjc7lnfkscg2c8hhqbvf1xdvgbr3njrs9b4ick91n44vjbhk"; + revision = "3"; + editedCabalFile = "0wl22dnz6ld300cg6id3lw991bp8kdfi8h0nbv37vn79i1zdcj5n"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; description = "Peano numbers"; license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; - }) {}; - "pedersen-commitment" = callPackage - ({ mkDerivation, base, bytestring, containers, cryptonite, memory - , mtl, protolude, stdenv, text - }: - mkDerivation { - pname = "pedersen-commitment"; - version = "0.2.0"; - sha256 = "6793cc37efa22307c935636f15dae7670330a84a7435f36412ced3b81410b0b7"; - libraryHaskellDepends = [ - base bytestring containers cryptonite memory mtl protolude text - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/adjoint-io/pedersen-commitment#readme"; - description = "An implementation of Pedersen commitment schemes"; - license = stdenv.lib.licenses.mit; + hydraPlatforms = lib.platforms.none; }) {}; "pem" = callPackage - ({ mkDerivation, base, basement, bytestring, memory, stdenv }: + ({ mkDerivation, base, basement, bytestring, lib, memory }: mkDerivation { pname = "pem"; version = "0.2.4"; @@ -25060,25 +30051,37 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/vincenthz/hs-pem"; description = "Privacy Enhanced Mail (PEM) format reader and writer"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "percent-format" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "percent-format"; - version = "0.0.1"; - sha256 = "7530a64ba6f1ac2b59bdc325f3a8a6f0006b4a24dc2cd86eb2b41ab46d460c09"; + version = "0.0.2"; + sha256 = "6e80124de2d7a7cc1f25781d85b061dfdbb68670e25973703201ef4691da8e5a"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/rudymatela/percent-format#readme"; description = "simple printf-style string formatting"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "peregrin" = callPackage + ({ mkDerivation, base, bytestring, lib, postgresql-simple, text }: + mkDerivation { + pname = "peregrin"; + version = "0.3.1"; + sha256 = "226c31bd6ed1b0520d051b8a509ac94f6c8e379e78194918e75e56797f4e3bc2"; + libraryHaskellDepends = [ base bytestring postgresql-simple text ]; + doHaddock = false; + doCheck = false; + description = "Database migration support for use in other libraries"; + license = lib.licenses.mit; }) {}; "perfect-hash-generator" = callPackage ({ mkDerivation, base, binary, bytestring, containers, data-ordlist - , directory, filepath, hashable, optparse-applicative, random - , stdenv, text, unordered-containers, vector + , directory, filepath, hashable, lib, optparse-applicative, random + , text, unordered-containers, vector }: mkDerivation { pname = "perfect-hash-generator"; @@ -25098,44 +30101,68 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/kostmo/perfect-hash-generator#readme"; description = "Perfect minimal hashing implementation in native Haskell"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; + }) {}; + "perfect-vector-shuffle" = callPackage + ({ mkDerivation, base, lib, MonadRandom, primitive, random, vector + }: + mkDerivation { + pname = "perfect-vector-shuffle"; + version = "0.1.1.1"; + sha256 = "c017bfd1794cc6c2c28dea260327a329f6a557a1d410e5da7ea0d1b435d991fc"; + revision = "5"; + editedCabalFile = "0lppvhpfpfzcpdm4fxmsps8s272gz3wd2h5xc1w1908b7qqln0rw"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base MonadRandom primitive random vector + ]; + executableHaskellDepends = [ + base MonadRandom primitive random vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/Boarders/perfect-vector-shuffle"; + description = "Library for performing vector shuffles"; + license = lib.licenses.bsd3; }) {}; "persist" = callPackage - ({ mkDerivation, base, bytestring, containers, stdenv, text }: + ({ mkDerivation, base, bytestring, containers, lib, text }: mkDerivation { pname = "persist"; - version = "0.1.1.1"; - sha256 = "6715cf359697e72ba4807ffb622037d27bb494fdd4d4fcf4d9cc66a294eb24e4"; + version = "0.1.1.5"; + sha256 = "238bbc5a40f3cfdd251512e22cc74b68e2b1c285f426fa2931cc68c5d69540a7"; libraryHaskellDepends = [ base bytestring containers text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/minad/persist"; description = "Minimal serialization library with focus on performance"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "persistable-record" = callPackage - ({ mkDerivation, array, base, containers, dlist, names-th - , product-isomorphic, stdenv, template-haskell, th-data-compat - , transformers + ({ mkDerivation, array, base, containers, dlist, lib, names-th + , product-isomorphic, template-haskell, th-bang-compat + , th-constraint-compat, th-data-compat, transformers }: mkDerivation { pname = "persistable-record"; - version = "0.6.0.4"; - sha256 = "6d3abe73d61cf691bb1b5a412fa8a6d8fcc5cb3070176041ad8953b63ca5f8f9"; + version = "0.6.0.5"; + sha256 = "0afbbddeb6721168900421dda1ed802ab84471511761a43a5505a0c3c011a8ca"; libraryHaskellDepends = [ array base containers dlist names-th product-isomorphic - template-haskell th-data-compat transformers + template-haskell th-bang-compat th-constraint-compat th-data-compat + transformers ]; doHaddock = false; doCheck = false; homepage = "http://khibino.github.io/haskell-relational-record/"; description = "Binding between SQL database values and haskell records"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "persistable-types-HDBC-pg" = callPackage - ({ mkDerivation, base, bytestring, convertible, dlist, HDBC + ({ mkDerivation, base, bytestring, convertible, dlist, HDBC, lib , persistable-record, relational-query, relational-query-HDBC - , stdenv, text-postgresql + , text-postgresql }: mkDerivation { pname = "persistable-types-HDBC-pg"; @@ -25149,63 +30176,61 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://khibino.github.io/haskell-relational-record/"; description = "HDBC and Relational-Record instances of PostgreSQL extended types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "persistent" = callPackage ({ mkDerivation, aeson, attoparsec, base, base64-bytestring - , blaze-html, blaze-markup, bytestring, conduit, containers - , fast-logger, http-api-data, monad-logger, mtl, old-locale - , path-pieces, resource-pool, resourcet, scientific, silently - , stdenv, tagged, template-haskell, text, time, transformers - , unliftio-core, unordered-containers, vector, void + , blaze-html, bytestring, conduit, containers, fast-logger + , http-api-data, lib, lift-type, monad-logger, mtl, path-pieces + , resource-pool, resourcet, scientific, silently, template-haskell + , text, th-lift-instances, time, transformers, unliftio + , unliftio-core, unordered-containers, vector }: mkDerivation { pname = "persistent"; - version = "2.9.0"; - sha256 = "e7865ceb4aa1e93ca8c65c789f92c8046a39ecf41283682bcace33e89b77f261"; - revision = "2"; - editedCabalFile = "1szx008irw7w2h9qz443mml06sg6w9vazbxxyi67d91hyjlgca2j"; + version = "2.13.1.1"; + sha256 = "2611bbee74ac451452fc2bf4bf78338a9c66591ff601b5234c5fcb5bf50de569"; libraryHaskellDepends = [ - aeson attoparsec base base64-bytestring blaze-html blaze-markup - bytestring conduit containers fast-logger http-api-data - monad-logger mtl old-locale path-pieces resource-pool resourcet - scientific silently tagged template-haskell text time transformers - unliftio-core unordered-containers vector void + aeson attoparsec base base64-bytestring blaze-html bytestring + conduit containers fast-logger http-api-data lift-type monad-logger + mtl path-pieces resource-pool resourcet scientific silently + template-haskell text th-lift-instances time transformers unliftio + unliftio-core unordered-containers vector ]; doHaddock = false; doCheck = false; homepage = "http://www.yesodweb.com/book/persistent"; description = "Type-safe, multi-backend data serialization"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "persistent-iproute" = callPackage - ({ mkDerivation, aeson, aeson-iproute, base, bytestring - , http-api-data, iproute, path-pieces, persistent, stdenv, text + "persistent-mtl" = callPackage + ({ mkDerivation, base, conduit, containers, lib, mtl, persistent + , resource-pool, resourcet, text, transformers, unliftio + , unliftio-core, unliftio-pool }: mkDerivation { - pname = "persistent-iproute"; - version = "0.2.3"; - sha256 = "f595a11ceaa1c19e11d6f4fc58ec2834eb100791ae82626912115f1d79edbfaa"; + pname = "persistent-mtl"; + version = "0.2.2.0"; + sha256 = "6890fa5a52723eff8ea80332a824767fe9a6af3cd92381931ab190f882eee87c"; libraryHaskellDepends = [ - aeson aeson-iproute base bytestring http-api-data iproute - path-pieces persistent text + base conduit containers mtl persistent resource-pool resourcet text + transformers unliftio unliftio-core unliftio-pool ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/greydot/persistent-iproute"; - description = "Persistent instances for types in iproute"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/brandonchinn178/persistent-mtl#readme"; + description = "Monad transformer for the persistent API"; + license = lib.licenses.bsd3; }) {}; "persistent-mysql" = callPackage ({ mkDerivation, aeson, base, blaze-builder, bytestring, conduit - , containers, monad-logger, mysql, mysql-simple, persistent - , resource-pool, resourcet, stdenv, text, transformers - , unliftio-core + , containers, lib, monad-logger, mysql, mysql-simple, persistent + , resource-pool, resourcet, text, transformers, unliftio-core }: mkDerivation { pname = "persistent-mysql"; - version = "2.9.0"; - sha256 = "ee4b17bd5ab8f724ad6cb98941418fca37eeaacb2ba7f21c2c7e2792898a4129"; + version = "2.13.0.1"; + sha256 = "abe957d5f3fd6bf413ade21c23f23626fe0c4eea07849dde8dff7ea6594784be"; libraryHaskellDepends = [ aeson base blaze-builder bytestring conduit containers monad-logger mysql mysql-simple persistent resource-pool resourcet text @@ -25215,113 +30240,170 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.yesodweb.com/book/persistent"; description = "Backend for the persistent library using MySQL database server"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "persistent-mysql-haskell" = callPackage - ({ mkDerivation, aeson, base, bytestring, conduit, containers - , io-streams, monad-logger, mysql-haskell, network, persistent - , persistent-template, resource-pool, resourcet, stdenv, text, time - , tls, transformers, unliftio-core + "persistent-pagination" = callPackage + ({ mkDerivation, base, conduit, esqueleto, foldl, lib, microlens + , mtl, persistent }: mkDerivation { - pname = "persistent-mysql-haskell"; - version = "0.5.1"; - sha256 = "ac85be0c46f5a1df2303685125560d6a22ff528fd6d0162ce49425cce48b80c2"; - isLibrary = true; - isExecutable = true; + pname = "persistent-pagination"; + version = "0.1.1.2"; + sha256 = "b0b89b80516702da271d18e9e8d5785b5ce531b0bfe6b3a83e537199094be89a"; libraryHaskellDepends = [ - aeson base bytestring conduit containers io-streams monad-logger - mysql-haskell network persistent resource-pool resourcet text time - tls transformers unliftio-core - ]; - executableHaskellDepends = [ - base monad-logger persistent persistent-template transformers + base conduit esqueleto foldl microlens mtl persistent ]; doHaddock = false; doCheck = false; - homepage = "http://www.yesodweb.com/book/persistent"; - description = "A pure haskell backend for the persistent library using MySQL database server"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/parsonsmatt/persistent-pagination#readme"; + description = "Efficient and correct pagination for persistent or esqueleto queries"; + license = lib.licenses.bsd3; }) {}; "persistent-postgresql" = callPackage - ({ mkDerivation, aeson, base, blaze-builder, bytestring, conduit - , containers, monad-logger, persistent, postgresql-libpq - , postgresql-simple, resource-pool, resourcet, stdenv, text, time - , transformers, unliftio-core + ({ mkDerivation, aeson, attoparsec, base, blaze-builder, bytestring + , conduit, containers, lib, monad-logger, mtl, persistent + , postgresql-libpq, postgresql-simple, resource-pool, resourcet + , string-conversions, text, time, transformers, unliftio-core }: mkDerivation { pname = "persistent-postgresql"; - version = "2.9.0"; - sha256 = "bd029ca877f9536398e9703e5886731059dbcbd7015cdc470b54727e7e5b14e7"; - revision = "1"; - editedCabalFile = "0xrnww7n6kwr2371fj5xklslbx0114yj3pxcpdzwalmin5wm8vah"; + version = "2.13.0.3"; + sha256 = "d274952dfa374b2dc213d866228c772fc03aa13133642eef2775c885b6f7c519"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - aeson base blaze-builder bytestring conduit containers monad-logger - persistent postgresql-libpq postgresql-simple resource-pool - resourcet text time transformers unliftio-core + aeson attoparsec base blaze-builder bytestring conduit containers + monad-logger mtl persistent postgresql-libpq postgresql-simple + resource-pool resourcet string-conversions text time transformers + unliftio-core ]; doHaddock = false; doCheck = false; homepage = "http://www.yesodweb.com/book/persistent"; description = "Backend for the persistent library using postgresql"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "persistent-qq" = callPackage + ({ mkDerivation, base, haskell-src-meta, lib, mtl, persistent + , template-haskell, text + }: + mkDerivation { + pname = "persistent-qq"; + version = "2.12.0.1"; + sha256 = "d7b80b6e1f368fc8c67d48db67bea1c2c7de3aa79795865bdd822bd9af8a76b7"; + libraryHaskellDepends = [ + base haskell-src-meta mtl persistent template-haskell text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/yesodweb/persistent#readme"; + description = "Provides a quasi-quoter for raw SQL for persistent"; + license = lib.licenses.mit; }) {}; "persistent-sqlite" = callPackage - ({ mkDerivation, aeson, base, bytestring, conduit, containers - , microlens-th, monad-logger, old-locale, persistent, resource-pool - , resourcet, sqlite, stdenv, text, time, transformers - , unliftio-core, unordered-containers + ({ mkDerivation, aeson, base, bytestring, conduit, containers, lib + , microlens-th, monad-logger, mtl, persistent, resource-pool + , resourcet, sqlite, text, time, transformers, unliftio-core + , unordered-containers }: mkDerivation { pname = "persistent-sqlite"; - version = "2.9.2"; - sha256 = "0fe538410b18bb9a61832fc5c1726ed161f4eb685c399d3660c4c41f54f0b5de"; + version = "2.13.0.3"; + sha256 = "680cbef69023a37a9a5c1be9f2f926e66257ae2bfc764c94afe4cc955942ea8b"; configureFlags = [ "-fsystemlib" ]; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ aeson base bytestring conduit containers microlens-th monad-logger - old-locale persistent resource-pool resourcet text time - transformers unliftio-core unordered-containers + mtl persistent resource-pool resourcet text time transformers + unliftio-core unordered-containers ]; librarySystemDepends = [ sqlite ]; doHaddock = false; doCheck = false; homepage = "http://www.yesodweb.com/book/persistent"; description = "Backend for the persistent library using sqlite3"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {inherit (pkgs) sqlite;}; "persistent-template" = callPackage - ({ mkDerivation, aeson, aeson-compat, base, bytestring, containers - , ghc-prim, http-api-data, monad-control, monad-logger, path-pieces - , persistent, stdenv, tagged, template-haskell, text, transformers - , unordered-containers - }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "persistent-template"; - version = "2.5.4"; - sha256 = "4cae740ce92f98cb3ae9e092e740753394d5687b887399ee5f87af7f3c730a01"; - revision = "3"; - editedCabalFile = "12f4pqxwfv2li78sd9s56p66xd0w465cmjycpkqvg8n1rjxkc8vs"; + version = "2.12.0.0"; + sha256 = "dc488b567d373ebfbf5f3df8bba240e6203d1b13556872648d5f0d228fd02c31"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "http://www.yesodweb.com/book/persistent"; + description = "Type-safe, non-relational, multi-backend persistence"; + license = lib.licenses.mit; + }) {}; + "persistent-test" = callPackage + ({ mkDerivation, aeson, base, blaze-html, bytestring, conduit + , containers, exceptions, hspec, hspec-expectations, http-api-data + , HUnit, lib, monad-control, monad-logger, mtl, path-pieces + , persistent, QuickCheck, quickcheck-instances, random, resourcet + , text, time, transformers, transformers-base, unliftio + , unliftio-core, unordered-containers + }: + mkDerivation { + pname = "persistent-test"; + version = "2.13.0.3"; + sha256 = "7a6766c670888816f64b13c1ff1c0894f137fd9e0ea93341700c800fb71c051f"; libraryHaskellDepends = [ - aeson aeson-compat base bytestring containers ghc-prim - http-api-data monad-control monad-logger path-pieces persistent - tagged template-haskell text transformers unordered-containers + aeson base blaze-html bytestring conduit containers exceptions + hspec hspec-expectations http-api-data HUnit monad-control + monad-logger mtl path-pieces persistent QuickCheck + quickcheck-instances random resourcet text time transformers + transformers-base unliftio unliftio-core unordered-containers ]; doHaddock = false; doCheck = false; homepage = "http://www.yesodweb.com/book/persistent"; - description = "Type-safe, non-relational, multi-backend persistence"; - license = stdenv.lib.licenses.mit; + description = "Tests for Persistent"; + license = lib.licenses.mit; + }) {}; + "persistent-typed-db" = callPackage + ({ mkDerivation, aeson, base, bytestring, conduit, http-api-data + , lib, monad-logger, path-pieces, persistent, resource-pool + , resourcet, template-haskell, text, transformers + }: + mkDerivation { + pname = "persistent-typed-db"; + version = "0.1.0.4"; + sha256 = "685e73eb12ea440850fa861bb04c59c056f4d36771988d272e38ce6f5e9ca5b5"; + libraryHaskellDepends = [ + aeson base bytestring conduit http-api-data monad-logger + path-pieces persistent resource-pool resourcet template-haskell + text transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/parsonsmatt/persistent-typed-db#readme"; + description = "Type safe access to multiple database schemata"; + license = lib.licenses.bsd3; + }) {}; + "pg-harness-client" = callPackage + ({ mkDerivation, base, bytestring, HTTP, lib }: + mkDerivation { + pname = "pg-harness-client"; + version = "0.6.0"; + sha256 = "d0624036ffa888edd9b5073a3c485400ef1057497f1748f5084c03818bcaf819"; + libraryHaskellDepends = [ base bytestring HTTP ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/BardurArantsson/pg-harness"; + description = "Client library for pg-harness-server"; + license = lib.licenses.bsd2; }) {}; "pg-transact" = callPackage - ({ mkDerivation, base, bytestring, exceptions, monad-control - , postgresql-simple, stdenv, transformers + ({ mkDerivation, base, bytestring, exceptions, lib, monad-control + , postgresql-simple, transformers }: mkDerivation { pname = "pg-transact"; - version = "0.1.0.1"; - sha256 = "598236369ee1228a3a76b4f0d5830d652a90ddbc0f98fdde064ad979a1abc97d"; + version = "0.3.2.0"; + sha256 = "af109e82fee758d159654b9c02c396197852cbd909b5f02dbbd4ef0613270432"; libraryHaskellDepends = [ base bytestring exceptions monad-control postgresql-simple transformers @@ -25329,25 +30411,24 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; homepage = "https://github.com/jfischoff/pg-transact#readme"; - description = "Another postgresql-simple transaction monad"; - license = stdenv.lib.licenses.bsd3; + description = "A postgresql-simple transaction monad"; + license = lib.licenses.bsd3; }) {}; "pgp-wordlist" = callPackage - ({ mkDerivation, base, bytestring, containers, stdenv, text, vector - }: + ({ mkDerivation, base, bytestring, containers, lib, text, vector }: mkDerivation { pname = "pgp-wordlist"; - version = "0.1.0.2"; - sha256 = "e28b6fe85222adf1247d5870ab47c68c3d25df3f9ceda104bfb64e1414a92466"; + version = "0.1.0.3"; + sha256 = "ef3b560276981def53abc01cbe3cb4d0bece8eaa8a210ee890729ee500c4e695"; libraryHaskellDepends = [ base bytestring containers text vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/quchen/pgp-wordlist"; description = "Translate between binary data and a human-readable collection of words"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "phantom-state" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "phantom-state"; version = "0.2.1.2"; @@ -25356,10 +30437,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Phantom State Transformer. Like State Monad, but without values."; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pid1" = callPackage - ({ mkDerivation, base, directory, process, stdenv, unix }: + ({ mkDerivation, base, directory, lib, process, unix }: mkDerivation { pname = "pid1"; version = "0.1.2.0"; @@ -25374,30 +30455,48 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/fpco/pid1#readme"; description = "Do signal handling and orphan reaping for Unix PID1 init processes"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "pinboard" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers, http-client + , http-client-tls, http-types, lib, monad-logger, mtl, network + , profunctors, random, text, time, transformers, unliftio + , unliftio-core, unordered-containers, vector + }: + mkDerivation { + pname = "pinboard"; + version = "0.10.2.0"; + sha256 = "938db0474ea30c6f4c602bf1c619375601f7ad5360811761aa5e1f3bf1731c8a"; + libraryHaskellDepends = [ + aeson base bytestring containers http-client http-client-tls + http-types monad-logger mtl network profunctors random text time + transformers unliftio unliftio-core unordered-containers vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jonschoning/pinboard"; + description = "Access to the Pinboard API"; + license = lib.licenses.mit; }) {}; "pipes" = callPackage - ({ mkDerivation, base, exceptions, mmorph, mtl, semigroups, stdenv - , transformers, void + ({ mkDerivation, base, exceptions, lib, mmorph, mtl, transformers + , void }: mkDerivation { pname = "pipes"; - version = "4.3.9"; - sha256 = "5c4cda351f9cf59376832baaeb857db25bd4990fd78c4b061aca0bde47271acb"; - revision = "1"; - editedCabalFile = "0mkwbbn8vlrsvm3pl2cyaw1qr9hbjqfm831naj7cbrmiksf2l5aa"; + version = "4.3.16"; + sha256 = "f4e16ecf010fd681a56e6216ab1bd429f3c9bc962ec032e32cfd23e374e97498"; libraryHaskellDepends = [ - base exceptions mmorph mtl semigroups transformers void + base exceptions mmorph mtl transformers void ]; doHaddock = false; doCheck = false; description = "Compositional pipelines"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pipes-aeson" = callPackage - ({ mkDerivation, aeson, attoparsec, base, bytestring, pipes - , pipes-attoparsec, pipes-bytestring, pipes-parse, stdenv - , transformers + ({ mkDerivation, aeson, attoparsec, base, bytestring, lib, pipes + , pipes-attoparsec, pipes-bytestring, pipes-parse, transformers }: mkDerivation { pname = "pipes-aeson"; @@ -25411,11 +30510,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/k0001/pipes-aeson"; description = "Encode and decode JSON streams using Aeson and Pipes"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pipes-attoparsec" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, pipes, pipes-parse - , stdenv, text, transformers + ({ mkDerivation, attoparsec, base, bytestring, lib, pipes + , pipes-parse, text, transformers }: mkDerivation { pname = "pipes-attoparsec"; @@ -25428,11 +30527,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/k0001/pipes-attoparsec"; description = "Attoparsec and Pipes integration"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pipes-binary" = callPackage - ({ mkDerivation, base, binary, bytestring, ghc-prim, pipes - , pipes-bytestring, pipes-parse, stdenv, transformers + ({ mkDerivation, base, binary, bytestring, ghc-prim, lib, pipes + , pipes-bytestring, pipes-parse, transformers }: mkDerivation { pname = "pipes-binary"; @@ -25446,16 +30545,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/k0001/pipes-binary"; description = "Encode and decode binary streams using the pipes and binary libraries"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pipes-bytestring" = callPackage - ({ mkDerivation, base, bytestring, pipes, pipes-group, pipes-parse - , stdenv, stringsearch, transformers + ({ mkDerivation, base, bytestring, lib, pipes, pipes-group + , pipes-parse, stringsearch, transformers }: mkDerivation { pname = "pipes-bytestring"; - version = "2.1.6"; - sha256 = "b1dc370680f3671759010caace183bce683d0481bd2c0e3f4906b78ac8623c18"; + version = "2.1.7"; + sha256 = "6c77863e8ad809f3b86e9e0cf8c553056a8ef12bb2691f8031c5917d0b090732"; libraryHaskellDepends = [ base bytestring pipes pipes-group pipes-parse stringsearch transformers @@ -25463,42 +30562,29 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "ByteString support for pipes"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "pipes-category" = callPackage - ({ mkDerivation, base, lens, mtl, pipes, pipes-extras, stdenv }: - mkDerivation { - pname = "pipes-category"; - version = "0.3.0.0"; - sha256 = "4711d889ed2bf7244bbbc292af5746e0378d72a09929aa1e668056e7f0180701"; - libraryHaskellDepends = [ base lens mtl pipes pipes-extras ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/louispan/pipes-category#readme"; - description = "Allows instances for Category, Arrow and ArrowChoice for Pipes"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pipes-concurrency" = callPackage - ({ mkDerivation, async, base, contravariant, pipes, semigroups - , stdenv, stm, void + ({ mkDerivation, async, base, contravariant, lib, pipes, semigroups + , stm, void }: mkDerivation { pname = "pipes-concurrency"; version = "2.0.12"; sha256 = "4343c67710e2fcd8987c537389773358150559bf06e86d96b1097c15ae81589d"; - revision = "1"; - editedCabalFile = "1c1rys2pp7a2z6si925ps610q8a38a6m26s182phwa5nfhyggpaw"; + revision = "2"; + editedCabalFile = "1c06nypirrd76jg5y508517smxh3izy98y6kj89k79kbpi5rncbj"; libraryHaskellDepends = [ async base contravariant pipes semigroups stm void ]; doHaddock = false; doCheck = false; description = "Concurrency for the pipes ecosystem"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pipes-csv" = callPackage - ({ mkDerivation, base, blaze-builder, bytestring, cassava, pipes - , stdenv, unordered-containers, vector + ({ mkDerivation, base, blaze-builder, bytestring, cassava, lib + , pipes, unordered-containers, vector }: mkDerivation { pname = "pipes-csv"; @@ -25511,23 +30597,25 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Fast, streaming csv parser"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "pipes-extras" = callPackage - ({ mkDerivation, base, foldl, lens, pipes, stdenv, transformers }: + ({ mkDerivation, base, foldl, lens, lib, pipes, transformers }: mkDerivation { pname = "pipes-extras"; version = "1.0.15"; sha256 = "02a9633ac912fd48e9a5ca0e6b48a6e9541ce59d11243096ca6af6b25701cbb3"; + revision = "3"; + editedCabalFile = "177l1fs1wgm34ifbx83xxf29m0ghq6z9skpkwm86qfln2hpikkj9"; libraryHaskellDepends = [ base foldl lens pipes transformers ]; doHaddock = false; doCheck = false; description = "Extra utilities for pipes"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pipes-fastx" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, pipes - , pipes-attoparsec, pipes-bytestring, stdenv + ({ mkDerivation, attoparsec, base, bytestring, lib, pipes + , pipes-attoparsec, pipes-bytestring }: mkDerivation { pname = "pipes-fastx"; @@ -25539,83 +30627,46 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Streaming parsers for Fasta and Fastq"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "pipes-fluid" = callPackage - ({ mkDerivation, base, constraints, lens, lifted-async - , monad-control, pipes, semigroups, stdenv, stm, these - , transformers, transformers-base - }: - mkDerivation { - pname = "pipes-fluid"; - version = "0.6.0.1"; - sha256 = "105d8e8df7e731e2d272a22891eb68db1ca3ec9f425b67af77c5d91e3f032f06"; - libraryHaskellDepends = [ - base constraints lens lifted-async monad-control pipes semigroups - stm these transformers transformers-base - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/louispan/pipes-fluid#readme"; - description = "Reactively combines Producers so that a value is yielded as soon as possible"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pipes-group" = callPackage - ({ mkDerivation, base, free, pipes, pipes-parse, stdenv - , transformers + ({ mkDerivation, base, free, lib, pipes, pipes-parse, transformers }: mkDerivation { pname = "pipes-group"; version = "1.0.12"; sha256 = "1373e89fbeb127c31461042cdda848da2048eda2700ddbd872d444af87745ac7"; + revision = "4"; + editedCabalFile = "16y13pmwwfj0cgwdjf9nglxgfxv3fkznjp1bf344jfvjm14vwg43"; libraryHaskellDepends = [ base free pipes pipes-parse transformers ]; doHaddock = false; doCheck = false; description = "Group streams into substreams"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pipes-http" = callPackage ({ mkDerivation, base, bytestring, http-client, http-client-tls - , pipes, stdenv + , lib, pipes }: mkDerivation { pname = "pipes-http"; - version = "1.0.5"; - sha256 = "49a196466de1638f3806a49bf10fef9eb3c06456ababf09ffd025b6b64f23055"; + version = "1.0.6"; + sha256 = "a231fb08dfac54c1fac7a0c805f1b6c6e60a380021bb5722b508d6b36e4ba700"; revision = "1"; - editedCabalFile = "015psgj5wl67p0qdc00nrn717gv354gii70c57n1px5j81b0z5cl"; + editedCabalFile = "1xaqygyzm0i7fg24mipngg4j258yqsrnp0wjgkl16syqsn387h8c"; libraryHaskellDepends = [ base bytestring http-client http-client-tls pipes ]; doHaddock = false; doCheck = false; description = "HTTP client with pipes interface"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "pipes-misc" = callPackage - ({ mkDerivation, base, clock, Decimal, lens, mmorph, mtl, pipes - , pipes-category, pipes-concurrency, semigroups, stdenv, stm - , transformers - }: - mkDerivation { - pname = "pipes-misc"; - version = "0.5.0.0"; - sha256 = "4e2e7e396ee0c659ae3742388d06b69e3b5146a5563cd3f4ba56f9a1febb8d26"; - libraryHaskellDepends = [ - base clock Decimal lens mmorph mtl pipes pipes-category - pipes-concurrency semigroups stm transformers - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/louispan/pipes-misc#readme"; - description = "Miscellaneous utilities for pipes, required by glazier-tutorial"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pipes-network" = callPackage - ({ mkDerivation, base, bytestring, exceptions, network - , network-simple, pipes, pipes-safe, stdenv, transformers + ({ mkDerivation, base, bytestring, exceptions, lib, network + , network-simple, pipes, pipes-safe, transformers }: mkDerivation { pname = "pipes-network"; @@ -25629,17 +30680,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/k0001/pipes-network"; description = "Use network sockets together with the pipes library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pipes-network-tls" = callPackage - ({ mkDerivation, base, bytestring, network, network-simple - , network-simple-tls, pipes, pipes-network, pipes-safe, stdenv, tls + ({ mkDerivation, base, bytestring, lib, network, network-simple + , network-simple-tls, pipes, pipes-network, pipes-safe, tls , transformers }: mkDerivation { pname = "pipes-network-tls"; - version = "0.3"; - sha256 = "a2694a6b15d71a8cae898dd8e6a085a4e1ae317c40f2752ceed2b991dfb6bab2"; + version = "0.4"; + sha256 = "751757bcb659bafed6e5abb781ca42d70be8b9f000afa0aea5bb64b01fc73698"; libraryHaskellDepends = [ base bytestring network network-simple network-simple-tls pipes pipes-network pipes-safe tls transformers @@ -25648,28 +30699,54 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/k0001/pipes-network-tls"; description = "TLS-secured network connections support for pipes"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "pipes-ordered-zip" = callPackage + ({ mkDerivation, base, lib, pipes, pipes-safe }: + mkDerivation { + pname = "pipes-ordered-zip"; + version = "1.2.1"; + sha256 = "b5fdb066640fdd786698afb7b9a820db4993daffc4947d32d845e5264bb7f849"; + libraryHaskellDepends = [ base pipes pipes-safe ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/githubuser/pipes-ordered-zip#readme"; + description = "merge two ordered Producers into a new Producer"; + license = lib.licenses.bsd3; }) {}; "pipes-parse" = callPackage - ({ mkDerivation, base, pipes, stdenv, transformers }: + ({ mkDerivation, base, lib, pipes, transformers }: mkDerivation { pname = "pipes-parse"; - version = "3.0.8"; - sha256 = "d28f831b2c8229cca567ee95570787d2dd3f5cfcff3b3c44ee308360a8c107a9"; + version = "3.0.9"; + sha256 = "a3973f9b01d68cce75d6c5b049fe5dbff6d4f6753019349ccff5cfad82048d15"; libraryHaskellDepends = [ base pipes transformers ]; doHaddock = false; doCheck = false; description = "Parsing infrastructure for the pipes ecosystem"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "pipes-random" = callPackage + ({ mkDerivation, base, lib, mwc-random, pipes, vector }: + mkDerivation { + pname = "pipes-random"; + version = "1.0.0.5"; + sha256 = "b3ec59bde4d004db2130097c7d981e3fdaf3c63a0ba7e903da33673d3b034bf7"; + libraryHaskellDepends = [ base mwc-random pipes vector ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/fosskers/pipes-random"; + description = "Producers for handling randomness"; + license = lib.licenses.bsd3; }) {}; "pipes-safe" = callPackage - ({ mkDerivation, base, containers, exceptions, monad-control, mtl - , pipes, primitive, stdenv, transformers, transformers-base + ({ mkDerivation, base, containers, exceptions, lib, monad-control + , mtl, pipes, primitive, transformers, transformers-base }: mkDerivation { pname = "pipes-safe"; - version = "2.3.1"; - sha256 = "9ef249d0a37c18ddc40efeb6a603c01d0438a45b100951ace3a739c6dc68cd35"; + version = "2.3.3"; + sha256 = "4bc1f7d91928caaf98d42e8d28ff2b3939faee187bc80588c076855afa48f7a5"; libraryHaskellDepends = [ base containers exceptions monad-control mtl pipes primitive transformers transformers-base @@ -25677,11 +30754,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Safety for the pipes ecosystem"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pipes-wai" = callPackage - ({ mkDerivation, base, blaze-builder, bytestring, http-types, pipes - , stdenv, transformers, wai + ({ mkDerivation, base, blaze-builder, bytestring, http-types, lib + , pipes, transformers, wai }: mkDerivation { pname = "pipes-wai"; @@ -25694,11 +30771,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/iand675/pipes-wai"; description = "A port of wai-conduit for the pipes ecosystem"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "pkcs10" = callPackage ({ mkDerivation, asn1-encoding, asn1-parse, asn1-types, base - , bytestring, cryptonite, pem, stdenv, x509 + , bytestring, cryptonite, lib, pem, x509 }: mkDerivation { pname = "pkcs10"; @@ -25712,10 +30789,49 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/fcomb/pkcs10-hs#readme"; description = "PKCS#10 library"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; + }) {}; + "pkgtreediff" = callPackage + ({ mkDerivation, async, base, directory, extra, filepath, Glob + , http-client, http-client-tls, http-directory, koji, lib + , simple-cmd, simple-cmd-args, text + }: + mkDerivation { + pname = "pkgtreediff"; + version = "0.4.1"; + sha256 = "e0c6478c08fba53a60bffc657f63614f94d8a740b0132312f05bf97cf9e5407a"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base text ]; + executableHaskellDepends = [ + async base directory extra filepath Glob http-client + http-client-tls http-directory koji simple-cmd simple-cmd-args text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/juhp/pkgtreediff"; + description = "Package tree diff tool"; + license = lib.licenses.gpl3Only; + }) {}; + "place-cursor-at" = callPackage + ({ mkDerivation, base, base-unicode-symbols, lib, libXinerama, X11 + }: + mkDerivation { + pname = "place-cursor-at"; + version = "1.0.1"; + sha256 = "3fcde9218bd900eef9e60b0c73945866e65cb07650cb726e5611b68fa2f7fd55"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ base base-unicode-symbols X11 ]; + executableSystemDepends = [ libXinerama ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/unclechu/place-cursor-at#readme"; + description = "A utility for X11 that moves the mouse cursor using the keyboard"; + license = lib.licenses.gpl3Only; }) {}; "placeholders" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { pname = "placeholders"; version = "0.1"; @@ -25725,11 +30841,40 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ahammar/placeholders"; description = "Placeholders for use while developing Haskell code"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "plaid" = callPackage + ({ mkDerivation, aeson, base, bytestring, casing, conduit + , conduit-extra, containers, either, http-client, http-client-tls + , http-conduit, lib, microlens, microlens-th, mtl, network + , pretty-simple, raw-strings-qq, safe-exceptions, text, time + , transformers + }: + mkDerivation { + pname = "plaid"; + version = "0.1.0.4"; + sha256 = "d1ba686d7ce7ec7fc27c7f1fc83042336ef620450b3a781009b41069eb689cd7"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson base bytestring casing containers http-client-tls + http-conduit microlens microlens-th mtl network pretty-simple + raw-strings-qq safe-exceptions text time + ]; + executableHaskellDepends = [ + aeson base bytestring conduit conduit-extra either http-client + http-client-tls microlens microlens-th mtl network pretty-simple + safe-exceptions text time transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/v0d1ch/plaid#readme"; + description = "Plaid.com api integration library"; + license = lib.licenses.bsd3; }) {}; "plotlyhs" = callPackage ({ mkDerivation, aeson, base, blaze-html, blaze-markup, bytestring - , lucid, microlens, microlens-th, stdenv, text, time + , lib, lucid, microlens, microlens-th, text, time }: mkDerivation { pname = "plotlyhs"; @@ -25743,19 +30888,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/diffusionkinetics/open/plotlyhs"; description = "Haskell bindings to Plotly.js"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "pointed" = callPackage ({ mkDerivation, base, comonad, containers, data-default-class - , hashable, kan-extensions, semigroupoids, semigroups, stdenv, stm + , hashable, kan-extensions, lib, semigroupoids, semigroups, stm , tagged, transformers, transformers-compat, unordered-containers }: mkDerivation { pname = "pointed"; - version = "5.0.1"; - sha256 = "b94635a5c8779238501a9156015422ce2fb4d5efd45d68999e8cbe2ecc5121dd"; - revision = "1"; - editedCabalFile = "1ccjmzz3jf5ybrzv7qdwm3qb8rz0yskvi4ackrixyhdk8bg5f3nc"; + version = "5.0.2"; + sha256 = "b8ba3d7c1e4a4fcb3f3c7f1c0a9f4d237bdf45e93ba7a2fad07ec5268c17e91e"; libraryHaskellDepends = [ base comonad containers data-default-class hashable kan-extensions semigroupoids semigroups stm tagged transformers @@ -25765,10 +30908,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/pointed/"; description = "Pointed and copointed data"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pointedlist" = callPackage - ({ mkDerivation, base, binary, stdenv }: + ({ mkDerivation, base, binary, lib }: mkDerivation { pname = "pointedlist"; version = "0.6.1"; @@ -25777,10 +30920,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A zipper-like comonad which works as a list, tracking a position"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pointless-fun" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "pointless-fun"; version = "1.1.0.6"; @@ -25790,22 +30933,40 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://code.haskell.org/~wren/"; description = "Some common point-free combinators"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "poll" = callPackage - ({ mkDerivation, base, enumset, stdenv, utility-ht }: + ({ mkDerivation, base, enumset, lib, utility-ht }: mkDerivation { pname = "poll"; - version = "0.0.0.1"; - sha256 = "b9fe87fe1b4d3ecb2ad3c1c290e231b0c93d498f0d318f67018a1dde97a0ed29"; + version = "0.0.0.2"; + sha256 = "8248d3758ea60655ac7da34640f31ab07dd11bf41f04b60899e79a943d8194ae"; libraryHaskellDepends = [ base enumset utility-ht ]; doHaddock = false; doCheck = false; description = "Bindings to poll.h"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "poly" = callPackage + ({ mkDerivation, base, deepseq, finite-typelits, lib, primitive + , semirings, vector, vector-algorithms, vector-sized + }: + mkDerivation { + pname = "poly"; + version = "0.5.0.0"; + sha256 = "f493191257207b9c51aceec8bfebc1eeaa7f34579900ada590be2fcba35ff6c0"; + libraryHaskellDepends = [ + base deepseq finite-typelits primitive semirings vector + vector-algorithms vector-sized + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/Bodigrim/poly#readme"; + description = "Polynomials"; + license = lib.licenses.bsd3; }) {}; "poly-arity" = callPackage - ({ mkDerivation, base, constraints, stdenv }: + ({ mkDerivation, base, constraints, lib }: mkDerivation { pname = "poly-arity"; version = "0.1.0"; @@ -25814,10 +30975,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Tools for working with functions of undetermined arity"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "polynomials-bernstein" = callPackage - ({ mkDerivation, base, stdenv, vector }: + ({ mkDerivation, base, lib, vector }: mkDerivation { pname = "polynomials-bernstein"; version = "1.1.2"; @@ -25829,11 +30990,13 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; license = "GPL"; }) {}; "polyparse" = callPackage - ({ mkDerivation, base, bytestring, stdenv, text }: + ({ mkDerivation, base, bytestring, lib, text }: mkDerivation { pname = "polyparse"; - version = "1.12.1"; - sha256 = "dd8d34e05853ea0ab9b9fee1cbaa51ae33095f7c0c09ff539dcd6d771e0adaa5"; + version = "1.13"; + sha256 = "1c4c72980e1e5a4f07fea65ca08b2399581d2a6aa21eb1078f7ad286c279707b"; + revision = "2"; + editedCabalFile = "1n5q6w7x46cvcq7j1pg9jx9h72vcsc5di35rbkmwgjw6pq4w4gfl"; libraryHaskellDepends = [ base bytestring text ]; doHaddock = false; doCheck = false; @@ -25841,9 +31004,49 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; description = "A variety of alternative parser combinator libraries"; license = "LGPL"; }) {}; + "polysemy" = callPackage + ({ mkDerivation, async, base, Cabal, cabal-doctest, containers + , first-class-families, lib, mtl, QuickCheck, stm, syb + , template-haskell, th-abstraction, transformers, type-errors + , type-errors-pretty, unagi-chan + }: + mkDerivation { + pname = "polysemy"; + version = "1.5.0.0"; + sha256 = "9fc7f55473931cd2661c18516838e4c29e760024f335a59acc92734b29a518b5"; + setupHaskellDepends = [ base Cabal cabal-doctest ]; + libraryHaskellDepends = [ + async base containers first-class-families mtl QuickCheck stm syb + template-haskell th-abstraction transformers type-errors + type-errors-pretty unagi-chan + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/polysemy-research/polysemy#readme"; + description = "Higher-order, low-boilerplate free monads"; + license = lib.licenses.bsd3; + }) {}; + "polysemy-plugin" = callPackage + ({ mkDerivation, base, Cabal, cabal-doctest, containers, ghc + , ghc-tcplugins-extra, lib, polysemy, syb, transformers + }: + mkDerivation { + pname = "polysemy-plugin"; + version = "0.3.0.0"; + sha256 = "43d0ab486cd5bcb6c46b94fcbef797fb135345d3a59d42e7d79b356bcd219e5d"; + setupHaskellDepends = [ base Cabal cabal-doctest ]; + libraryHaskellDepends = [ + base containers ghc ghc-tcplugins-extra polysemy syb transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/polysemy-research/polysemy#readme"; + description = "Disambiguate obvious uses of effects"; + license = lib.licenses.bsd3; + }) {}; "pooled-io" = callPackage - ({ mkDerivation, base, concurrent-split, containers, deepseq - , stdenv, transformers, unsafe, utility-ht + ({ mkDerivation, base, concurrent-split, containers, deepseq, lib + , transformers, unsafe, utility-ht }: mkDerivation { pname = "pooled-io"; @@ -25859,35 +31062,48 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://hub.darcs.net/thielema/pooled-io/"; description = "Run jobs on a limited number of threads and support data dependencies"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "port-utils" = callPackage - ({ mkDerivation, base, network, stdenv }: + ({ mkDerivation, base, lib, network }: mkDerivation { pname = "port-utils"; - version = "0.2.0.0"; - sha256 = "e19d8ba0c05d1a617f303d184b83a57830b0175d345041d7cd79d71f17a76ad3"; + version = "0.2.1.0"; + sha256 = "b6f830946a9daa829bb14dc7f105f28ae2cfa2ee8540af8550e3c975ac7117de"; libraryHaskellDepends = [ base network ]; doHaddock = false; doCheck = false; homepage = "https://github.com/jfischoff/port-utils#readme"; description = "Utilities for creating and waiting on ports"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "posix-paths" = callPackage - ({ mkDerivation, base, bytestring, stdenv, unix }: + ({ mkDerivation, base, bytestring, lib, unix, unliftio }: mkDerivation { pname = "posix-paths"; - version = "0.2.1.6"; - sha256 = "7239746716761bfc268b60348c5da3c2cf098fe2583f365096a6bef10f637e45"; - libraryHaskellDepends = [ base bytestring unix ]; + version = "0.3.0.0"; + sha256 = "82a89de8d2fafbfedbd3a23b1be31ada184cce5961f22e7fd22b2a75ad8757d2"; + libraryHaskellDepends = [ base bytestring unix unliftio ]; doHaddock = false; doCheck = false; description = "POSIX filepath/directory functionality"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "possibly" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "possibly"; + version = "1.0.0.0"; + sha256 = "52cd989873c966faffe60d0fe41a0222cb4dccc50313f9c9ed61a0d09db5ea22"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/cdornan/enum-text#readme"; + description = "type Possibly a = Either String a"; + license = lib.licenses.bsd3; }) {}; "post-mess-age" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "post-mess-age"; version = "0.2.1.0"; @@ -25896,147 +31112,192 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Send messages to a handle concurrently without getting them mixed"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "postgres-options" = callPackage + ({ mkDerivation, base, bytestring, generic-monoid, lib, split + , uri-bytestring + }: + mkDerivation { + pname = "postgres-options"; + version = "0.2.0.0"; + sha256 = "c45f459abcc797d0707c1931301434037acdfada33e47c843f219cf35609d9b5"; + libraryHaskellDepends = [ + base bytestring generic-monoid split uri-bytestring + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jfischoff/postgres-options#readme"; + description = "An Options type representing options for postgres connections"; + license = lib.licenses.bsd3; }) {}; "postgresql-binary" = callPackage - ({ mkDerivation, aeson, base, base-prelude, binary-parser - , bytestring, bytestring-strict-builder, containers, loch-th - , network-ip, placeholders, scientific, stdenv, text, time - , transformers, unordered-containers, uuid, vector + ({ mkDerivation, aeson, base, binary-parser, bytestring + , bytestring-strict-builder, containers, lib, network-ip + , scientific, text, time, transformers, unordered-containers, uuid + , vector }: mkDerivation { pname = "postgresql-binary"; - version = "0.12.1.2"; - sha256 = "83ad514b9f6328e89f92f66a60de7f65609386773b6edf27f8aee2ee52120582"; + version = "0.12.4"; + sha256 = "8cb802f888181dd7f1d2affbf8da0a2a63063eecd8201d5b0ec3a1a7b5e3a0c6"; libraryHaskellDepends = [ - aeson base base-prelude binary-parser bytestring - bytestring-strict-builder containers loch-th network-ip - placeholders scientific text time transformers unordered-containers - uuid vector + aeson base binary-parser bytestring bytestring-strict-builder + containers network-ip scientific text time transformers + unordered-containers uuid vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nikita-volkov/postgresql-binary"; description = "Encoders and decoders for the PostgreSQL's binary format"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "postgresql-libpq" = callPackage - ({ mkDerivation, base, bytestring, Cabal, postgresql, stdenv, unix - }: + ({ mkDerivation, base, bytestring, Cabal, lib, postgresql, unix }: mkDerivation { pname = "postgresql-libpq"; - version = "0.9.4.2"; - sha256 = "cea053c79ef1505c30518db7b9fb2ee68c9e2915d48b22f01f8eb9a9b49f06f9"; + version = "0.9.4.3"; + sha256 = "e3e246dcd55352fce514969a72a6fe37771102034fb8e662fdc7ae780b83d6bd"; + revision = "1"; + editedCabalFile = "1clivf13z15w954a0kcfkv8yc0d8kx61b68x2hk7a9236ck7l2m2"; setupHaskellDepends = [ base Cabal ]; libraryHaskellDepends = [ base bytestring unix ]; librarySystemDepends = [ postgresql ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/phadej/postgresql-libpq"; + homepage = "https://github.com/haskellari/postgresql-libpq"; description = "low-level binding to libpq"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) postgresql;}; - "postgresql-schema" = callPackage - ({ mkDerivation, base, basic-prelude, optparse-applicative - , postgresql-simple, shelly, stdenv, text, time + "postgresql-libpq-notify" = callPackage + ({ mkDerivation, base, lib, postgresql-libpq, stm }: + mkDerivation { + pname = "postgresql-libpq-notify"; + version = "0.2.0.0"; + sha256 = "6cee527617e5245bd1dc6b57b8a9b5ebf6cc070035117c3ae166a0067a1c661a"; + libraryHaskellDepends = [ base postgresql-libpq stm ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jfischoff/postgresql-libpq-notify#readme"; + description = "Minimal dependency PostgreSQL notifications library"; + license = lib.licenses.bsd3; + }) {}; + "postgresql-orm" = callPackage + ({ mkDerivation, aeson, base, blaze-builder, bytestring + , bytestring-builder, directory, filepath, ghc-prim + , haskell-src-exts, lib, mtl, old-locale, postgresql-simple + , process, temporary, text, time, transformers, unix + , unordered-containers, vector }: mkDerivation { - pname = "postgresql-schema"; - version = "0.1.14"; - sha256 = "73decc70c9fc349d0162c253eb0e92a1add5964c28ef89abfe30e97f1184d572"; + pname = "postgresql-orm"; + version = "0.5.1"; + sha256 = "a3507e5ccdb8712dbd8c228b706ce6303f4c0794d4d48fd8a683f4ce7cd10a3b"; isLibrary = true; isExecutable = true; enableSeparateDataOutput = true; libraryHaskellDepends = [ - base basic-prelude postgresql-simple shelly text - ]; - executableHaskellDepends = [ - base basic-prelude optparse-applicative shelly text time + aeson base blaze-builder bytestring bytestring-builder directory + filepath ghc-prim haskell-src-exts mtl old-locale postgresql-simple + process temporary text time transformers unix unordered-containers + vector ]; + executableHaskellDepends = [ base filepath ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/mfine/postgresql-schema"; - description = "PostgreSQL Schema Management"; - license = stdenv.lib.licenses.bsd3; + description = "An ORM (Object Relational Mapping) and migrations DSL for PostgreSQL"; + license = "GPL"; }) {}; "postgresql-simple" = callPackage ({ mkDerivation, aeson, attoparsec, base, bytestring - , bytestring-builder, case-insensitive, containers, hashable, Only - , postgresql-libpq, scientific, stdenv, template-haskell, text - , time, transformers, uuid-types, vector + , bytestring-builder, case-insensitive, containers, hashable, lib + , Only, postgresql-libpq, scientific, template-haskell, text + , time-compat, transformers, uuid-types, vector }: mkDerivation { pname = "postgresql-simple"; - version = "0.6"; - sha256 = "c96839c35485c7df0c84c76493c31435781c989a8d42e1dfc2e20202de46e0ca"; + version = "0.6.4"; + sha256 = "6d90394203ea3aa27cae4492569ab14bf175cd2d30112e565ffb92dbe95ce267"; + revision = "2"; + editedCabalFile = "1kwjlj0bsc1yd4dgfc0ydawq9acfjlf0bymwc830dryp16wpj9zv"; libraryHaskellDepends = [ aeson attoparsec base bytestring bytestring-builder case-insensitive containers hashable Only postgresql-libpq - scientific template-haskell text time transformers uuid-types - vector + scientific template-haskell text time-compat transformers + uuid-types vector ]; doHaddock = false; doCheck = false; description = "Mid-Level PostgreSQL client library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "postgresql-simple-queue" = callPackage - ({ mkDerivation, aeson, base, bytestring, exceptions, monad-control - , pg-transact, postgresql-simple, random, stdenv, stm, text, time - , transformers + "postgresql-typed" = callPackage + ({ mkDerivation, aeson, array, attoparsec, base, binary, bytestring + , containers, cryptonite, data-default, haskell-src-meta, HDBC, lib + , memory, network, old-locale, postgresql-binary, scientific + , template-haskell, text, time, tls, utf8-string, uuid, x509 + , x509-store, x509-validation }: mkDerivation { - pname = "postgresql-simple-queue"; - version = "1.0.1"; - sha256 = "330b69c54e075104171758117e714b7da6c740dff8ca09fbe33bd3ab854e5a3f"; + pname = "postgresql-typed"; + version = "0.6.2.0"; + sha256 = "5c1d5123567d634b91d053d154ed69e253e703516694ffe80e8cde115561686c"; libraryHaskellDepends = [ - aeson base bytestring exceptions monad-control pg-transact - postgresql-simple random stm text time transformers + aeson array attoparsec base binary bytestring containers cryptonite + data-default haskell-src-meta HDBC memory network old-locale + postgresql-binary scientific template-haskell text time tls + utf8-string uuid x509 x509-store x509-validation ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/jfischoff/postgresql-queue#readme"; - description = "A PostgreSQL backed queue"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/dylex/postgresql-typed"; + description = "PostgreSQL interface with compile-time SQL type checking, optional HDBC backend"; + license = lib.licenses.bsd3; }) {}; - "postgresql-simple-url" = callPackage - ({ mkDerivation, base, network-uri, postgresql-simple, split - , stdenv + "postgrest" = callPackage + ({ mkDerivation, aeson, ansi-wl-pprint, auto-update, base + , base64-bytestring, bytestring, case-insensitive, cassava + , configurator-pg, containers, contravariant, contravariant-extras + , cookie, directory, either, gitrev, hasql, hasql-pool + , hasql-transaction, heredoc, HTTP, http-types + , insert-ordered-containers, interpolatedstring-perl6, jose, lens + , lens-aeson, lib, network, network-uri, optparse-applicative + , parsec, protolude, Ranged-sets, regex-tdfa, retry, scientific + , swagger2, text, time, unix, unordered-containers, vector, wai + , wai-cors, wai-extra, wai-middleware-static, warp }: mkDerivation { - pname = "postgresql-simple-url"; - version = "0.2.1.0"; - sha256 = "1307f57cde2bd7f6d795a860deab53d3d64043f51af31e3114dee516ef7ee9c9"; - revision = "1"; - editedCabalFile = "0ck0vrlsyj3vm8sk59jnyyqpvnv1l9mciifdnrzwr981pha147qp"; + pname = "postgrest"; + version = "7.0.1"; + sha256 = "eee92b13da69555fd5132035ab007a6d780a565ac40ca5ab477e6c67634bc6b2"; + revision = "6"; + editedCabalFile = "0kkhkz1bmgc1p0yry24fhc4a3s9w28wg6gxai0cggvalbz8c4pc4"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - base network-uri postgresql-simple split + aeson ansi-wl-pprint base base64-bytestring bytestring + case-insensitive cassava configurator-pg containers contravariant + contravariant-extras cookie either gitrev hasql hasql-pool + hasql-transaction heredoc HTTP http-types insert-ordered-containers + interpolatedstring-perl6 jose lens lens-aeson network-uri + optparse-applicative parsec protolude Ranged-sets regex-tdfa + scientific swagger2 text time unordered-containers vector wai + wai-cors wai-extra wai-middleware-static ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/futurice/postgresql-simple-url"; - description = "Parse postgres:// url into ConnectInfo"; - license = stdenv.lib.licenses.mit; - }) {}; - "postgresql-transactional" = callPackage - ({ mkDerivation, base, monad-control, mtl, postgresql-simple - , stdenv - }: - mkDerivation { - pname = "postgresql-transactional"; - version = "1.1.1"; - sha256 = "f9302a1e134b31f2e9bd243c4fe36a25b3a9a9d6984288be1bc9c29882545ed3"; - libraryHaskellDepends = [ - base monad-control mtl postgresql-simple + executableHaskellDepends = [ + auto-update base base64-bytestring bytestring directory either + hasql hasql-pool hasql-transaction network protolude retry text + time unix wai warp ]; doHaddock = false; doCheck = false; - description = "a transactional monad on top of postgresql-simple"; - license = stdenv.lib.licenses.mit; + homepage = "https://postgrest.org"; + description = "REST API for any Postgres database"; + license = lib.licenses.mit; }) {}; "pptable" = callPackage - ({ mkDerivation, base, boxes, containers, generic-deriving, pretty - , stdenv, syb, vector + ({ mkDerivation, base, boxes, containers, generic-deriving, lib + , pretty, syb, vector }: mkDerivation { pname = "pptable"; @@ -26051,22 +31312,41 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/gdevanla/pptable#readme"; description = "Pretty Print containers in a tabular format"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "pqueue" = callPackage - ({ mkDerivation, base, deepseq, stdenv }: + ({ mkDerivation, base, deepseq, lib }: mkDerivation { pname = "pqueue"; - version = "1.4.1.2"; - sha256 = "d2aaacbe069a5dac61cee677c68eb34d74afa09c59d90d43e2fa07a6c5869fec"; + version = "1.4.1.3"; + sha256 = "57a8d8d86b533e4d3bd3ffb5147d067106aaa5ae9f75fc325fd0a0e62c85e7eb"; libraryHaskellDepends = [ base deepseq ]; doHaddock = false; doCheck = false; description = "Reliable, persistent, fast priority queues"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "prairie" = callPackage + ({ mkDerivation, aeson, base, constraints, containers, lens, lib + , template-haskell, text + }: + mkDerivation { + pname = "prairie"; + version = "0.0.1.0"; + sha256 = "87c7b780e71ac8e63e36be03e644319d7f9b9584804fafa3a17b7f5f26f547d8"; + revision = "2"; + editedCabalFile = "1yp173nnsk875wvqqnr9ifkvj8k7zcjbgvzpkyc0sxkq3nlrjs9q"; + libraryHaskellDepends = [ + aeson base constraints containers lens template-haskell text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/parsonsmatt/prairie#readme"; + description = "A first class record field library"; + license = lib.licenses.bsd3; }) {}; "prefix-units" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "prefix-units"; version = "0.2.0"; @@ -26076,22 +31356,22 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/iustin/prefix-units"; description = "A basic library for SI/binary prefix units"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "prelude-compat" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "prelude-compat"; - version = "0.0.0.1"; - sha256 = "7bdc875d5b7265a87f06866dc00da69edcd4ae36ea9687c8c6e643833ffb40d4"; + version = "0.0.0.2"; + sha256 = "c1250f8e9a9f134f89292a31067958dc7eec2871abc1e7631a0bf3324b0360d7"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; description = "Provide Prelude and Data.List with fixed content across GHC versions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "prelude-safeenum" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "prelude-safeenum"; version = "0.1.1.2"; @@ -26101,23 +31381,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://code.haskell.org/~wren/"; description = "A redefinition of the Prelude's Enum class in order to render it safe"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "present" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: - mkDerivation { - pname = "present"; - version = "4.1.0"; - sha256 = "bae8b334817a31572cc0e771f40e89b976e72b2b55d0955e4e198502dd8a427b"; - libraryHaskellDepends = [ base template-haskell ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/chrisdone/present"; - description = "Make presentations for data types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pretty-class" = callPackage - ({ mkDerivation, base, pretty, stdenv }: + ({ mkDerivation, base, lib, pretty }: mkDerivation { pname = "pretty-class"; version = "1.0.1.1"; @@ -26127,28 +31394,54 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/ddssff/pretty-class"; description = "Pretty printing class similar to Show"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "pretty-diff" = callPackage + ({ mkDerivation, base, data-default, Diff, lib, text }: + mkDerivation { + pname = "pretty-diff"; + version = "0.4.0.3"; + sha256 = "f49d8f26e959f81b62f2a00b5368ffe884ee572ec708eab3f4c695545bc2fa63"; + libraryHaskellDepends = [ base data-default Diff text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/stoeffel/pretty-diff#readme"; + description = "Pretty printing a diff of two values"; + license = lib.licenses.bsd3; }) {}; "pretty-hex" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "pretty-hex"; - version = "1.0"; - sha256 = "ff9a5f2023d6a4454f06cc395726b4cac3f9d0ea03759b14ccf7d62df79e9c7a"; + version = "1.1"; + sha256 = "27c78f299151a9a844f4a2c0f629fb99160901e78f78a688cb088bd532501731"; libraryHaskellDepends = [ base bytestring ]; doHaddock = false; doCheck = false; description = "A library for hex dumps of ByteStrings"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "pretty-relative-time" = callPackage + ({ mkDerivation, base, lib, time, validity, validity-time }: + mkDerivation { + pname = "pretty-relative-time"; + version = "0.2.0.0"; + sha256 = "ade414859cca68f71c07f9148e55cb7117ac3b20987d9c18966b09d9815e879f"; + libraryHaskellDepends = [ base time validity validity-time ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/pretty-relative-time#readme"; + description = "Pretty relative time"; + license = lib.licenses.mit; }) {}; "pretty-show" = callPackage ({ mkDerivation, array, base, filepath, ghc-prim, happy - , haskell-lexer, pretty, stdenv, text + , haskell-lexer, lib, pretty, text }: mkDerivation { pname = "pretty-show"; - version = "1.9.5"; - sha256 = "b095bebb79951d2e25a543a591844fb638165672d7b95d325844611297ba423f"; + version = "1.10"; + sha256 = "307f9086e0b063d439dc4f513e36a145e8a57f23de448aefae2a6c00f6da6fd2"; isLibrary = true; isExecutable = true; enableSeparateDataOutput = true; @@ -26161,56 +31454,63 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://wiki.github.com/yav/pretty-show"; description = "Tools for working with derived `Show` instances and generic inspection of values"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "pretty-simple" = callPackage - ({ mkDerivation, ansi-terminal, base, mtl, stdenv, text - , transformers + ({ mkDerivation, base, Cabal, cabal-doctest, containers, lib, mtl + , prettyprinter, prettyprinter-ansi-terminal, text, transformers }: mkDerivation { pname = "pretty-simple"; - version = "2.2.0.1"; - sha256 = "18ab80e80593063b11aa85c117e12253ec5dc438b1d342822ea1c25886485173"; + version = "4.0.0.0"; + sha256 = "dc5743f6e32d0e0570fe2ea303a6965ea3d945a84ee43ead734fd04a0aea3beb"; isLibrary = true; isExecutable = true; + setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ - ansi-terminal base mtl text transformers + base containers mtl prettyprinter prettyprinter-ansi-terminal text + transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/cdepillabout/pretty-simple"; description = "pretty printer for data types with a 'Show' instance"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pretty-sop" = callPackage - ({ mkDerivation, base, generics-sop, pretty-show, stdenv }: + ({ mkDerivation, base, generics-sop, lib, pretty-show }: mkDerivation { pname = "pretty-sop"; - version = "0.2.0.2"; - sha256 = "d64ff28d14360f782dc3ffaec16497015ef9ffc91b2c1cf234274cde9f2d3274"; - revision = "2"; - editedCabalFile = "04hzf2ajlnh3ynk72xr5s396v8y0d8fkr4pf11nqss7yf60dkxwi"; + version = "0.2.0.3"; + sha256 = "bedb878698d798f4d4367fd2fd8f6c3a69cb33e41c17364274233f3c175f7e83"; + revision = "1"; + editedCabalFile = "04gr1aaqaq347rv5vqh93qcnbc53y55hrds73js5329z2j1gbmng"; libraryHaskellDepends = [ base generics-sop pretty-show ]; doHaddock = false; doCheck = false; description = "A generic pretty-printer using generics-sop"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "pretty-types" = callPackage - ({ mkDerivation, base, mtl, stdenv, tagged }: + "pretty-terminal" = callPackage + ({ mkDerivation, base, lib, text }: mkDerivation { - pname = "pretty-types"; - version = "0.2.3.1"; - sha256 = "e56c49d1099aaeafe0b982ef9e60cb7194fd987c4b659a8d7bcde380d3b8784f"; - libraryHaskellDepends = [ base mtl tagged ]; + pname = "pretty-terminal"; + version = "0.1.0.0"; + sha256 = "8e76f74c84fc7039845b8915dbe91e852673ca17047871c304fc0b491eaf2567"; + revision = "1"; + editedCabalFile = "1ncs74ycnpkcqazhz3iqi2cx9nr88vg8i457ynmf7a5jxf35s4z9"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base text ]; + executableHaskellDepends = [ base text ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/sheyll/pretty-types#readme"; - description = "A small pretty printing DSL for complex types"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/loganmac/pretty-terminal#readme"; + description = "Styling and coloring terminal output with ANSI escape sequences"; + license = lib.licenses.bsd3; }) {}; "prettyclass" = callPackage - ({ mkDerivation, base, pretty, stdenv }: + ({ mkDerivation, base, lib, pretty }: mkDerivation { pname = "prettyclass"; version = "1.0.0.0"; @@ -26219,14 +31519,14 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Pretty printing class similar to Show"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "prettyprinter" = callPackage - ({ mkDerivation, base, stdenv, text }: + ({ mkDerivation, base, lib, text }: mkDerivation { pname = "prettyprinter"; - version = "1.2.1"; - sha256 = "e7653e0ba87cc06553a50e4780dde81c5dd156196c0199511d03d972e5517fcf"; + version = "1.7.0"; + sha256 = "591b87ce8a5cff39d66cb1c156c7d27d04de57952f16eb3ce3afe309ac26e0a7"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base text ]; @@ -26234,40 +31534,37 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/quchen/prettyprinter"; description = "A modern, easy to use, well-documented, extensible pretty-printer"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; }) {}; "prettyprinter-ansi-terminal" = callPackage - ({ mkDerivation, ansi-terminal, base, prettyprinter, stdenv, text - }: + ({ mkDerivation, ansi-terminal, base, lib, prettyprinter, text }: mkDerivation { pname = "prettyprinter-ansi-terminal"; - version = "1.1.1.2"; - sha256 = "d3e0b420df2904ae1ef23daf9bbb6de2c1fbbee056b779fc2cebe303cedf4641"; + version = "1.1.2"; + sha256 = "e26b7338b90830a126e210ec164426bd3da7d099a319d1287a40e3efce2a1799"; libraryHaskellDepends = [ ansi-terminal base prettyprinter text ]; doHaddock = false; doCheck = false; homepage = "http://github.com/quchen/prettyprinter"; description = "ANSI terminal backend for the »prettyprinter« package"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; }) {}; "prettyprinter-compat-annotated-wl-pprint" = callPackage - ({ mkDerivation, base, prettyprinter, stdenv, text }: + ({ mkDerivation, base, lib, prettyprinter, text }: mkDerivation { pname = "prettyprinter-compat-annotated-wl-pprint"; - version = "1"; - sha256 = "2c259bac999d75b071a077f218a433c070783e9f40b67796e31a776fefbaf57e"; - revision = "3"; - editedCabalFile = "0vzi7id60pfj35xp61akzvfx9x6py45r5b8343i48ljpir91rvgw"; + version = "1.1"; + sha256 = "76c9266a980a70f9646726ff3a01b001c433728a732d17c2819546bcf8fe935e"; libraryHaskellDepends = [ base prettyprinter text ]; doHaddock = false; doCheck = false; homepage = "http://github.com/quchen/prettyprinter"; - description = "Prettyprinter compatibility module for previous users of the annotated-wl-pprint package"; - license = stdenv.lib.licenses.bsd2; + description = "Drop-in compatibility package to migrate from »annotated-wl-pprint« to »prettyprinter«"; + license = lib.licenses.bsd2; }) {}; "prettyprinter-compat-ansi-wl-pprint" = callPackage - ({ mkDerivation, base, prettyprinter, prettyprinter-ansi-terminal - , stdenv, text + ({ mkDerivation, base, lib, prettyprinter + , prettyprinter-ansi-terminal, text }: mkDerivation { pname = "prettyprinter-compat-ansi-wl-pprint"; @@ -26282,10 +31579,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/quchen/prettyprinter"; description = "Drop-in compatibility package to migrate from »ansi-wl-pprint« to »prettyprinter«"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; }) {}; "prettyprinter-compat-wl-pprint" = callPackage - ({ mkDerivation, base, prettyprinter, stdenv, text }: + ({ mkDerivation, base, lib, prettyprinter, text }: mkDerivation { pname = "prettyprinter-compat-wl-pprint"; version = "1.0.0.1"; @@ -26297,23 +31594,41 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/quchen/prettyprinter"; description = "Prettyprinter compatibility module for previous users of the wl-pprint package"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; + }) {}; + "prettyprinter-convert-ansi-wl-pprint" = callPackage + ({ mkDerivation, ansi-terminal, ansi-wl-pprint, base, lib + , prettyprinter, prettyprinter-ansi-terminal, text + }: + mkDerivation { + pname = "prettyprinter-convert-ansi-wl-pprint"; + version = "1.1.1"; + sha256 = "81307dcf5ad79e82d58c73f2c0ab5ac0b11bfd6b96291c9afec6571fae15ee2d"; + libraryHaskellDepends = [ + ansi-terminal ansi-wl-pprint base prettyprinter + prettyprinter-ansi-terminal text + ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/quchen/prettyprinter"; + description = "Converter from »ansi-wl-pprint« documents to »prettyprinter«-based ones"; + license = lib.licenses.bsd2; }) {}; "prim-uniq" = callPackage - ({ mkDerivation, base, dependent-sum, primitive, stdenv }: + ({ mkDerivation, base, dependent-sum, lib, primitive }: mkDerivation { pname = "prim-uniq"; - version = "0.1.0.1"; - sha256 = "fb059785133fe5ecaa57c6c840192f252c4c5a1a598160d5704ac2a83e895aff"; + version = "0.2"; + sha256 = "bbadfebdc4def5cc8a9db3458df710c45f2b4e72ee5d2e6c42562b77c7a6f2d0"; libraryHaskellDepends = [ base dependent-sum primitive ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/mokus0/prim-uniq"; + homepage = "https://github.com/obsidiansystems/prim-uniq"; description = "Opaque unique identifiers in primitive state monads"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "primes" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "primes"; version = "0.2.1.0"; @@ -26323,32 +31638,105 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/sebfisch/primes"; description = "Efficient, purely functional generation of prime numbers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "primitive" = callPackage - ({ mkDerivation, base, ghc-prim, stdenv, transformers }: + ({ mkDerivation, base, deepseq, lib, transformers }: mkDerivation { pname = "primitive"; - version = "0.6.4.0"; - sha256 = "4cbeaf7924dd79221f327ea101a29bf35c4976dc3319df157ff46ea68e6a0c64"; - revision = "1"; - editedCabalFile = "18a14k1yiam1m4l29rin9a0y53yp3nxvkz358nysld8aqwy2qsjv"; - libraryHaskellDepends = [ base ghc-prim transformers ]; + version = "0.7.1.0"; + sha256 = "6bebecfdf2a57787d9fd5231bfd612b65a92edd7b33a973b2a0f11312b89a3f0"; + revision = "3"; + editedCabalFile = "03vgkhib8w3g0m0zwpz74hsixrf0pvgh6ql0xcy05fpq1kynppi9"; + libraryHaskellDepends = [ base deepseq transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell/primitive"; description = "Primitive memory-related operations"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "primitive-addr" = callPackage + ({ mkDerivation, base, lib, primitive }: + mkDerivation { + pname = "primitive-addr"; + version = "0.1.0.2"; + sha256 = "4281c3a429bc03ab2940d072a6cbd63948bdf2607561456d972ba3ca4db9211b"; + libraryHaskellDepends = [ base primitive ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/andrewthad/primitive-addr"; + description = "Addresses to unmanaged memory"; + license = lib.licenses.bsd3; + }) {}; + "primitive-extras" = callPackage + ({ mkDerivation, base, bytestring, cereal, deferred-folds, focus + , foldl, lib, list-t, primitive, primitive-unlifted, profunctors + , vector + }: + mkDerivation { + pname = "primitive-extras"; + version = "0.10.1"; + sha256 = "ccefe83d06d8305a9b710d60a6852025d0a8079022deac6a10a04f8c49b2b635"; + libraryHaskellDepends = [ + base bytestring cereal deferred-folds focus foldl list-t primitive + primitive-unlifted profunctors vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/metrix-ai/primitive-extras"; + description = "Extras for the \"primitive\" library"; + license = lib.licenses.mit; + }) {}; + "primitive-unaligned" = callPackage + ({ mkDerivation, base, lib, primitive }: + mkDerivation { + pname = "primitive-unaligned"; + version = "0.1.1.1"; + sha256 = "14322b85b3cd12221cc15de323dee8f7cefe65bab647b3d00cfde4969a216ab8"; + libraryHaskellDepends = [ base primitive ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell-primitive/primitive-unaligned"; + description = "Unaligned access to primitive arrays"; + license = lib.licenses.bsd3; + }) {}; + "primitive-unlifted" = callPackage + ({ mkDerivation, base, bytestring, lib, primitive, text-short }: + mkDerivation { + pname = "primitive-unlifted"; + version = "0.1.3.0"; + sha256 = "30f2cf8fe9968217b95a471194341206a6697f611b2af3c8e9a1eca6b362fae0"; + libraryHaskellDepends = [ base bytestring primitive text-short ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell-primitive/primitive-unlifted"; + description = "Primitive GHC types with unlifted types inside"; + license = lib.licenses.bsd3; + }) {}; + "print-console-colors" = callPackage + ({ mkDerivation, ansi-terminal, base, lib }: + mkDerivation { + pname = "print-console-colors"; + version = "0.1.0.0"; + sha256 = "0849e3de1139d5438a5ecfff82e42fe85d59cd430ddb1baf4909ab86eca2a18b"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ ansi-terminal base ]; + executableHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/cdepillabout/print-console-colors#readme"; + description = "Print all ANSI console colors"; + license = lib.licenses.bsd3; }) {}; "probability" = callPackage - ({ mkDerivation, base, containers, random, stdenv, transformers + ({ mkDerivation, base, containers, lib, random, transformers , utility-ht }: mkDerivation { pname = "probability"; - version = "0.2.5.2"; - sha256 = "0f2b8c734eca6b079109948a28d85733543d5cea1dea2d5a1369f52ffc4a3415"; - enableSeparateDataOutput = true; + version = "0.2.7"; + sha256 = "4962b734040280920637ece971f60c789bc0d0ff20559e6293456c9f942789d4"; libraryHaskellDepends = [ base containers random transformers utility-ht ]; @@ -26356,11 +31744,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Probabilistic_Functional_Programming"; description = "Probabilistic Functional Programming"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "process-extras" = callPackage ({ mkDerivation, base, bytestring, data-default, deepseq - , generic-deriving, ListLike, mtl, process, stdenv, text + , generic-deriving, lib, ListLike, mtl, process, text }: mkDerivation { pname = "process-extras"; @@ -26374,10 +31762,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/seereason/process-extras"; description = "Process extras"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "product-isomorphic" = callPackage - ({ mkDerivation, base, stdenv, template-haskell, th-data-compat }: + ({ mkDerivation, base, lib, template-haskell, th-data-compat }: mkDerivation { pname = "product-isomorphic"; version = "0.0.3.3"; @@ -26387,30 +31775,29 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/khibino/haskell-product-isomorphic"; description = "Weaken applicative functor on products"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "product-profunctors" = callPackage - ({ mkDerivation, base, bifunctors, contravariant, profunctors - , stdenv, tagged, template-haskell + ({ mkDerivation, base, bifunctors, contravariant, lib, profunctors + , tagged, template-haskell, th-abstraction }: mkDerivation { pname = "product-profunctors"; - version = "0.10.0.0"; - sha256 = "ad8d7687c2eee4bcd2f3925a74f53d743c9f678b80be2a523221039004d51a68"; - revision = "1"; - editedCabalFile = "17zi38fzg7yf9i5da2hlch6jw2qhmjcvs9wwkhyvra520605mlya"; + version = "0.11.0.2"; + sha256 = "f42477c12fe3c450e78c80173da1094b2b8769c43cbedc359c4144fa0afe018f"; libraryHaskellDepends = [ base bifunctors contravariant profunctors tagged template-haskell + th-abstraction ]; doHaddock = false; doCheck = false; homepage = "https://github.com/tomjaguarpaw/product-profunctors"; description = "product-profunctors"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "profiterole" = callPackage ({ mkDerivation, base, containers, directory, extra, filepath - , ghc-prof, hashable, scientific, stdenv, text + , ghc-prof, hashable, lib, scientific, text }: mkDerivation { pname = "profiterole"; @@ -26426,38 +31813,35 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/ndmitchell/profiterole#readme"; description = "Restructure GHC profile reports"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "profunctors" = callPackage ({ mkDerivation, base, base-orphans, bifunctors, comonad - , contravariant, distributive, semigroups, stdenv, tagged - , transformers + , contravariant, distributive, lib, tagged, transformers }: mkDerivation { pname = "profunctors"; - version = "5.3"; - sha256 = "74632acc5bb76e04ade95e187be432b607da0e863c0e08f3cabafb23d8b4a3b7"; + version = "5.6.2"; + sha256 = "65955d7b50525a4a3bccdab1d982d2ae342897fd38140d5a94b5ef3800d8c92a"; libraryHaskellDepends = [ base base-orphans bifunctors comonad contravariant distributive - semigroups tagged transformers + tagged transformers ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/profunctors/"; description = "Profunctors"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "project-template" = callPackage ({ mkDerivation, base, base64-bytestring, bytestring, conduit - , conduit-extra, containers, directory, filepath, mtl, resourcet - , stdenv, text, transformers + , conduit-extra, containers, directory, filepath, lib, mtl + , resourcet, text, transformers }: mkDerivation { pname = "project-template"; - version = "0.2.0.1"; - sha256 = "eb52496fa7448f5fed445525c05327b31a45282fc1d0a772c7022a9809e7c9dc"; - revision = "1"; - editedCabalFile = "0lq3sqnq0nr0gbvgzp0lqdl3j3mqdmdlf8xsw0j3pjh581xj3k0a"; + version = "0.2.1.0"; + sha256 = "2d99e5bf750e409d8f2daa2a9038ce39c40c310e2e52076549659968461f8429"; libraryHaskellDepends = [ base base64-bytestring bytestring conduit conduit-extra containers directory filepath mtl resourcet text transformers @@ -26466,10 +31850,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/fpco/haskell-ide"; description = "Specify Haskell project templates and generate files"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "projectroot" = callPackage - ({ mkDerivation, base, directory, stdenv }: + ({ mkDerivation, base, directory, lib }: mkDerivation { pname = "projectroot"; version = "0.2.0.1"; @@ -26479,17 +31863,36 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/yamadapc/haskell-projectroot"; description = "Bindings to the projectroot C logic"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "prometheus" = callPackage + ({ mkDerivation, atomic-primops, base, bytestring, containers + , http-client, http-client-tls, http-types, lib, network-uri, text + , transformers, wai, warp + }: + mkDerivation { + pname = "prometheus"; + version = "2.2.2"; + sha256 = "4ec351ed21d2c8f6f3132640a8aeaa7fc62d9f9d0f6ef76861ef3bb2e7642387"; + libraryHaskellDepends = [ + atomic-primops base bytestring containers http-client + http-client-tls http-types network-uri text transformers wai warp + ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/bitnomial/prometheus"; + description = "Prometheus Haskell Client"; + license = lib.licenses.bsd3; }) {}; "prometheus-client" = callPackage ({ mkDerivation, atomic-primops, base, bytestring, clock - , containers, deepseq, exceptions, mtl, stdenv, stm, text + , containers, deepseq, exceptions, lib, mtl, stm, text , transformers, transformers-compat, utf8-string }: mkDerivation { pname = "prometheus-client"; - version = "1.0.0"; - sha256 = "279e415720adb45a0ca67af18029c7b9e2ea0a34ec79b7278ed8e20e135b3344"; + version = "1.0.1"; + sha256 = "36c2c6322bc4f70f635909f32d0965fa6ce5ebbb177482b83f783613e8a7ccbf"; libraryHaskellDepends = [ atomic-primops base bytestring clock containers deepseq exceptions mtl stm text transformers transformers-compat utf8-string @@ -26498,10 +31901,46 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/fimad/prometheus-haskell"; description = "Haskell client library for http://prometheus.io."; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; + }) {}; + "prometheus-metrics-ghc" = callPackage + ({ mkDerivation, base, lib, prometheus-client, text, utf8-string }: + mkDerivation { + pname = "prometheus-metrics-ghc"; + version = "1.0.1.1"; + sha256 = "c9622b98470710b33ce5611ed0b0d19754e3b1905da564517d6acb547d12ca29"; + libraryHaskellDepends = [ + base prometheus-client text utf8-string + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/fimad/prometheus-haskell"; + description = "Metrics exposing GHC runtime information for use with prometheus-client"; + license = lib.licenses.asl20; + }) {}; + "prometheus-wai-middleware" = callPackage + ({ mkDerivation, async, base, clock, containers, http-types, lib + , prometheus, text, wai, warp + }: + mkDerivation { + pname = "prometheus-wai-middleware"; + version = "1.0.1.0"; + sha256 = "595d4a428ebbb81270fe29086d84a5ede326a79f1cf5d293608e07828e2437eb"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base clock containers http-types prometheus text wai + ]; + executableHaskellDepends = [ + async base http-types prometheus wai warp + ]; + doHaddock = false; + doCheck = false; + description = "Instrument a wai application with various metrics"; + license = lib.licenses.bsd3; }) {}; "promises" = callPackage - ({ mkDerivation, base, primitive, stdenv }: + ({ mkDerivation, base, lib, primitive }: mkDerivation { pname = "promises"; version = "0.3"; @@ -26511,10 +31950,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/promises/"; description = "Lazy demand-driven promises"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "prompt" = callPackage - ({ mkDerivation, base, base-compat, mtl, stdenv, transformers + ({ mkDerivation, base, base-compat, lib, mtl, transformers , transformers-compat }: mkDerivation { @@ -26528,169 +31967,53 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mstksg/prompt"; description = "Monad (and transformer) for deferred-effect pure prompt-response queries"; - license = stdenv.lib.licenses.mit; - }) {}; - "proto-lens" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, containers, deepseq - , lens-family, lens-labels, parsec, pretty, stdenv, text - , transformers, void - }: - mkDerivation { - pname = "proto-lens"; - version = "0.4.0.1"; - sha256 = "959d11ee1b863c20b3c2de977df3ab05ab2426413c78c3b7456206dd060adfe7"; - enableSeparateDataOutput = true; - libraryHaskellDepends = [ - attoparsec base bytestring containers deepseq lens-family - lens-labels parsec pretty text transformers void - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/google/proto-lens#readme"; - description = "A lens-based implementation of protocol buffers in Haskell"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "proto-lens-arbitrary" = callPackage - ({ mkDerivation, base, bytestring, containers, lens-family - , proto-lens, QuickCheck, stdenv, text - }: - mkDerivation { - pname = "proto-lens-arbitrary"; - version = "0.1.2.5"; - sha256 = "0d8e201f65d71a2ee6c9414bb341a64df393f693f4d4d1c61d213d91534e8d8d"; - libraryHaskellDepends = [ - base bytestring containers lens-family proto-lens QuickCheck text - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/google/proto-lens#readme"; - description = "Arbitrary instances for proto-lens"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "proto-lens-combinators" = callPackage - ({ mkDerivation, base, Cabal, lens-family, proto-lens - , proto-lens-setup, stdenv, transformers - }: - mkDerivation { - pname = "proto-lens-combinators"; - version = "0.4.0.1"; - sha256 = "6b5264a009d401bc0503447567a9ccdd4fe82d0639e0115b00b9b85eab4c6d36"; - setupHaskellDepends = [ base Cabal proto-lens-setup ]; - libraryHaskellDepends = [ - base lens-family proto-lens transformers - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/google/proto-lens#readme"; - description = "Utilities functions to proto-lens"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "proto-lens-optparse" = callPackage - ({ mkDerivation, base, optparse-applicative, proto-lens, stdenv - , text - }: - mkDerivation { - pname = "proto-lens-optparse"; - version = "0.1.1.4"; - sha256 = "f053140fddc73b7450f897536c0da196d6236b353ba5ed029c9e3db5b864c5b6"; - libraryHaskellDepends = [ - base optparse-applicative proto-lens text - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/google/proto-lens#readme"; - description = "Adapting proto-lens to optparse-applicative ReadMs"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "proto-lens-protobuf-types" = callPackage - ({ mkDerivation, base, Cabal, lens-labels, proto-lens - , proto-lens-runtime, proto-lens-setup, protobuf, stdenv, text - }: - mkDerivation { - pname = "proto-lens-protobuf-types"; - version = "0.4.0.1"; - sha256 = "2a475e0b1271ada78df17a39febdba813ffacdd3594bb72d346391eb2f412224"; - setupHaskellDepends = [ base Cabal proto-lens-setup ]; - libraryHaskellDepends = [ - base lens-labels proto-lens proto-lens-runtime text - ]; - libraryToolDepends = [ protobuf ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/google/proto-lens#readme"; - description = "Basic protocol buffer message types"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "proto-lens-protoc" = callPackage - ({ mkDerivation, base, bytestring, containers, filepath - , haskell-src-exts, lens-family, pretty, proto-lens, protobuf - , stdenv, text - }: - mkDerivation { - pname = "proto-lens-protoc"; - version = "0.4.0.2"; - sha256 = "b5daf9d6e31edf9a75e5300c1095dcd091f91bff3bc05a04b49e6141d8d96bcf"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - base containers filepath haskell-src-exts lens-family pretty - proto-lens text - ]; - libraryToolDepends = [ protobuf ]; - executableHaskellDepends = [ - base bytestring containers lens-family proto-lens text - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/google/proto-lens#readme"; - description = "Protocol buffer compiler for the proto-lens library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; - "proto-lens-runtime" = callPackage - ({ mkDerivation, base, bytestring, containers, deepseq, filepath - , lens-family, lens-labels, proto-lens, stdenv, text + "prospect" = callPackage + ({ mkDerivation, base, deepseq, free, kan-extensions, lib, mtl + , transformers }: mkDerivation { - pname = "proto-lens-runtime"; - version = "0.4.0.2"; - sha256 = "591356bda042e52e8f1239f49c40c679698340eea3697356b11624f48b8fcbcc"; + pname = "prospect"; + version = "0.1.0.0"; + sha256 = "6ffae759fb5d81786342686c5544601a6bbaa74a7ca7f7c1a3ab4ebbc7846de7"; libraryHaskellDepends = [ - base bytestring containers deepseq filepath lens-family lens-labels - proto-lens text + base deepseq free kan-extensions mtl transformers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/google/proto-lens#readme"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/isovector/prospect#readme"; + description = "Explore continuations with trepidation"; + license = lib.licenses.bsd3; }) {}; - "proto-lens-setup" = callPackage - ({ mkDerivation, base, bytestring, Cabal, containers, deepseq - , directory, filepath, process, proto-lens-protoc, stdenv - , temporary, text + "proto3-wire" = callPackage + ({ mkDerivation, base, bytestring, cereal, containers, deepseq + , ghc-prim, hashable, lib, parameterized, primitive, QuickCheck + , safe, text, transformers, unordered-containers, vector }: mkDerivation { - pname = "proto-lens-setup"; - version = "0.4.0.1"; - sha256 = "5762ce4e02ae0bf9272ffbca8b417a430f3bc9a32036504f3940c0287e9114f5"; + pname = "proto3-wire"; + version = "1.2.2"; + sha256 = "8d409536a89a0187f0576711966d2ef45d43acab7b6a3a1c5ee12f6d01adbfb9"; libraryHaskellDepends = [ - base bytestring Cabal containers deepseq directory filepath process - proto-lens-protoc temporary text + base bytestring cereal containers deepseq ghc-prim hashable + parameterized primitive QuickCheck safe text transformers + unordered-containers vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/google/proto-lens#readme"; - description = "Cabal support for codegen with proto-lens"; - license = stdenv.lib.licenses.bsd3; + description = "A low-level implementation of the Protocol Buffers (version 3) wire format"; + license = lib.licenses.asl20; }) {}; "protobuf" = callPackage ({ mkDerivation, base, base-orphans, bytestring, cereal - , data-binary-ieee754, deepseq, mtl, stdenv, text + , data-binary-ieee754, deepseq, lib, mtl, text , unordered-containers }: mkDerivation { pname = "protobuf"; - version = "0.2.1.2"; - sha256 = "b3c871918a665f0543fde247ab8af61c4fc451103140d34bf652c0d5fc4d17de"; + version = "0.2.1.3"; + sha256 = "a9fbff8d94e97a95ed8d959b5958e4633bd79d10df489764a36c160a91cb29f5"; libraryHaskellDepends = [ base base-orphans bytestring cereal data-binary-ieee754 deepseq mtl text unordered-containers @@ -26699,12 +32022,12 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/alphaHeavy/protobuf"; description = "Google Protocol Buffers via GHC.Generics"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "protobuf-simple" = callPackage ({ mkDerivation, base, binary, bytestring, containers - , data-binary-ieee754, directory, filepath, mtl, parsec, split - , stdenv, text + , data-binary-ieee754, directory, filepath, lib, mtl, parsec, split + , text }: mkDerivation { pname = "protobuf-simple"; @@ -26722,17 +32045,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/sru-systems/protobuf-simple"; description = "Simple Protocol Buffers library (proto2)"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "protocol-buffers" = callPackage ({ mkDerivation, aeson, array, base, base16-bytestring, binary - , bytestring, containers, directory, filepath, mtl, parsec, stdenv + , bytestring, containers, directory, filepath, lib, mtl, parsec , syb, text, utf8-string, vector }: mkDerivation { pname = "protocol-buffers"; - version = "2.4.12"; - sha256 = "8fdcfd0017376db8cc519679344392891abfa4408de809a5c52b10091b9e3b7c"; + version = "2.4.17"; + sha256 = "eb4bb2e818ce436057fab080ebfafcb8ad736c52407ed74d4b218c345d0ffe08"; libraryHaskellDepends = [ aeson array base base16-bytestring binary bytestring containers directory filepath mtl parsec syb text utf8-string vector @@ -26741,16 +32064,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/k-bx/protocol-buffers"; description = "Parse Google Protocol Buffer specifications"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "protocol-buffers-descriptor" = callPackage - ({ mkDerivation, base, bytestring, containers, protocol-buffers - , stdenv + ({ mkDerivation, base, bytestring, containers, lib + , protocol-buffers }: mkDerivation { pname = "protocol-buffers-descriptor"; - version = "2.4.12"; - sha256 = "96b14bf9e149cf7a2ea06ddbe147d237101a1a37bf9a5375ee078642df0d8c40"; + version = "2.4.17"; + sha256 = "2aca3da8793b34a85736550a096fc412cae24745aa00e268d5887d98ce4639b6"; + revision = "1"; + editedCabalFile = "0zin8qqvb1hg5kq2s17rkik55pjnws556xflg76x1xrqkyivhqlg"; enableSeparateDataOutput = true; libraryHaskellDepends = [ base bytestring containers protocol-buffers @@ -26759,11 +32084,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/k-bx/protocol-buffers"; description = "Text.DescriptorProto.Options and code generated from the Google Protocol Buffer specification"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "protocol-radius" = callPackage ({ mkDerivation, base, bytestring, cereal, containers, cryptonite - , dlist, memory, stdenv, template-haskell, text, transformers + , dlist, lib, memory, template-haskell, text, transformers }: mkDerivation { pname = "protocol-radius"; @@ -26776,17 +32101,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "parser and printer for radius protocol packet"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "protocol-radius-test" = callPackage - ({ mkDerivation, base, bytestring, cereal, containers - , protocol-radius, QuickCheck, quickcheck-simple, stdenv - , transformers + ({ mkDerivation, base, bytestring, cereal, containers, lib + , protocol-radius, QuickCheck, quickcheck-simple, transformers }: mkDerivation { pname = "protocol-radius-test"; - version = "0.0.1.0"; - sha256 = "b5cc9a15e7910ecb449d3bbb142b809fa34bee2079e772ca63d4bb975a41ada0"; + version = "0.1.0.1"; + sha256 = "f51eb0bc2921036cc924b1e0ae42f8fb2488907c80b7bcff35461db913b1d792"; libraryHaskellDepends = [ base bytestring cereal containers protocol-radius QuickCheck quickcheck-simple transformers @@ -26794,17 +32118,19 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "testsuit of protocol-radius haskell package"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "protolude" = callPackage ({ mkDerivation, array, async, base, bytestring, containers - , deepseq, ghc-prim, hashable, mtl, mtl-compat, stdenv, stm, text + , deepseq, ghc-prim, hashable, lib, mtl, mtl-compat, stm, text , transformers, transformers-compat }: mkDerivation { pname = "protolude"; - version = "0.2.3"; - sha256 = "d23d39b5088f1656649c8e42fc86a20e48799d38f79d162fb38bd50d7ef7f37f"; + version = "0.3.0"; + sha256 = "4083385a9e03fab9201f63ce198b9ced3fbc1c50d6d42574db5e36c757bedcac"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ array async base bytestring containers deepseq ghc-prim hashable mtl mtl-compat stm text transformers transformers-compat @@ -26813,72 +32139,77 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/sdiehl/protolude"; description = "A small prelude"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "proxied" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "proxied"; - version = "0.3"; - sha256 = "534d4d425f2834b39689e2af301bd5ff81d1619e65664a5efd797a0c88dbeb26"; + version = "0.3.1"; + sha256 = "996894e00af70c715a208a09824a38c001963762f3715cecec8ac4f2fef6ac51"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/RyanGlScott/proxied"; description = "Make functions consume Proxy instead of undefined"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "psql-helpers" = callPackage - ({ mkDerivation, base, postgresql-simple, stdenv }: - mkDerivation { - pname = "psql-helpers"; - version = "0.1.0.0"; - sha256 = "f13ca642072477d3ab0246c514e3fc78e0c5cb419345240fbad994ed2a3219f4"; - libraryHaskellDepends = [ base postgresql-simple ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/agrafix/psql-helpers#readme"; - description = "A small collection of helper functions to generate postgresql queries"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.bsd3; }) {}; "psqueues" = callPackage - ({ mkDerivation, base, deepseq, ghc-prim, hashable, stdenv }: + ({ mkDerivation, base, deepseq, ghc-prim, hashable, lib }: mkDerivation { pname = "psqueues"; - version = "0.2.7.1"; - sha256 = "047e42ecd50d09fef99d1db9f8b1e511b64ea4b41afc435ad5fdd373d2ea8ec1"; + version = "0.2.7.2"; + sha256 = "26263b555d943f9b18bbebda6a090848fdba3c1b403a9b7c848f6bac99e893f9"; revision = "1"; - editedCabalFile = "0336d9ckixv4n23vy5l3xk0wavfn3z9xk105gig0zv70b3jh3r3y"; + editedCabalFile = "0d0mm3c8x31dasfzp1884r2irkm3c9irvvbahjzfr1bzzxfb7vyv"; libraryHaskellDepends = [ base deepseq ghc-prim hashable ]; doHaddock = false; doCheck = false; description = "Pure priority search queues"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "pure-zlib" = callPackage - ({ mkDerivation, array, base, base-compat, bytestring - , bytestring-builder, containers, fingertree, stdenv - }: + "ptr-poker" = callPackage + ({ mkDerivation, base, bytestring, lib, scientific, text }: mkDerivation { - pname = "pure-zlib"; - version = "0.6.4"; - sha256 = "eb679aecb3fa310d28a31549cf83c29fba6f6e3c78bcdea82c9e22db36dc3017"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - array base base-compat bytestring bytestring-builder containers - fingertree - ]; - executableHaskellDepends = [ base base-compat bytestring ]; + pname = "ptr-poker"; + version = "0.1.1.4"; + sha256 = "6e66f3a648439aa9940de6f2f7ba00bf0578ed6daf16f4369a21bedc631b2bbd"; + libraryHaskellDepends = [ base bytestring scientific text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/nikita-volkov/ptr-poker"; + description = "Pointer poking action construction and composition toolkit"; + license = lib.licenses.mit; + }) {}; + "publicsuffix" = callPackage + ({ mkDerivation, base, filepath, lib, template-haskell }: + mkDerivation { + pname = "publicsuffix"; + version = "0.20200526"; + sha256 = "6b55720c121173ae86c2aa20e07c31c56bad9034529a21082f0ac25f499e376a"; + libraryHaskellDepends = [ base filepath template-haskell ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/GaloisInc/pure-zlib"; - description = "A Haskell-only implementation of zlib / DEFLATE"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/wereHamster/publicsuffix-haskell/"; + description = "The publicsuffix list exposed as proper Haskell types"; + license = lib.licenses.mit; }) {}; + "pulse-simple" = callPackage + ({ mkDerivation, base, bytestring, lib, libpulseaudio }: + mkDerivation { + pname = "pulse-simple"; + version = "0.1.14"; + sha256 = "84429d8b05f34be7f34cca59f361ededbc8c82e0c27f4acb8a155750ba6541ab"; + libraryHaskellDepends = [ base bytestring ]; + librarySystemDepends = [ libpulseaudio ]; + doHaddock = false; + doCheck = false; + description = "binding to Simple API of pulseaudio"; + license = lib.licenses.bsd3; + }) {inherit (pkgs) libpulseaudio;}; "pureMD5" = callPackage - ({ mkDerivation, base, binary, bytestring, cereal, crypto-api - , stdenv, tagged + ({ mkDerivation, base, binary, bytestring, cereal, crypto-api, lib + , tagged }: mkDerivation { pname = "pureMD5"; @@ -26890,16 +32221,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A Haskell-only implementation of the MD5 digest (hash) algorithm"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "purescript-bridge" = callPackage ({ mkDerivation, base, containers, directory, filepath - , generic-deriving, lens, mtl, stdenv, text, transformers + , generic-deriving, lens, lib, mtl, text, transformers }: mkDerivation { pname = "purescript-bridge"; - version = "0.13.0.0"; - sha256 = "2b1a6bbc0e1c155b20bb02356821185c7661d15cc8042ddfe12725eef2065149"; + version = "0.14.0.0"; + sha256 = "4391281c089125a5897d8d5bd2d66745e1ba388736365ec4d41331d167ddf4be"; libraryHaskellDepends = [ base containers directory filepath generic-deriving lens mtl text transformers @@ -26907,12 +32238,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Generate PureScript data types from Haskell data types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "pushbullet-types" = callPackage - ({ mkDerivation, aeson, base, http-api-data, microlens - , microlens-th, scientific, stdenv, text, time - , unordered-containers + ({ mkDerivation, aeson, base, http-api-data, lib, microlens + , microlens-th, scientific, text, time, unordered-containers }: mkDerivation { pname = "pushbullet-types"; @@ -26925,30 +32255,45 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Datatypes used by the Pushbullet APIs"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "pusher-http-haskell" = callPackage ({ mkDerivation, aeson, base, base16-bytestring, bytestring - , cryptonite, hashable, http-client, http-types, memory, stdenv - , text, time, transformers, unordered-containers, vector + , cryptonite, hashable, http-client, http-client-tls, http-types + , lib, memory, text, time, unordered-containers }: mkDerivation { pname = "pusher-http-haskell"; - version = "1.5.1.7"; - sha256 = "ec5e08a5695d0ebd0e1624d2fa50bb86f0b2ef8977b84bc942c372483c32e106"; + version = "2.1.0.3"; + sha256 = "ad7ff5e98bbeb0c26db54e01b17ac59d94869fcae93d5e56ea0e17b9ff8a35ed"; libraryHaskellDepends = [ aeson base base16-bytestring bytestring cryptonite hashable - http-client http-types memory text time transformers - unordered-containers vector + http-client http-client-tls http-types memory text time + unordered-containers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/pusher-community/pusher-http-haskell"; - description = "Haskell client library for the Pusher HTTP API"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/WillSewell/pusher-http-haskell"; + description = "Haskell client library for the Pusher Channels HTTP API"; + license = lib.licenses.mit; + }) {}; + "pvar" = callPackage + ({ mkDerivation, base, deepseq, lib, primitive }: + mkDerivation { + pname = "pvar"; + version = "1.0.0.0"; + sha256 = "96a683b532ea7ccda7813e09147a9da65578e9385d8001607dadd19fd0e24838"; + revision = "1"; + editedCabalFile = "0r3r7w9x31pimrzmp5fjabgcx8caxf1g0mk9izksw2wnn1anhjix"; + libraryHaskellDepends = [ base deepseq primitive ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/lehins/pvar#readme"; + description = "Mutable variable with primitive values"; + license = lib.licenses.bsd3; }) {}; "qchas" = callPackage - ({ mkDerivation, base, hmatrix, linear, random, stdenv }: + ({ mkDerivation, base, hmatrix, lib, linear, random }: mkDerivation { pname = "qchas"; version = "1.1.0.1"; @@ -26961,10 +32306,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/ardeleanasm/qchas#readme"; description = "A library for implementing Quantum Algorithms"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "qm-interpolated-string" = callPackage - ({ mkDerivation, base, bytestring, haskell-src-meta, stdenv + ({ mkDerivation, base, bytestring, haskell-src-meta, lib , template-haskell, text }: mkDerivation { @@ -26978,78 +32323,63 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/unclechu/haskell-qm-interpolated-string"; description = "Implementation of interpolated multiline strings"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; - "qnap-decrypt" = callPackage - ({ mkDerivation, base, binary, bytestring, cipher-aes128, conduit - , conduit-extra, crypto-api, directory, filepath - , optparse-applicative, stdenv, streaming-commons, tagged - , utf8-string + "qrcode-core" = callPackage + ({ mkDerivation, base, binary, bytestring, case-insensitive + , containers, dlist, lib, primitive, text, vector }: mkDerivation { - pname = "qnap-decrypt"; - version = "0.3.3"; - sha256 = "66b9a66298a950abe9639c248be8448a43a9afc1a86655148a86bbecbfbf963f"; - isLibrary = true; - isExecutable = true; - enableSeparateDataOutput = true; + pname = "qrcode-core"; + version = "0.9.4"; + sha256 = "c03e9163ea441424cf88c69ab12984766716010010f8055740ea518dc7e932b7"; libraryHaskellDepends = [ - base binary bytestring cipher-aes128 conduit conduit-extra - crypto-api directory streaming-commons tagged utf8-string - ]; - executableHaskellDepends = [ - base binary bytestring cipher-aes128 conduit conduit-extra - crypto-api directory filepath optparse-applicative - streaming-commons tagged utf8-string + base binary bytestring case-insensitive containers dlist primitive + text vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/alexkazik/qnap-decrypt#readme"; - description = "Decrypt files encrypted by QNAP's Hybrid Backup Sync"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/alexkazik/qrcode#readme"; + description = "QR code library in pure Haskell"; + license = lib.licenses.mit; }) {}; - "quadratic-irrational" = callPackage - ({ mkDerivation, arithmoi, base, containers, mtl, stdenv - , transformers + "qrcode-juicypixels" = callPackage + ({ mkDerivation, base, base64-bytestring, bytestring, JuicyPixels + , lib, qrcode-core, text, vector }: mkDerivation { - pname = "quadratic-irrational"; - version = "0.0.6"; - sha256 = "209b70c62e4d3e83fb8a081576b7a0db9d8c3d50a3c7b32a63ed5c3953ec0d0a"; - revision = "1"; - editedCabalFile = "0i7dsl7zm9r7sgfs2cwmic3qbk15lc7kbhjd53vin89p21fh8mzm"; + pname = "qrcode-juicypixels"; + version = "0.8.2"; + sha256 = "6f3870ee5a632c3dfee1920c3769689a240ff8e3b1a2e640a1a2554810883e4e"; libraryHaskellDepends = [ - arithmoi base containers mtl transformers + base base64-bytestring bytestring JuicyPixels qrcode-core text + vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/ion1/quadratic-irrational"; - description = "An implementation of quadratic irrationals"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/alexkazik/qrcode#readme"; + description = "Converts a qrcode-core image to JuicyPixels"; + license = lib.licenses.mit; }) {}; - "quickbench" = callPackage - ({ mkDerivation, base, containers, directory, docopt, pretty-show - , process, safe, split, stdenv, tabular, time + "quadratic-irrational" = callPackage + ({ mkDerivation, arithmoi, base, containers, integer-roots, lib + , transformers }: mkDerivation { - pname = "quickbench"; - version = "1.0"; - sha256 = "8bfe252e50a683346e753db312e9542f8d43256947ab215fcfd24af03787b926"; - isLibrary = true; - isExecutable = true; + pname = "quadratic-irrational"; + version = "0.1.1"; + sha256 = "fa50a1757c2bf5e1045defe220878d86e3db051fe9553f30bc79596ef2d6d386"; libraryHaskellDepends = [ - base containers directory docopt pretty-show process safe split - tabular time + arithmoi base containers integer-roots transformers ]; - executableHaskellDepends = [ base process ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/simonmichael/quickbench#readme"; - description = "quick & easy benchmarking of command-line programs"; - license = "GPL"; + homepage = "https://github.com/ion1/quadratic-irrational"; + description = "An implementation of quadratic irrationals"; + license = lib.licenses.mit; }) {}; "quickcheck-arbitrary-adt" = callPackage - ({ mkDerivation, base, QuickCheck, stdenv }: + ({ mkDerivation, base, lib, QuickCheck }: mkDerivation { pname = "quickcheck-arbitrary-adt"; version = "0.3.1.0"; @@ -27059,10 +32389,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/plow-technologies/quickcheck-arbitrary-adt#readme"; description = "Generic typeclasses for generating arbitrary ADTs"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "quickcheck-assertions" = callPackage - ({ mkDerivation, base, ieee754, pretty-show, QuickCheck, stdenv }: + ({ mkDerivation, base, ieee754, lib, pretty-show, QuickCheck }: mkDerivation { pname = "quickcheck-assertions"; version = "0.3.0"; @@ -27072,32 +32402,84 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/s9gf4ult/quickcheck-assertions"; description = "HUnit like assertions for QuickCheck"; - license = stdenv.lib.licenses.lgpl3; + license = lib.licenses.lgpl3Only; + }) {}; + "quickcheck-classes" = callPackage + ({ mkDerivation, aeson, base, containers, lib, primitive + , primitive-addr, QuickCheck, quickcheck-classes-base + , semigroupoids, semirings, transformers, vector + }: + mkDerivation { + pname = "quickcheck-classes"; + version = "0.6.5.0"; + sha256 = "62e32ad01c194798ebfb1a39ea9c06ccd54bd6d21cf726e9d0fc9db56b093ca6"; + libraryHaskellDepends = [ + aeson base containers primitive primitive-addr QuickCheck + quickcheck-classes-base semigroupoids semirings transformers vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/andrewthad/quickcheck-classes#readme"; + description = "QuickCheck common typeclasses"; + license = lib.licenses.bsd3; + }) {}; + "quickcheck-classes-base" = callPackage + ({ mkDerivation, base, containers, lib, QuickCheck, transformers }: + mkDerivation { + pname = "quickcheck-classes-base"; + version = "0.6.2.0"; + sha256 = "901945e1c442c558d739bc28088a5564f25c4f3615ce7f03b67c5ecc087e8699"; + libraryHaskellDepends = [ + base containers QuickCheck transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/andrewthad/quickcheck-classes#readme"; + description = "QuickCheck common typeclasses from `base`"; + license = lib.licenses.bsd3; + }) {}; + "quickcheck-higherorder" = callPackage + ({ mkDerivation, base, lib, QuickCheck, test-fun }: + mkDerivation { + pname = "quickcheck-higherorder"; + version = "0.1.0.0"; + sha256 = "dcf8c743ffa54ccbcc85e476a8636b33947f9a318f21f94cc4e6499760c867bf"; + revision = "1"; + editedCabalFile = "1xlfpnfbjlihl021b1l6mnl195fcpsjpmdnszf0bfh7q8mrdwr3j"; + libraryHaskellDepends = [ base QuickCheck test-fun ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/Lysxia/quickcheck-higherorder#readme"; + description = "QuickCheck extension for higher-order properties"; + license = lib.licenses.mit; }) {}; "quickcheck-instances" = callPackage - ({ mkDerivation, array, base, base-compat, bytestring - , case-insensitive, containers, hashable, old-time, QuickCheck - , scientific, stdenv, tagged, text, time, transformers - , transformers-compat, unordered-containers, uuid-types, vector + ({ mkDerivation, array, base, bytestring, case-insensitive + , containers, data-fix, hashable, integer-logarithms, lib, old-time + , QuickCheck, scientific, splitmix, strict, tagged, text, these + , time, time-compat, transformers, transformers-compat + , unordered-containers, uuid-types, vector }: mkDerivation { pname = "quickcheck-instances"; - version = "0.3.19"; - sha256 = "57a4aefff05313fb07a651934088d18a584f8bcfeaa02305be65525f12409a56"; + version = "0.3.25.2"; + sha256 = "70ccf54c6553d6a23b4ee48dc02f1e4120cbb9a609e03af073b93541b35a1846"; + revision = "1"; + editedCabalFile = "0pmsq83jzf7gxr59h8j85121n6n0iqbl3smccl9v7n3gkp70kr2q"; libraryHaskellDepends = [ - array base base-compat bytestring case-insensitive containers - hashable old-time QuickCheck scientific tagged text time - transformers transformers-compat unordered-containers uuid-types - vector + array base bytestring case-insensitive containers data-fix hashable + integer-logarithms old-time QuickCheck scientific splitmix strict + tagged text these time time-compat transformers transformers-compat + unordered-containers uuid-types vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/phadej/qc-instances"; + homepage = "https://github.com/haskellari/qc-instances"; description = "Common quickcheck instances"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "quickcheck-io" = callPackage - ({ mkDerivation, base, HUnit, QuickCheck, stdenv }: + ({ mkDerivation, base, HUnit, lib, QuickCheck }: mkDerivation { pname = "quickcheck-io"; version = "0.2.0"; @@ -27107,22 +32489,22 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/hspec/quickcheck-io#readme"; description = "Use HUnit assertions as QuickCheck properties"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "quickcheck-simple" = callPackage - ({ mkDerivation, base, QuickCheck, stdenv }: + ({ mkDerivation, base, lib, QuickCheck }: mkDerivation { pname = "quickcheck-simple"; - version = "0.1.0.4"; - sha256 = "808eb5966a97bd38a3992b280428a0b289ccb46c38397ea8e34661d1e1ec4414"; + version = "0.1.1.1"; + sha256 = "51358328e5d3ea20dcb668e971e07bc7c8451cade47e930c68e3a6718317032a"; libraryHaskellDepends = [ base QuickCheck ]; doHaddock = false; doCheck = false; description = "Test properties and default-mains for QuickCheck"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "quickcheck-special" = callPackage - ({ mkDerivation, base, QuickCheck, special-values, stdenv }: + ({ mkDerivation, base, lib, QuickCheck, special-values }: mkDerivation { pname = "quickcheck-special"; version = "0.1.0.6"; @@ -27134,30 +32516,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/minad/quickcheck-special#readme"; description = "Edge cases and special values for QuickCheck Arbitrary instances"; - license = stdenv.lib.licenses.mit; - }) {}; - "quickcheck-state-machine" = callPackage - ({ mkDerivation, ansi-wl-pprint, base, containers, exceptions - , lifted-async, matrix, monad-control, mtl, pretty-show, QuickCheck - , split, stdenv, stm, tree-diff, vector - }: - mkDerivation { - pname = "quickcheck-state-machine"; - version = "0.4.3"; - sha256 = "3d2b858e43764da5b9d390048e43ef91a4128b75a1921a8a7f68299ba1d43039"; - libraryHaskellDepends = [ - ansi-wl-pprint base containers exceptions lifted-async matrix - monad-control mtl pretty-show QuickCheck split stm tree-diff vector - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/advancedtelematic/quickcheck-state-machine#readme"; - description = "Test monadic programs using state machine based models"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; "quickcheck-text" = callPackage - ({ mkDerivation, base, binary, bytestring, QuickCheck, stdenv, text - }: + ({ mkDerivation, base, binary, bytestring, lib, QuickCheck, text }: mkDerivation { pname = "quickcheck-text"; version = "0.1.2.1"; @@ -27167,10 +32529,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/olorin/quickcheck-text"; description = "Alternative arbitrary instance for Text"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "quickcheck-transformer" = callPackage + ({ mkDerivation, base, lib, QuickCheck, random, transformers }: + mkDerivation { + pname = "quickcheck-transformer"; + version = "0.3.1.1"; + sha256 = "3284beb5990d966055c07323b29cc95df54b1c9e836ccb7e1248a68809b9802a"; + libraryHaskellDepends = [ base QuickCheck random transformers ]; + doHaddock = false; + doCheck = false; + homepage = "http://hub.darcs.net/thielema/quickcheck-transformer/"; + description = "A GenT monad transformer for QuickCheck library"; + license = lib.licenses.mit; }) {}; "quickcheck-unicode" = callPackage - ({ mkDerivation, base, QuickCheck, stdenv }: + ({ mkDerivation, base, lib, QuickCheck }: mkDerivation { pname = "quickcheck-unicode"; version = "1.0.1.0"; @@ -27180,44 +32555,113 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/bos/quickcheck-unicode"; description = "Generator and shrink functions for testing Unicode-related software"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; }) {}; - "rainbow" = callPackage - ({ mkDerivation, base, bytestring, lens-simple, process, stdenv - , text + "quiet" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "quiet"; + version = "0.2"; + sha256 = "118bf67379dce4737619998380e399acba306dc8a086a069d4a01d5694325e4c"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jacobstanley/quiet#readme"; + description = "Generic deriving of Read/Show with no record labels"; + license = lib.licenses.bsd3; + }) {}; + "quote-quot" = callPackage + ({ mkDerivation, base, lib, template-haskell }: + mkDerivation { + pname = "quote-quot"; + version = "0.2.0.0"; + sha256 = "1c742d631e62067f5c595d9f6f8470ff5e2737809ee8b22397b4bd338030486a"; + libraryHaskellDepends = [ base template-haskell ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/Bodigrim/quote-quot#readme"; + description = "Divide without division"; + license = lib.licenses.bsd3; + }) {}; + "radius" = callPackage + ({ mkDerivation, base, binary, bytestring, cryptonite, iproute + , lens, lib, memory }: mkDerivation { - pname = "rainbow"; - version = "0.30.0.2"; - sha256 = "be021eb05bc3e6a00b4fc10e1af941afa0c0a69ab83e5204e8455cfd5c0f5ec7"; + pname = "radius"; + version = "0.7.1.0"; + sha256 = "1413823ed438a220489264b4d5c6a865f98361fbda0163a59ae59f6401f9ede0"; libraryHaskellDepends = [ - base bytestring lens-simple process text + base binary bytestring cryptonite iproute lens memory ]; doHaddock = false; doCheck = false; + homepage = "https://gitlab.com/codemonkeylabs/RADIUS"; + description = "Remote Authentication Dial In User Service (RADIUS)"; + license = lib.licenses.bsd3; + }) {}; + "rainbow" = callPackage + ({ mkDerivation, base, bytestring, lens, lib, terminfo, text }: + mkDerivation { + pname = "rainbow"; + version = "0.34.2.2"; + sha256 = "8e56c1a03a0b2b3e30d67fd7607aa4f93a841e17aa8c4e526ceed464229ba5e7"; + libraryHaskellDepends = [ base bytestring lens terminfo text ]; + doHaddock = false; + doCheck = false; homepage = "https://www.github.com/massysett/rainbow"; description = "Print text to terminal with colors and effects"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "rainbox" = callPackage - ({ mkDerivation, base, bytestring, containers, lens-simple, rainbow - , stdenv, text + ({ mkDerivation, base, bytestring, containers, lens, lib, rainbow + , text }: mkDerivation { pname = "rainbox"; - version = "0.20.0.0"; - sha256 = "937f61d2fbc7b41f065cec9bb9d6550b54346e52b788d30f73ef78cf8545b61f"; + version = "0.26.0.0"; + sha256 = "a19d51036a1e8b0a08ca3629db60e613207d7d2288a0c0791c8c56700948101e"; libraryHaskellDepends = [ - base bytestring containers lens-simple rainbow text + base bytestring containers lens rainbow text ]; doHaddock = false; doCheck = false; homepage = "https://www.github.com/massysett/rainbox"; description = "Two-dimensional box pretty printing, with colors"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "ral" = callPackage + ({ mkDerivation, adjunctions, base, bin, deepseq, distributive, fin + , hashable, indexed-traversable, lib, QuickCheck, semigroupoids + }: + mkDerivation { + pname = "ral"; + version = "0.2"; + sha256 = "7bb8dd47aac3fdae1a59b4ff9090cbd934d90cc056c438f712f47f4232179977"; + libraryHaskellDepends = [ + adjunctions base bin deepseq distributive fin hashable + indexed-traversable QuickCheck semigroupoids + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/phadej/vec"; + description = "Random access lists"; + license = lib.licenses.gpl2Plus; + }) {}; + "rampart" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "rampart"; + version = "1.1.0.3"; + sha256 = "1eac8404ffca6de208648dfeac11b3b7a1bcf7be12b781690ae2323731401624"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + description = "Determine how intervals relate to each other"; + license = lib.licenses.isc; }) {}; "ramus" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "ramus"; version = "0.1.2"; @@ -27227,10 +32671,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/NickSeagull/ramus#readme"; description = "Elm signal system for Haskell"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "rando" = callPackage - ({ mkDerivation, base, stdenv, tf-random, vector }: + ({ mkDerivation, base, lib, tf-random, vector }: mkDerivation { pname = "rando"; version = "0.0.0.4"; @@ -27239,59 +32683,56 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Easy-to-use randomness for livecoding"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; }) {}; "random" = callPackage - ({ mkDerivation, base, stdenv, time }: + ({ mkDerivation, base, bytestring, deepseq, lib, mtl, splitmix }: mkDerivation { pname = "random"; - version = "1.1"; - sha256 = "b718a41057e25a3a71df693ab0fe2263d492e759679b3c2fea6ea33b171d3a5a"; - revision = "1"; - editedCabalFile = "1pv5d7bm2rgap7llp5vjsplrg048gvf0226y0v19gpvdsx7n4rvv"; - libraryHaskellDepends = [ base time ]; + version = "1.2.0"; + sha256 = "e4519cf7c058bfd5bdbe4acc782284acc9e25e74487208619ca83cbcd63fb9de"; + revision = "6"; + editedCabalFile = "1hzfz9b1cxrsya8i53yx145iypaakfsfjix7l8girhx7vbz0cm8r"; + libraryHaskellDepends = [ base bytestring deepseq mtl splitmix ]; doHaddock = false; doCheck = false; - description = "random number library"; - license = stdenv.lib.licenses.bsd3; + description = "Pseudo-random number generation"; + license = lib.licenses.bsd3; }) {}; "random-bytestring" = callPackage - ({ mkDerivation, base, bytestring, mwc-random, pcg-random, stdenv - }: + ({ mkDerivation, base, bytestring, lib, mwc-random, pcg-random }: mkDerivation { pname = "random-bytestring"; - version = "0.1.3.1"; - sha256 = "33a826fd04068902acb62b04cb88c5a0c47e483b88053be9f6de1d64911f0eb4"; - revision = "1"; - editedCabalFile = "0gk5hcx1j06rklfd2cv63kh5dzjk8hr184riam784c7s9zg3s9a4"; + version = "0.1.4"; + sha256 = "920c6feea2e360a96275993191cc89e72784a3787bf4ad7d53eff58e5f209638"; libraryHaskellDepends = [ base bytestring mwc-random pcg-random ]; doHaddock = false; doCheck = false; homepage = "https://www.github.com/larskuhtz/random-bytestring"; description = "Efficient generation of random bytestrings"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "random-fu" = callPackage - ({ mkDerivation, base, erf, log-domain, math-functions, monad-loops - , mtl, random-shuffle, random-source, rvar, stdenv, syb + ({ mkDerivation, base, erf, lib, math-functions, monad-loops, mtl + , random, random-shuffle, random-source, rvar, syb , template-haskell, transformers, vector }: mkDerivation { pname = "random-fu"; - version = "0.2.7.0"; - sha256 = "b6b3a4b3ede34991d26e0447f90b14fa66af61f376fa0aed2e0899fdc879b0c4"; + version = "0.2.7.7"; + sha256 = "8466bcfb5290bdc30a571c91e1eb526c419ea9773bc118996778b516cfc665ca"; libraryHaskellDepends = [ - base erf log-domain math-functions monad-loops mtl random-shuffle + base erf math-functions monad-loops mtl random random-shuffle random-source rvar syb template-haskell transformers vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mokus0/random-fu"; description = "Random number generation"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "random-shuffle" = callPackage - ({ mkDerivation, base, MonadRandom, random, stdenv }: + ({ mkDerivation, base, lib, MonadRandom, random }: mkDerivation { pname = "random-shuffle"; version = "0.0.4"; @@ -27300,30 +32741,30 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Random shuffle implementation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "random-source" = callPackage - ({ mkDerivation, base, flexible-defaults, mersenne-random-pure64 - , mtl, mwc-random, random, stateref, stdenv, syb, template-haskell - , th-extras + ({ mkDerivation, base, flexible-defaults, lib + , mersenne-random-pure64, mtl, mwc-random, primitive, random + , stateref, syb, template-haskell, th-extras }: mkDerivation { pname = "random-source"; - version = "0.3.0.6"; - sha256 = "f3dfec3aef0614ff856abbba018f3bc3446295157895ea09a015737d67205b73"; + version = "0.3.0.11"; + sha256 = "5ba3647d7324f51e8c14a17666dca865c3329daedaa12be2cbba2402415b9853"; libraryHaskellDepends = [ - base flexible-defaults mersenne-random-pure64 mtl mwc-random random - stateref syb template-haskell th-extras + base flexible-defaults mersenne-random-pure64 mtl mwc-random + primitive random stateref syb template-haskell th-extras ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mokus0/random-fu"; description = "Generic basis for random number generators"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "random-tree" = callPackage - ({ mkDerivation, base, containers, lens, MonadRandom, mtl, random - , random-shuffle, stdenv, transformers, tree-fun + ({ mkDerivation, base, containers, lens, lib, MonadRandom, mtl + , random, random-shuffle, transformers, tree-fun }: mkDerivation { pname = "random-tree"; @@ -27336,59 +32777,72 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Create random trees"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; }) {}; "range" = callPackage - ({ mkDerivation, base, free, parsec, stdenv }: + ({ mkDerivation, base, free, lib, parsec }: mkDerivation { pname = "range"; - version = "0.2.1.1"; - sha256 = "ac760a2408d51e40148b93b72d79320f13dfc8a68424d2510b518a49ef87ee8d"; + version = "0.3.0.2"; + sha256 = "13c8f168b584637a5a1a389ef34e986ff10a0fe4f486d320a8fc8949e82a6b4f"; libraryHaskellDepends = [ base free parsec ]; doHaddock = false; doCheck = false; homepage = "https://bitbucket.org/robertmassaioli/range"; description = "An efficient and versatile range library"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "range-set-list" = callPackage - ({ mkDerivation, base, containers, deepseq, hashable, stdenv }: + ({ mkDerivation, base, containers, deepseq, hashable, lib }: mkDerivation { pname = "range-set-list"; - version = "0.1.3"; - sha256 = "e51b393d2c09e3c2b0c21523389a48ce8e6090413abdfff1c623815c76cc96df"; - revision = "1"; - editedCabalFile = "00ddj7if8lcrqf5c882m4slm15sdwcghz7d2fz222c7jcw1ahvdr"; + version = "0.1.3.1"; + sha256 = "12e8d9cb99a2847da32934ed7f44a5acedaa59d8fa19eff0f46aa77921460c55"; + revision = "2"; + editedCabalFile = "08b5zlc2q3nyxxjzzigjbjygvd2001i2w3vslacib3kxm4569n8v"; libraryHaskellDepends = [ base containers deepseq hashable ]; doHaddock = false; doCheck = false; homepage = "https://github.com/phadej/range-set-list#readme"; description = "Memory efficient sets with ranges of elements"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "ranged-list" = callPackage + ({ mkDerivation, base, lib, typecheck-plugin-nat-simple }: + mkDerivation { + pname = "ranged-list"; + version = "0.1.0.0"; + sha256 = "888f6006268a9ce5f8dea1e4c02bb57a5431a6e503d587c4550de5131e400a6c"; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ base typecheck-plugin-nat-simple ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/YoshikuniJujo/ranged-list#readme"; + description = "The list like structure whose length or range of length can be specified"; + license = lib.licenses.bsd3; }) {}; "rank1dynamic" = callPackage - ({ mkDerivation, base, binary, stdenv }: + ({ mkDerivation, base, binary, lib }: mkDerivation { pname = "rank1dynamic"; - version = "0.4.0"; - sha256 = "3c424bfe52b7d4766fd66ea34c204cf920b146455711d8d10d580ca6c175ab1d"; - revision = "1"; - editedCabalFile = "1idh1iz15pzdhrhy19584i9ahz41ijbmf56wbb2wns2kipy6w9lr"; + version = "0.4.1"; + sha256 = "39a0d3e5279abee1724a65d793a7c7e5fc36dea948104ddc4ea884e108e1a2a7"; libraryHaskellDepends = [ base binary ]; doHaddock = false; doCheck = false; homepage = "http://haskell-distributed.github.com"; description = "Like Data.Dynamic/Data.Typeable but with support for rank-1 polymorphic types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "rank2classes" = callPackage - ({ mkDerivation, base, distributive, stdenv, template-haskell - , transformers + ({ mkDerivation, base, Cabal, cabal-doctest, distributive, lib + , template-haskell, transformers }: mkDerivation { pname = "rank2classes"; - version = "1.2"; - sha256 = "57c8359d29b84f9837f99ddf23e4d5a2ee494bcac10b929ddb0d6ed7c9d358e1"; + version = "1.4.1"; + sha256 = "6b12b50fb1d3d61c99bc14afc41ccf22d5066db5239eefddfbbbc96d713facb2"; + setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ base distributive template-haskell transformers ]; @@ -27396,18 +32850,20 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/blamario/grampa/tree/master/rank2classes"; description = "standard type constructor class hierarchy, only with methods of rank 2 types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "rasterific-svg" = callPackage ({ mkDerivation, base, binary, bytestring, containers, directory - , filepath, FontyFruity, JuicyPixels, lens, linear, mtl - , optparse-applicative, primitive, Rasterific, scientific, stdenv - , svg-tree, text, transformers, vector + , filepath, FontyFruity, JuicyPixels, lens, lib, linear, mtl + , optparse-applicative, primitive, Rasterific, scientific, svg-tree + , text, transformers, vector }: mkDerivation { pname = "rasterific-svg"; version = "0.3.3.2"; sha256 = "02db61c98e6e550824e8d9813efe5e97293843e39e1c00e88837061b61a017c4"; + revision = "2"; + editedCabalFile = "1938sp9m0yi7ypxk74bzrbkp9b4yk6hsaqhlhbraf9yb7w61228v"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -27422,73 +32878,106 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "SVG renderer based on Rasterific"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "rate-limit" = callPackage + ({ mkDerivation, base, lib, stm, time, time-units }: + mkDerivation { + pname = "rate-limit"; + version = "1.4.2"; + sha256 = "5552bbf9b669772b88c23b649167d2f0cb9aef1ad99c03127a3b48fff94e617d"; + libraryHaskellDepends = [ base stm time time-units ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/acw/rate-limit"; + description = "A basic library for rate-limiting IO actions"; + license = lib.licenses.bsd3; }) {}; "ratel" = callPackage ({ mkDerivation, aeson, base, bytestring, case-insensitive - , containers, http-client, http-client-tls, http-types, stdenv - , text, uuid + , containers, http-client, http-client-tls, http-types, lib, text + , uuid }: mkDerivation { pname = "ratel"; - version = "1.0.7"; - sha256 = "fc7cd1f9ad297b211ac639cb4c78be9c973bc11a0a01b9b5e5470dcb0b71e6ce"; + version = "1.0.15"; + sha256 = "2282f2f11fb143b9e12fcd9f694fdb222d3277a7efc4d618f71198ea744fe391"; libraryHaskellDepends = [ aeson base bytestring case-insensitive containers http-client http-client-tls http-types text uuid ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/tfausak/ratel#readme"; description = "Notify Honeybadger about exceptions"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "ratel-wai" = callPackage ({ mkDerivation, base, bytestring, case-insensitive, containers - , http-client, ratel, stdenv, wai + , http-client, lib, ratel, wai }: mkDerivation { pname = "ratel-wai"; - version = "1.0.4"; - sha256 = "9528a62b62107b606c9aad9f14f5f5d8e588d22c988fc7e720aa03e2822131b3"; + version = "1.1.5"; + sha256 = "be880cc99c088ec176c0944c868d4f3a0a7b0915fbb2c3754a99491da4d5d929"; libraryHaskellDepends = [ base bytestring case-insensitive containers http-client ratel wai ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/tfausak/ratel-wai#readme"; description = "Notify Honeybadger about exceptions via a WAI middleware"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "rattletrap" = callPackage - ({ mkDerivation, aeson, aeson-pretty, base, binary, binary-bits - , bytestring, containers, filepath, http-client, http-client-tls - , stdenv, template-haskell, text, transformers + "rattle" = callPackage + ({ mkDerivation, async, base, bytestring, cmdargs + , cryptohash-sha256, deepseq, directory, extra, filepath + , filepattern, hashable, heaps, js-dgtable, js-flot, js-jquery, lib + , process, shake, template-haskell, terminal-size, time + , transformers, unix, unordered-containers, utf8-string }: mkDerivation { - pname = "rattletrap"; - version = "6.0.2"; - sha256 = "216295103133cbd4fef5ee81f6d3b84a959dfca90905fbcd835ffd60747804a4"; + pname = "rattle"; + version = "0.2"; + sha256 = "73ad0180c04fda1427b9625e1aa969c6670fb79aa0899a0b520e0dd1a29da3d9"; isLibrary = true; isExecutable = true; + enableSeparateDataOutput = true; libraryHaskellDepends = [ - aeson aeson-pretty base binary binary-bits bytestring containers - filepath http-client http-client-tls template-haskell text - transformers + async base bytestring cryptohash-sha256 deepseq directory extra + filepath filepattern hashable heaps js-dgtable js-flot js-jquery + shake template-haskell terminal-size time transformers unix + unordered-containers utf8-string ]; executableHaskellDepends = [ - aeson aeson-pretty base binary binary-bits bytestring containers - filepath http-client http-client-tls template-haskell text - transformers + base bytestring cmdargs directory extra filepath process shake + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ndmitchell/rattle#readme"; + description = "Forward build system, with caching and speculation"; + license = lib.licenses.bsd3; + }) {}; + "rattletrap" = callPackage + ({ mkDerivation, aeson, aeson-pretty, array, base, bytestring + , containers, filepath, http-client, http-client-tls, lib, text + }: + mkDerivation { + pname = "rattletrap"; + version = "11.1.1"; + sha256 = "43092946095f9e7aa37e897eecf017275e374cb10f8647fd370a2b03456cdd31"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson aeson-pretty array base bytestring containers filepath + http-client http-client-tls text ]; + executableHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/tfausak/rattletrap#readme"; description = "Parse and generate Rocket League replays"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "raw-strings-qq" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { pname = "raw-strings-qq"; version = "1.1"; @@ -27498,10 +32987,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/23Skidoo/raw-strings-qq"; description = "Raw string literals for Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "rawfilepath" = callPackage - ({ mkDerivation, base, bytestring, stdenv, unix }: + ({ mkDerivation, base, bytestring, lib, unix }: mkDerivation { pname = "rawfilepath"; version = "0.2.4"; @@ -27511,11 +33000,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/xtendo-org/rawfilepath#readme"; description = "Use RawFilePath instead of FilePath"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; }) {}; "rawstring-qm" = callPackage - ({ mkDerivation, base, bytestring, stdenv, template-haskell, text - }: + ({ mkDerivation, base, bytestring, lib, template-haskell, text }: mkDerivation { pname = "rawstring-qm"; version = "0.2.3.0"; @@ -27525,19 +33013,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/tolysz/rawstring-qm"; description = "Simple raw string quotation and dictionary interpolation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "rcu" = callPackage - ({ mkDerivation, atomic-primops, base, Cabal, cabal-doctest, fail - , ghc-prim, parallel, primitive, stdenv, transformers + ({ mkDerivation, atomic-primops, base, fail, ghc-prim, lib + , parallel, primitive, transformers }: mkDerivation { pname = "rcu"; - version = "0.2.3"; - sha256 = "e10cbd0bd02adf8bfa7c709b66b5fc611c6765f8d97dc54a02b9963f08f2809f"; + version = "0.2.5"; + sha256 = "f4b095f555f242eb08805df8055d89b971ea31f2695315f18f4db2e2bb794cdc"; isLibrary = true; isExecutable = true; - setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ atomic-primops base fail ghc-prim parallel primitive transformers ]; @@ -27546,10 +33033,40 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/rcu/"; description = "Read-Copy-Update for Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "rdf" = callPackage + ({ mkDerivation, attoparsec, base, bytestring, deepseq, dlist, fgl + , lib, text, transformers + }: + mkDerivation { + pname = "rdf"; + version = "0.1.0.5"; + sha256 = "da9442a8df022d0acd755c18b408a94d5e63ab2eb4330fed1d6dc8e692af36cb"; + libraryHaskellDepends = [ + attoparsec base bytestring deepseq dlist fgl text transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/traviswhitaker/rdf"; + description = "Representation and Incremental Processing of RDF Data"; + license = lib.licenses.mit; + }) {}; + "rdtsc" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "rdtsc"; + version = "1.3.0.1"; + sha256 = "54c9a925f68d6c60b405e92f9d3bd9ebfc25cce0c72d2313a6c7e1b7cc2ed950"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/mgrabmueller/rdtsc"; + description = "Binding for the rdtsc machine instruction"; + license = lib.licenses.bsd3; }) {}; "re2" = callPackage - ({ mkDerivation, base, bytestring, re2, stdenv, vector }: + ({ mkDerivation, base, bytestring, lib, re2, vector }: mkDerivation { pname = "re2"; version = "0.3"; @@ -27560,10 +33077,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/rblaze/haskell-re2#readme"; description = "Bindings to the re2 regular expression library"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {inherit (pkgs) re2;}; "read-editor" = callPackage - ({ mkDerivation, base, directory, process, stdenv }: + ({ mkDerivation, base, directory, lib, process }: mkDerivation { pname = "read-editor"; version = "0.1.0.2"; @@ -27575,10 +33092,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/yamadapc/haskell-read-editor"; description = "Opens a temporary file on the system's EDITOR and returns the resulting edits"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "read-env-var" = callPackage - ({ mkDerivation, base, exceptions, stdenv, transformers }: + ({ mkDerivation, base, exceptions, lib, transformers }: mkDerivation { pname = "read-env-var"; version = "1.0.0.0"; @@ -27588,10 +33105,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/cdepillabout/read-env-var#readme"; description = "Functions for safely reading environment variables"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "readable" = callPackage - ({ mkDerivation, base, bytestring, stdenv, text }: + ({ mkDerivation, base, bytestring, lib, text }: mkDerivation { pname = "readable"; version = "0.3.1"; @@ -27601,89 +33118,165 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mightybyte/readable"; description = "Reading from Text and ByteString"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "reanimate" = callPackage + ({ mkDerivation, aeson, ansi-terminal, array, attoparsec, base + , base64-bytestring, bytestring, cassava, cereal, colour + , containers, cryptohash-sha256, cubicbezier, directory, filelock + , filepath, fingertree, fsnotify, geojson, hashable, hgeometry + , hgeometry-combinatorial, JuicyPixels, lens, lib, linear, matrix + , mtl, neat-interpolation, network, open-browser + , optparse-applicative, parallel, process, random, random-shuffle + , reanimate-svg, split, temporary, text, time, unix + , unordered-containers, vector, vector-space, websockets, xml + }: + mkDerivation { + pname = "reanimate"; + version = "1.1.4.0"; + sha256 = "a5cc06592584d226cba70f5171f4162d2c6be26373cfded4e186177b6328e63f"; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + aeson ansi-terminal array attoparsec base base64-bytestring + bytestring cassava cereal colour containers cryptohash-sha256 + cubicbezier directory filelock filepath fingertree fsnotify geojson + hashable hgeometry hgeometry-combinatorial JuicyPixels lens linear + matrix mtl neat-interpolation network open-browser + optparse-applicative parallel process random random-shuffle + reanimate-svg split temporary text time unix unordered-containers + vector vector-space websockets xml + ]; + doHaddock = false; + doCheck = false; + homepage = "https://reanimate.github.io"; + description = "Animation library based on SVGs"; + license = lib.licenses.publicDomain; + }) {}; + "reanimate-svg" = callPackage + ({ mkDerivation, attoparsec, base, bytestring, containers + , double-conversion, hashable, JuicyPixels, lens, lib, linear, mtl + , scientific, text, transformers, vector, xml + }: + mkDerivation { + pname = "reanimate-svg"; + version = "0.13.0.1"; + sha256 = "2101eb57fc66361f2bb9b8e6369e20af8c3dc32d251900bd72b8539d29c861c0"; + libraryHaskellDepends = [ + attoparsec base bytestring containers double-conversion hashable + JuicyPixels lens linear mtl scientific text transformers vector xml + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/reanimate/reanimate-svg#readme"; + description = "SVG file loader and serializer"; + license = lib.licenses.bsd3; }) {}; "rebase" = callPackage - ({ mkDerivation, base, base-prelude, bifunctors, bytestring - , containers, contravariant, contravariant-extras, deepseq, dlist - , either, fail, hashable, mtl, profunctors, scientific - , semigroupoids, semigroups, stdenv, stm, text, time, transformers - , unordered-containers, uuid, vector, void + ({ mkDerivation, base, bifunctors, bytestring, comonad, containers + , contravariant, deepseq, dlist, either, hashable, hashable-time + , lib, mtl, profunctors, scientific, selective, semigroupoids, stm + , text, time, transformers, unordered-containers, uuid-types + , vector, vector-instances, void }: mkDerivation { pname = "rebase"; - version = "1.3"; - sha256 = "073aedeef6788525d069b4d4b7e3acd2a0918149a5e439d54ef82f4cf626e109"; - revision = "1"; - editedCabalFile = "1yz51pghns6xanzdnlkagghpzwnkl7wjqnqcp5gs0zs1iywrbl45"; + version = "1.13.0.1"; + sha256 = "47a4530019aa0828965d1f377f2f8217c3475f4fe99eb4246148581014dc016a"; libraryHaskellDepends = [ - base base-prelude bifunctors bytestring containers contravariant - contravariant-extras deepseq dlist either fail hashable mtl - profunctors scientific semigroupoids semigroups stm text time - transformers unordered-containers uuid vector void + base bifunctors bytestring comonad containers contravariant deepseq + dlist either hashable hashable-time mtl profunctors scientific + selective semigroupoids stm text time transformers + unordered-containers uuid-types vector vector-instances void ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nikita-volkov/rebase"; description = "A more progressive alternative to the \"base\" package"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "record-dot-preprocessor" = callPackage - ({ mkDerivation, base, extra, filepath, stdenv }: + ({ mkDerivation, base, extra, ghc, lib, uniplate }: mkDerivation { pname = "record-dot-preprocessor"; - version = "0.1.4"; - sha256 = "9dd32e7c89f4ac9480035639c2b17da32b90ad7501c2501843270d67db4c43d6"; - isLibrary = false; + version = "0.2.11"; + sha256 = "ad96d350275ec5704632b60195dc91ec8f67a1dc99d0c8381872ea0c913d53c3"; + isLibrary = true; isExecutable = true; - executableHaskellDepends = [ base extra filepath ]; + libraryHaskellDepends = [ base extra ghc uniplate ]; + executableHaskellDepends = [ base extra ]; doHaddock = false; doCheck = false; homepage = "https://github.com/ndmitchell/record-dot-preprocessor#readme"; description = "Preprocessor to allow record.field syntax"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "record-hasfield" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "record-hasfield"; + version = "1.0"; + sha256 = "523d2f5ffcbc54881fb3318411a095ae4ac6ec48e36cd6aecf90486a89849eca"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ndmitchell/record-hasfield#readme"; + description = "A version of GHC.Records as available in future GHCs."; + license = lib.licenses.bsd3; + }) {}; + "record-wrangler" = callPackage + ({ mkDerivation, base, lib, template-haskell }: + mkDerivation { + pname = "record-wrangler"; + version = "0.1.1.0"; + sha256 = "8cf6105b49c0adb9247b681a174efa46f567e4cb270b658731508939ceaaabd3"; + libraryHaskellDepends = [ base template-haskell ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/lumihq/record-wrangler#readme"; + description = "Alter your records with ease"; + license = lib.licenses.asl20; }) {}; "records-sop" = callPackage - ({ mkDerivation, base, deepseq, generics-sop, ghc-prim, stdenv }: + ({ mkDerivation, base, deepseq, generics-sop, ghc-prim, lib }: mkDerivation { pname = "records-sop"; - version = "0.1.0.2"; - sha256 = "059257b7e81768e0ce4e62f0c7b15fc4976c9903015d8cf6aa330778301bfda0"; - revision = "1"; - editedCabalFile = "082f4dmdvbnv6jq28mrva8clxif366vcbn9m8d1bb8lcf9h3qxjb"; + version = "0.1.1.0"; + sha256 = "b4b99bac23fe396b82f1b6f4df038a7937b15952a233105b83becc9b715e0606"; libraryHaskellDepends = [ base deepseq generics-sop ghc-prim ]; doHaddock = false; doCheck = false; description = "Record subtyping and record utilities with generics-sop"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "recursion-schemes" = callPackage - ({ mkDerivation, base, base-orphans, comonad, free, stdenv - , template-haskell, th-abstraction, transformers + ({ mkDerivation, base, base-orphans, comonad, containers, data-fix + , free, lib, template-haskell, th-abstraction, transformers }: mkDerivation { pname = "recursion-schemes"; - version = "5.1"; - sha256 = "01db11b8eb64b11a9f2b65a4d5422dee351b8991aa3ae04c91a2ed016745f3d2"; + version = "5.2.2.1"; + sha256 = "bee32985de5560ba69ef1503eff041091ddaffd68ba8ad736a8fcd95971f02db"; libraryHaskellDepends = [ - base base-orphans comonad free template-haskell th-abstraction - transformers + base base-orphans comonad containers data-fix free template-haskell + th-abstraction transformers ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/recursion-schemes/"; - description = "Generalized bananas, lenses and barbed wire"; - license = stdenv.lib.licenses.bsd3; + description = "Representing common recursion patterns as higher-order functions"; + license = lib.licenses.bsd2; }) {}; "reducers" = callPackage ({ mkDerivation, array, base, bytestring, containers, fingertree - , hashable, semigroupoids, semigroups, stdenv, text, transformers + , hashable, lib, semigroupoids, semigroups, text, transformers , unordered-containers }: mkDerivation { pname = "reducers"; version = "3.12.3"; sha256 = "7186733767405984c1eda96b18908f458b379f116a1589cd66f4319fe8458e27"; + revision = "2"; + editedCabalFile = "1kd38n9h2hxl09khvkvkhnflgm6rbky1zkw3iazlpb8xk9zkk39s"; libraryHaskellDepends = [ array base bytestring containers fingertree hashable semigroupoids semigroups text transformers unordered-containers @@ -27692,10 +33285,34 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/reducers/"; description = "Semigroups, specialized containers and a general map/reduce framework"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "ref-fd" = callPackage + ({ mkDerivation, base, lib, stm, transformers }: + mkDerivation { + pname = "ref-fd"; + version = "0.5"; + sha256 = "121b5d090fc9038e646d282c391140346851c184305862980bd43bd0bdef64e4"; + libraryHaskellDepends = [ base stm transformers ]; + doHaddock = false; + doCheck = false; + description = "A type class for monads with references using functional dependencies"; + license = lib.licenses.bsd3; + }) {}; + "ref-tf" = callPackage + ({ mkDerivation, base, lib, stm, transformers }: + mkDerivation { + pname = "ref-tf"; + version = "0.5"; + sha256 = "9be4048db432cb7f3ed2291268e11c7182e88f42fc6dce70f41a99758c188e1a"; + libraryHaskellDepends = [ base stm transformers ]; + doHaddock = false; + doCheck = false; + description = "A type class for monads with references using type families"; + license = lib.licenses.bsd3; }) {}; "refact" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "refact"; version = "0.3.0.2"; @@ -27704,138 +33321,182 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Specify refactorings to perform with apply-refact"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "references" = callPackage - ({ mkDerivation, array, base, containers, directory, either - , filepath, instance-control, mtl, stdenv, template-haskell, text - , transformers, uniplate - }: - mkDerivation { - pname = "references"; - version = "0.3.3.1"; - sha256 = "bc07606d36639148374e7a29a67ac489c7a0ed02655311b5d633a144a746c10e"; - libraryHaskellDepends = [ - array base containers directory either filepath instance-control - mtl template-haskell text transformers uniplate - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/lazac/references"; - description = "Selectors for reading and updating data"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "refined" = callPackage - ({ mkDerivation, base, deepseq, exceptions, mtl, prettyprinter - , stdenv, template-haskell, transformers + ({ mkDerivation, aeson, base, bytestring, deepseq, exceptions, lib + , mtl, QuickCheck, template-haskell, text, these-skinny }: mkDerivation { pname = "refined"; - version = "0.3.0.0"; - sha256 = "7acef92eb96ec709133556896c37193d95aad8b1421c9e117d8d5ab3f981cf80"; + version = "0.6.2"; + sha256 = "bf19db8922072ddc1e778c2716a8030ddf36c772e8f14df73e33d169a836def5"; libraryHaskellDepends = [ - base deepseq exceptions mtl prettyprinter template-haskell - transformers + aeson base bytestring deepseq exceptions mtl QuickCheck + template-haskell text these-skinny ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nikita-volkov/refined"; description = "Refinement types with static and runtime checking"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "reflection" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { pname = "reflection"; - version = "2.1.4"; - sha256 = "f22fc478d43a36ec3d6c48c57ec53636c0bf936f3733b9a2b34e1a2e6351c44d"; + version = "2.1.6"; + sha256 = "bf3e14917ebb329a53701a3cce0afe670f20037a0148dbfa5cbfa574ed6ba6cd"; libraryHaskellDepends = [ base template-haskell ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/reflection"; description = "Reifies arbitrary terms into types that can be reflected back into terms"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "reform" = callPackage + ({ mkDerivation, base, containers, lib, mtl, semigroups, text }: + mkDerivation { + pname = "reform"; + version = "0.2.7.4"; + sha256 = "02613b12605bf587cf3b0125e362ad96309545d94001779dda44b215cb978036"; + libraryHaskellDepends = [ base containers mtl semigroups text ]; + doHaddock = false; + doCheck = false; + homepage = "http://www.happstack.com/"; + description = "reform is a type-safe HTML form generation and validation library"; + license = lib.licenses.bsd3; + }) {}; + "reform-blaze" = callPackage + ({ mkDerivation, base, blaze-html, blaze-markup, lib, reform, text + }: + mkDerivation { + pname = "reform-blaze"; + version = "0.2.4.3"; + sha256 = "11bcf127356bf5840a0947ea1058cbf1e08096ab0fc872aa5c1ec7d88e40b2e4"; + libraryHaskellDepends = [ + base blaze-html blaze-markup reform text + ]; + doHaddock = false; + doCheck = false; + homepage = "http://www.happstack.com/"; + description = "Add support for using blaze-html with Reform"; + license = lib.licenses.bsd3; + }) {}; + "reform-hamlet" = callPackage + ({ mkDerivation, base, blaze-markup, lib, reform, shakespeare, text + }: + mkDerivation { + pname = "reform-hamlet"; + version = "0.0.5.3"; + sha256 = "512729389fc3eec118a8079486eb2319e1e8eaecdeecafdd6b36205373ce3466"; + libraryHaskellDepends = [ + base blaze-markup reform shakespeare text + ]; + doHaddock = false; + doCheck = false; + homepage = "http://www.happstack.com/"; + description = "Add support for using Hamlet with Reform"; + license = lib.licenses.bsd3; + }) {}; + "reform-happstack" = callPackage + ({ mkDerivation, base, bytestring, happstack-server, lib, mtl + , random, reform, text, utf8-string + }: + mkDerivation { + pname = "reform-happstack"; + version = "0.2.5.4"; + sha256 = "e630c760b13ecca39ee51ce441c36b1a9e7dce09caeedcf33618e46d409276f6"; + libraryHaskellDepends = [ + base bytestring happstack-server mtl random reform text utf8-string + ]; + doHaddock = false; + doCheck = false; + homepage = "http://www.happstack.com/"; + description = "Happstack support for reform"; + license = lib.licenses.bsd3; }) {}; "regex" = callPackage ({ mkDerivation, array, base, base-compat, bytestring, containers - , hashable, regex-base, regex-pcre-builtin, regex-tdfa - , regex-tdfa-text, stdenv, template-haskell, text, time - , time-locale-compat, transformers, unordered-containers - , utf8-string + , hashable, lib, regex-base, regex-pcre-builtin, regex-tdfa + , template-haskell, text, time, time-locale-compat, transformers + , unordered-containers, utf8-string }: mkDerivation { pname = "regex"; - version = "1.0.2.0"; - sha256 = "aacd9b91e0598931745db5a3eea1cdfd6edf3b1e18ceb288c82eb8088b005fb8"; + version = "1.1.0.0"; + sha256 = "1d291cd8c7668899bd606b35c94e2188e2858b2944ff571abf058ec98a7f1d0a"; libraryHaskellDepends = [ array base base-compat bytestring containers hashable regex-base - regex-pcre-builtin regex-tdfa regex-tdfa-text template-haskell text - time time-locale-compat transformers unordered-containers - utf8-string + regex-pcre-builtin regex-tdfa template-haskell text time + time-locale-compat transformers unordered-containers utf8-string ]; doHaddock = false; doCheck = false; homepage = "http://regex.uk"; description = "Toolkit for regex-base"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "regex-applicative" = callPackage - ({ mkDerivation, base, containers, stdenv, transformers }: + ({ mkDerivation, base, containers, filtrable, lib, transformers }: mkDerivation { pname = "regex-applicative"; - version = "0.3.3"; - sha256 = "6659a2cc1c8137d77ef57f75027723b075d473354d935233d98b1ae1b03c3be6"; - libraryHaskellDepends = [ base containers transformers ]; + version = "0.3.4"; + sha256 = "1769a479c3ff953bc5a99a89e5648a6f01c5ff54fc9a09acceb9e029e2352636"; + libraryHaskellDepends = [ base containers filtrable transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/feuerbach/regex-applicative"; description = "Regex-based parsing with applicative interface"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "regex-applicative-text" = callPackage - ({ mkDerivation, base, regex-applicative, stdenv, text }: + ({ mkDerivation, base, lib, regex-applicative, text }: mkDerivation { pname = "regex-applicative-text"; version = "0.1.0.1"; sha256 = "b093051f80865d257da2ded8ad1b566927b01b3d2f86d41da2ffee4a26c4e2d9"; - revision = "3"; - editedCabalFile = "1h911harqgfgkhdr22cndj2fdsl48sqhn8q0akgjngpf3p8z0bvv"; + revision = "5"; + editedCabalFile = "1jgmhqhlhj9zhxwikmhiq71fj1900iqiyg6r9l5y7xjk7arwscmi"; libraryHaskellDepends = [ base regex-applicative text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/phadej/regex-applicative-text#readme"; description = "regex-applicative on text"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "regex-base" = callPackage - ({ mkDerivation, array, base, bytestring, containers, mtl, stdenv + ({ mkDerivation, array, base, bytestring, containers, lib, mtl + , text }: mkDerivation { pname = "regex-base"; - version = "0.93.2"; - sha256 = "20dc5713a16f3d5e2e6d056b4beb9cfdc4368cd09fd56f47414c847705243278"; - libraryHaskellDepends = [ array base bytestring containers mtl ]; + version = "0.94.0.1"; + sha256 = "71b1d96fff201f31fe8cd4532f056aca03a21cd486890256dc3007dd73adedd9"; + libraryHaskellDepends = [ + array base bytestring containers mtl text + ]; doHaddock = false; doCheck = false; - homepage = "http://sourceforge.net/projects/lazy-regex"; - description = "Replaces/Enhances Text.Regex"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://wiki.haskell.org/Regular_expressions"; + description = "Common \"Text.Regex.*\" API for Regex matching"; + license = lib.licenses.bsd3; }) {}; "regex-compat" = callPackage - ({ mkDerivation, array, base, regex-base, regex-posix, stdenv }: + ({ mkDerivation, array, base, lib, regex-base, regex-posix }: mkDerivation { pname = "regex-compat"; - version = "0.95.1"; - sha256 = "d57cb1a5a4d66753b18eaa37a1621246f660472243b001894f970037548d953b"; + version = "0.95.2.1"; + sha256 = "8f7b386c72fd605a292edfb809b8620245b4a3ab7af192ad79e36778596e7947"; libraryHaskellDepends = [ array base regex-base regex-posix ]; doHaddock = false; doCheck = false; - homepage = "http://sourceforge.net/projects/lazy-regex"; - description = "Replaces/Enhances Text.Regex"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://wiki.haskell.org/Regular_expressions"; + description = "Replaces/enhances \"Text.Regex\""; + license = lib.licenses.bsd3; }) {}; "regex-compat-tdfa" = callPackage - ({ mkDerivation, array, base, regex-base, regex-tdfa, stdenv }: + ({ mkDerivation, array, base, lib, regex-base, regex-tdfa }: mkDerivation { pname = "regex-compat-tdfa"; version = "0.95.1.4"; @@ -27845,147 +33506,119 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://hub.darcs.net/shelarcy/regex-compat-tdfa"; description = "Unicode Support version of Text.Regex, using regex-tdfa"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "regex-pcre" = callPackage - ({ mkDerivation, array, base, bytestring, containers, pcre - , regex-base, stdenv + ({ mkDerivation, array, base, bytestring, containers, lib, pcre + , regex-base }: mkDerivation { pname = "regex-pcre"; - version = "0.94.4"; - sha256 = "8eaa7d4ac6c0a4ba35aa59fc3f6b8f8e252bb25a47e136791446a74752e226c0"; + version = "0.95.0.0"; + sha256 = "16ad6f10de3b14a4020075b3db64d2ca0c585d94013420418ddd4abd0836c75a"; + revision = "2"; + editedCabalFile = "0bvpy3rswyawv23s14nbxvgz5761s61g0shcj7p032i95iq7dj6d"; libraryHaskellDepends = [ array base bytestring containers regex-base ]; - librarySystemDepends = [ pcre ]; + libraryPkgconfigDepends = [ pcre ]; doHaddock = false; doCheck = false; - homepage = "http://hackage.haskell.org/package/regex-pcre"; - description = "Replaces/Enhances Text.Regex"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://wiki.haskell.org/Regular_expressions"; + description = "PCRE Backend for \"Text.Regex\" (regex-base)"; + license = lib.licenses.bsd3; }) {inherit (pkgs) pcre;}; "regex-pcre-builtin" = callPackage - ({ mkDerivation, array, base, bytestring, containers, regex-base - , stdenv + ({ mkDerivation, array, base, bytestring, containers, lib + , regex-base, text }: mkDerivation { pname = "regex-pcre-builtin"; - version = "0.94.4.8.8.35"; - sha256 = "0bd1b695de953ba4b6e6e0de007021c346cb2a6c8e09356fbcd34f8a79d2ea78"; - libraryHaskellDepends = [ - array base bytestring containers regex-base - ]; - doHaddock = false; - doCheck = false; - homepage = "http://hackage.haskell.org/package/regex-pcre"; - description = "Replaces/Enhances Text.Regex"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "regex-pcre-text" = callPackage - ({ mkDerivation, array, base, bytestring, regex-base - , regex-pcre-builtin, regex-tdfa-text, stdenv, text - }: - mkDerivation { - pname = "regex-pcre-text"; - version = "0.94.0.1"; - sha256 = "17991ed7b00da5cfb2efa0cefac16f9e0452fc794fe538d26d5cc802f0d8e9bd"; + version = "0.95.2.3.8.43"; + sha256 = "2773bd731045682c3acd359edc11a4bceddd4f62ba116e3cc7f307cffadf8609"; libraryHaskellDepends = [ - array base bytestring regex-base regex-pcre-builtin regex-tdfa-text - text + array base bytestring containers regex-base text ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/cdornan/regex-pcre-text"; - description = "Text-based PCRE API for regex-base"; - license = stdenv.lib.licenses.bsd3; + description = "PCRE Backend for \"Text.Regex\" (regex-base)"; + license = lib.licenses.bsd3; }) {}; "regex-posix" = callPackage - ({ mkDerivation, array, base, bytestring, containers, regex-base - , stdenv + ({ mkDerivation, array, base, bytestring, containers, lib + , regex-base }: mkDerivation { pname = "regex-posix"; - version = "0.95.2"; - sha256 = "56019921cd4a4c9682b81ec614236fea816ba8ed8785a1640cd66d8b24fc703e"; + version = "0.96.0.0"; + sha256 = "251300f1a6bb2e91abb8bf513a21981f8fab79c98a65acea2bb6d6a524414521"; + revision = "2"; + editedCabalFile = "10al5qljh6pc46581nkhrs0rjn8w05pp6jb4v55lgfr17ac0z1xx"; libraryHaskellDepends = [ array base bytestring containers regex-base ]; doHaddock = false; doCheck = false; - homepage = "http://sourceforge.net/projects/lazy-regex"; - description = "Replaces/Enhances Text.Regex"; - license = stdenv.lib.licenses.bsd3; + description = "POSIX Backend for \"Text.Regex\" (regex-base)"; + license = lib.licenses.bsd3; }) {}; "regex-tdfa" = callPackage - ({ mkDerivation, array, base, bytestring, containers, ghc-prim, mtl - , parsec, regex-base, stdenv + ({ mkDerivation, array, base, bytestring, containers, lib, mtl + , parsec, regex-base, text }: mkDerivation { pname = "regex-tdfa"; - version = "1.2.3.1"; - sha256 = "8aaaeeecf050807c7c514d4dd1763ac63bd121782de5a0847bef5d48a095ea50"; + version = "1.3.1.1"; + sha256 = "b1be517f6eaaa82bcb733919c58a111ce2acb03cc8fe962b15b64a32c3c059d7"; libraryHaskellDepends = [ - array base bytestring containers ghc-prim mtl parsec regex-base + array base bytestring containers mtl parsec regex-base text ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/ChrisKuklewicz/regex-tdfa"; - description = "Replaces/Enhances Text.Regex"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "regex-tdfa-text" = callPackage - ({ mkDerivation, array, base, regex-base, regex-tdfa, stdenv, text - }: - mkDerivation { - pname = "regex-tdfa-text"; - version = "1.0.0.3"; - sha256 = "38d77a0d225c306c52c6d4eed12d11d05a4bc4194d547cb9a7a9b6f5a8792001"; - libraryHaskellDepends = [ array base regex-base regex-tdfa text ]; - doHaddock = false; - doCheck = false; - description = "Text interface for regex-tdfa"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://wiki.haskell.org/Regular_expressions"; + description = "Pure Haskell Tagged DFA Backend for \"Text.Regex\" (regex-base)"; + license = lib.licenses.bsd3; }) {}; "regex-with-pcre" = callPackage - ({ mkDerivation, base, base-compat, bytestring, containers, regex - , regex-base, regex-pcre-builtin, regex-pcre-text, regex-tdfa - , stdenv, template-haskell, text, transformers - , unordered-containers + ({ mkDerivation, base, base-compat, bytestring, containers, lib + , regex, regex-base, regex-pcre-builtin, regex-tdfa + , template-haskell, text, transformers, unordered-containers }: mkDerivation { pname = "regex-with-pcre"; - version = "1.0.2.0"; - sha256 = "53c7bd8fc0e361b04af3bd3f2f546826a88b6827b252688d4ebb3fb8092f76a7"; + version = "1.1.0.0"; + sha256 = "5d5d2e468820777054cb532333cddf340fc82b45076d17288a6072abcd0898a3"; libraryHaskellDepends = [ base base-compat bytestring containers regex regex-base - regex-pcre-builtin regex-pcre-text regex-tdfa template-haskell text - transformers unordered-containers + regex-pcre-builtin regex-tdfa template-haskell text transformers + unordered-containers ]; doHaddock = false; doCheck = false; homepage = "http://regex.uk"; description = "Toolkit for regex-base"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "registry" = callPackage - ({ mkDerivation, base, exceptions, mtl, protolude, resourcet - , stdenv, text, transformers-base + ({ mkDerivation, base, containers, exceptions, hashable, lib + , mmorph, mtl, protolude, resourcet, semigroupoids, semigroups + , template-haskell, text, transformers-base }: mkDerivation { pname = "registry"; - version = "0.1.2.2"; - sha256 = "8741ec54316a115ac39472d321c2f8d20f1366189f54454e4237f922656ed0ce"; + version = "0.2.0.3"; + sha256 = "7af54423ec059df795b7a386227fac00281401e9f438584792de84bfd76518ba"; libraryHaskellDepends = [ - base exceptions mtl protolude resourcet text transformers-base + base containers exceptions hashable mmorph mtl protolude resourcet + semigroupoids semigroups template-haskell text transformers-base ]; doHaddock = false; doCheck = false; description = "data structure for assembling components"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "reinterpret-cast" = callPackage - ({ mkDerivation, array, base, stdenv }: + ({ mkDerivation, array, base, lib }: mkDerivation { pname = "reinterpret-cast"; version = "0.1.0"; @@ -27995,10 +33628,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/nh2/reinterpret-cast"; description = "Memory reinterpretation casts for Float/Double and Word32/Word64"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "relapse" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, stdenv }: + ({ mkDerivation, attoparsec, base, bytestring, lib }: mkDerivation { pname = "relapse"; version = "1.0.0.0"; @@ -28008,39 +33641,40 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/iostat/relapse#readme"; description = "Sensible RLP encoding"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "relational-query" = callPackage - ({ mkDerivation, array, base, bytestring, containers, dlist + ({ mkDerivation, array, base, bytestring, containers, dlist, lib , names-th, persistable-record, product-isomorphic, sql-words - , stdenv, template-haskell, text, th-reify-compat, time - , time-locale-compat, transformers + , template-haskell, text, th-constraint-compat, th-reify-compat + , time, time-locale-compat, transformers }: mkDerivation { pname = "relational-query"; - version = "0.12.1.0"; - sha256 = "33d12441a13c0480b40ca6377413e40b96141fb7da6205e8510adf49201dadd5"; + version = "0.12.2.3"; + sha256 = "253e5de15220afa5076be862d50b2ab794bb793c7f019e110d0fb63f1f98587e"; libraryHaskellDepends = [ array base bytestring containers dlist names-th persistable-record - product-isomorphic sql-words template-haskell text th-reify-compat - time time-locale-compat transformers + product-isomorphic sql-words template-haskell text + th-constraint-compat th-reify-compat time time-locale-compat + transformers ]; doHaddock = false; doCheck = false; homepage = "http://khibino.github.io/haskell-relational-record/"; description = "Typeful, Modular, Relational, algebraic query engine"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "relational-query-HDBC" = callPackage ({ mkDerivation, base, containers, convertible, dlist, HDBC - , HDBC-session, names-th, persistable-record, product-isomorphic - , relational-query, relational-schemas, sql-words, stdenv - , template-haskell, th-data-compat, transformers + , HDBC-session, lib, names-th, persistable-record + , product-isomorphic, relational-query, relational-schemas + , sql-words, template-haskell, th-data-compat, transformers }: mkDerivation { pname = "relational-query-HDBC"; - version = "0.7.1.1"; - sha256 = "b30acd65cf9fc42e28188018435137ae29ef491b82e4dc5ece7c434b3a9eff51"; + version = "0.7.2.0"; + sha256 = "83e90974b7e1281d7e1ac3aea03c145080aa53adfd1c36bf7096dc6b2096ef3f"; libraryHaskellDepends = [ base containers convertible dlist HDBC HDBC-session names-th persistable-record product-isomorphic relational-query @@ -28051,12 +33685,12 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://khibino.github.io/haskell-relational-record/"; description = "HDBC instance of relational-query and typed query interface for HDBC"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "relational-record" = callPackage - ({ mkDerivation, base, persistable-record + ({ mkDerivation, base, lib, persistable-record , persistable-types-HDBC-pg, product-isomorphic, relational-query - , relational-query-HDBC, stdenv + , relational-query-HDBC }: mkDerivation { pname = "relational-record"; @@ -28070,34 +33704,49 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://khibino.github.io/haskell-relational-record/"; description = "Meta package of Relational Record"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "relational-schemas" = callPackage - ({ mkDerivation, base, bytestring, containers, relational-query - , stdenv, template-haskell, time + ({ mkDerivation, base, bytestring, containers, lib + , relational-query, sql-words, template-haskell, time }: mkDerivation { pname = "relational-schemas"; - version = "0.1.6.2"; - sha256 = "5522efa683c5da8c37b09d2ebc636bc8d60804ed2372912ca7cc80793e45a7b0"; + version = "0.1.8.0"; + sha256 = "849651c007e27d39f868b4f23e3f5b1b1e4a55b766e6ddf90e64fbdbb11c4b04"; libraryHaskellDepends = [ - base bytestring containers relational-query template-haskell time + base bytestring containers relational-query sql-words + template-haskell time ]; doHaddock = false; doCheck = false; homepage = "http://khibino.github.io/haskell-relational-record/"; description = "RDBMSs' schema templates for relational-query"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "reliable-io" = callPackage + ({ mkDerivation, base, bindings-DSL, lib }: + mkDerivation { + pname = "reliable-io"; + version = "0.0.1"; + sha256 = "7dbf21c93d5a43360bf98c46beb534d400cb562376d24b37fbce58a6902e7735"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base bindings-DSL ]; + doHaddock = false; + doCheck = false; + homepage = "http://www.github.com/Mokosha/reliable-io"; + description = "Bindings to the low-level reliable.io library."; + license = lib.licenses.bsd3; }) {}; "relude" = callPackage ({ mkDerivation, base, bytestring, containers, deepseq, ghc-prim - , hashable, mtl, stdenv, stm, text, transformers - , unordered-containers + , hashable, lib, mtl, stm, text, transformers, unordered-containers }: mkDerivation { pname = "relude"; - version = "0.4.0"; - sha256 = "2ec5f256d6813ad87c2fa00780b26e071e6ce917bbee1e5a0868690d5194e80f"; + version = "0.7.0.0"; + sha256 = "c7492118453176e9ffbfca6c6723d4429d1d11f2133325ce06e87353cc80a1bf"; libraryHaskellDepends = [ base bytestring containers deepseq ghc-prim hashable mtl stm text transformers unordered-containers @@ -28105,12 +33754,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; homepage = "https://github.com/kowainik/relude"; - description = "Custom prelude from Kowainik"; - license = stdenv.lib.licenses.mit; + description = "Safe, performant, user-friendly and lightweight Haskell Standard Library"; + license = lib.licenses.mit; }) {}; "renderable" = callPackage - ({ mkDerivation, base, containers, hashable, stdenv, transformers - }: + ({ mkDerivation, base, containers, hashable, lib, transformers }: mkDerivation { pname = "renderable"; version = "0.2.0.1"; @@ -28120,109 +33768,90 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/schell/renderable"; description = "An API for managing renderable resources"; - license = stdenv.lib.licenses.mit; - }) {}; - "repa" = callPackage - ({ mkDerivation, base, bytestring, ghc-prim, QuickCheck, stdenv - , template-haskell, vector - }: - mkDerivation { - pname = "repa"; - version = "3.4.1.4"; - sha256 = "43607a5de4b89b8e58bfcbc261445d89fa40b685d43952797704b80d09e5a39e"; - revision = "1"; - editedCabalFile = "1c5rf3ky5lw9q1ji2y37m721gs7m5liw3j84159ib0w0bb3ddzmi"; - libraryHaskellDepends = [ - base bytestring ghc-prim QuickCheck template-haskell vector - ]; - doHaddock = false; - doCheck = false; - homepage = "http://repa.ouroborus.net"; - description = "High performance, regular, shape polymorphic parallel arrays"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; - "repa-algorithms" = callPackage - ({ mkDerivation, base, repa, stdenv, vector }: + "replace-attoparsec" = callPackage + ({ mkDerivation, attoparsec, base, bytestring, lib, text }: mkDerivation { - pname = "repa-algorithms"; - version = "3.4.1.3"; - sha256 = "de586fe7e14e0e000da50022e2129cabfd47773ba7844753c535c982f20e0fae"; - libraryHaskellDepends = [ base repa vector ]; + pname = "replace-attoparsec"; + version = "1.4.4.0"; + sha256 = "2e7e27cea59e25f3eed69516812e860137b115ec4ad18d82c5a2eebf9a225a1a"; + libraryHaskellDepends = [ attoparsec base bytestring text ]; doHaddock = false; doCheck = false; - homepage = "http://repa.ouroborus.net"; - description = "Algorithms using the Repa array library"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/jamesdbrock/replace-attoparsec"; + description = "Find, replace, and split string patterns with Attoparsec parsers (instead of regex)"; + license = lib.licenses.bsd2; }) {}; - "repa-io" = callPackage - ({ mkDerivation, base, binary, bmp, bytestring, old-time, repa - , stdenv, vector + "replace-megaparsec" = callPackage + ({ mkDerivation, base, bytestring, lib, megaparsec + , parser-combinators, text }: mkDerivation { - pname = "repa-io"; - version = "3.4.1.1"; - sha256 = "b5dbca96a988fb8bd918288ea1cfcf215fe46062e45001b209603b63a39ba9da"; - revision = "3"; - editedCabalFile = "027vn7an0hm3ysnzk19y0dbjpah0wpg96dgb55149x1310vwybxl"; + pname = "replace-megaparsec"; + version = "1.4.4.0"; + sha256 = "8136b67fc34dabcf09ea8cb31b19498bf2dca0011bb2c326a5cf54f802d08bda"; libraryHaskellDepends = [ - base binary bmp bytestring old-time repa vector + base bytestring megaparsec parser-combinators text ]; doHaddock = false; doCheck = false; - homepage = "http://repa.ouroborus.net"; - description = "Read and write Repa arrays in various formats"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/jamesdbrock/replace-megaparsec"; + description = "Find, replace, and split string patterns with Megaparsec parsers (instead of regex)"; + license = lib.licenses.bsd2; }) {}; "repline" = callPackage - ({ mkDerivation, base, containers, haskeline, mtl, process, stdenv + ({ mkDerivation, base, containers, exceptions, haskeline, lib, mtl + , process }: mkDerivation { pname = "repline"; - version = "0.2.0.0"; - sha256 = "ecc72092d0340b896ee6bf96bf6645694dbcd33361725a2cd28c5ab5d60c02de"; - libraryHaskellDepends = [ base containers haskeline mtl process ]; + version = "0.4.0.0"; + sha256 = "43c28c49c8e16276d32d0889f37f750d7c7a8d2758f1d35a9f36e68944e457b7"; + libraryHaskellDepends = [ + base containers exceptions haskeline mtl process + ]; doHaddock = false; doCheck = false; homepage = "https://github.com/sdiehl/repline"; description = "Haskeline wrapper for GHCi-like REPL interfaces"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "req" = callPackage ({ mkDerivation, aeson, authenticate-oauth, base, blaze-builder - , bytestring, case-insensitive, connection, data-default-class - , http-api-data, http-client, http-client-tls, http-types - , monad-control, mtl, retry, stdenv, text, time, transformers - , transformers-base + , bytestring, case-insensitive, connection, exceptions + , http-api-data, http-client, http-client-tls, http-types, lib + , modern-uri, monad-control, mtl, retry, template-haskell, text + , time, transformers, transformers-base, unliftio-core }: mkDerivation { pname = "req"; - version = "1.2.1"; - sha256 = "133da0f08c9c9b9331004bf6ec5955147aee46005ec1500aa13dcac45c940fe9"; - revision = "2"; - editedCabalFile = "19zayp5lvg2ahjrpxikhhq61w5nlzfp144333vxk03w345akmmrk"; + version = "3.9.0"; + sha256 = "639574931404d0ce32aaa67625528286940b511f6a7ec307e1bf1b6bdc5157c1"; enableSeparateDataOutput = true; libraryHaskellDepends = [ aeson authenticate-oauth base blaze-builder bytestring - case-insensitive connection data-default-class http-api-data - http-client http-client-tls http-types monad-control mtl retry text - time transformers transformers-base + case-insensitive connection exceptions http-api-data http-client + http-client-tls http-types modern-uri monad-control mtl retry + template-haskell text time transformers transformers-base + unliftio-core ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mrkkrp/req"; description = "Easy-to-use, type-safe, expandable, high-level HTTP client library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "req-conduit" = callPackage - ({ mkDerivation, base, bytestring, conduit, http-client, req - , resourcet, stdenv, transformers + ({ mkDerivation, base, bytestring, conduit, http-client, lib, req + , resourcet, transformers }: mkDerivation { pname = "req-conduit"; version = "1.0.0"; sha256 = "1da764e4bdc5454aef3d79cff2d72c9fa393a8d049ab14c3ba2be77325d96ba4"; - revision = "4"; - editedCabalFile = "13chmpfq1m1fgmgf7nxgs4dgfkpsv2khp4ma3cqqki76j1s8rq3p"; + revision = "8"; + editedCabalFile = "1md7zajmw87qrx6rvs35yrkbjs3s9nm0akg35jmf7a34xccrr7a7"; libraryHaskellDepends = [ base bytestring conduit http-client req resourcet transformers ]; @@ -28230,43 +33859,74 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mrkkrp/req-conduit"; description = "Conduit helpers for the req HTTP client library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "rerebase" = callPackage + ({ mkDerivation, lib, rebase }: + mkDerivation { + pname = "rerebase"; + version = "1.13.0.1"; + sha256 = "7bba6402ff520dd355c45a3a1a83ff03040389b0d0d932722c2672c84da2a048"; + libraryHaskellDepends = [ rebase ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/nikita-volkov/rerebase"; + description = "Reexports from \"base\" with a bunch of other standard libraries"; + license = lib.licenses.mit; }) {}; - "req-url-extra" = callPackage - ({ mkDerivation, aeson, base, data-default-class, modern-uri, req - , stdenv, text + "rescue" = callPackage + ({ mkDerivation, base, exceptions, ghc, lib, mtl, text + , transformers, transformers-base, world-peace }: mkDerivation { - pname = "req-url-extra"; - version = "0.1.0.0"; - sha256 = "b3de266ad49fb3c03ff26d589d89f81ddea7f319900b07e59843e57986d37d84"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ base modern-uri req ]; - executableHaskellDepends = [ - aeson base data-default-class modern-uri req text + pname = "rescue"; + version = "0.4.2.1"; + sha256 = "7e06b7363f729a9e6c55639d400ab4a3b646efac1f2373ed955b2ef463a7dc24"; + libraryHaskellDepends = [ + base exceptions ghc mtl text transformers transformers-base + world-peace ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/rcook/req-url-extra#readme"; - description = "Provides URI/URL helper functions for use with Req"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/expede/rescue#readme"; + description = "More understandable exceptions"; + license = lib.licenses.asl20; }) {}; - "rerebase" = callPackage - ({ mkDerivation, rebase, stdenv }: + "resistor-cube" = callPackage + ({ mkDerivation, base, comfort-array, lapack, lib }: mkDerivation { - pname = "rerebase"; - version = "1.3"; - sha256 = "ca155b086b4c83da781602427203f2180e7ee581fc4aae02783f7da893c98599"; - libraryHaskellDepends = [ rebase ]; + pname = "resistor-cube"; + version = "0.0.1.2"; + sha256 = "c69ad83ea57a2e9c6ab6e87a33ccdbb08651b1cc1407ff8c698b42bc6ef7b7c9"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ base comfort-array lapack ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/nikita-volkov/rerebase"; - description = "Reexports from \"base\" with a bunch of other standard libraries"; - license = stdenv.lib.licenses.mit; + homepage = "http://hub.darcs.net/thielema/resistor-cube"; + description = "Compute total resistance of a cube of resistors"; + license = lib.licenses.bsd3; + }) {}; + "resolv" = callPackage + ({ mkDerivation, base, base16-bytestring, binary, bytestring + , containers, lib + }: + mkDerivation { + pname = "resolv"; + version = "0.1.2.0"; + sha256 = "81a2bafad484db123cf8d17a02d98bb388a127fd0f822fa022589468a0e64671"; + revision = "3"; + editedCabalFile = "0af5dsdyn04i76d012xhhfkkml10bqzl6q2yivkhf8rlvh1fiii5"; + libraryHaskellDepends = [ + base base16-bytestring binary bytestring containers + ]; + doHaddock = false; + doCheck = false; + description = "Domain Name Service (DNS) lookup via the libresolv standard library routines"; + license = lib.licenses.gpl2Plus; }) {}; "resource-pool" = callPackage - ({ mkDerivation, base, hashable, monad-control, stdenv, stm, time + ({ mkDerivation, base, hashable, lib, monad-control, stm, time , transformers, transformers-base, vector }: mkDerivation { @@ -28281,16 +33941,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/bos/pool"; description = "A high-performance striped resource pooling implementation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "resourcet" = callPackage - ({ mkDerivation, base, containers, exceptions, mtl, primitive - , stdenv, transformers, unliftio-core + ({ mkDerivation, base, containers, exceptions, lib, mtl, primitive + , transformers, unliftio-core }: mkDerivation { pname = "resourcet"; - version = "1.2.2"; - sha256 = "1323425aba3827479eb3588efaf7608b12a083327d64ec814f02863c3673cbe5"; + version = "1.2.4.2"; + sha256 = "17f20842043ad199961a801b6efb1233b9098eb3537f8395844268f6a223eb87"; libraryHaskellDepends = [ base containers exceptions mtl primitive transformers unliftio-core ]; @@ -28298,11 +33958,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/snoyberg/conduit"; description = "Deterministic allocation and freeing of scarce resources"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "result" = callPackage - ({ mkDerivation, base, bifunctors, keys, mtl, stdenv, transformers - }: + ({ mkDerivation, base, bifunctors, keys, lib, mtl, transformers }: mkDerivation { pname = "result"; version = "0.2.6.0"; @@ -28312,19 +33971,19 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/srijs/haskell-result"; description = "Encode success or at least one error"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "rethinkdb-client-driver" = callPackage ({ mkDerivation, aeson, base, binary, bytestring, containers - , hashable, mtl, network, old-locale, scientific, stdenv, stm + , hashable, lib, mtl, network, old-locale, scientific, stm , template-haskell, text, time, unordered-containers, vector }: mkDerivation { pname = "rethinkdb-client-driver"; version = "0.0.25"; sha256 = "0f9dc156cd61b866b847b1b1a60a2345b4b5556b8b75a9e8499b0514e7f98996"; - revision = "3"; - editedCabalFile = "1g4shgl944fd3qbqkd68jv6vh65plaivci4vjzfs4py7a2p62db1"; + revision = "5"; + editedCabalFile = "051fgkx8zdlbpnsgvqm4jqk9a21xszz9sdhcmchx6h4ilyn7byjy"; libraryHaskellDepends = [ aeson base binary bytestring containers hashable mtl network old-locale scientific stm template-haskell text time @@ -28334,27 +33993,27 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/wereHamster/rethinkdb-client-driver"; description = "Client driver for RethinkDB"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "retry" = callPackage - ({ mkDerivation, base, data-default-class, exceptions, ghc-prim - , random, stdenv, transformers + ({ mkDerivation, base, exceptions, ghc-prim, lib, random + , transformers }: mkDerivation { pname = "retry"; - version = "0.7.7.0"; - sha256 = "3ccbc27a08ad0c7291342140f417cef11c2b11886586cc2bd870fa1e80cbd16c"; + version = "0.8.1.2"; + sha256 = "c5415ed7928d81611fa570fef9dd6c009f3d722a16a36f1177bdde2e888e9e5b"; libraryHaskellDepends = [ - base data-default-class exceptions ghc-prim random transformers + base exceptions ghc-prim random transformers ]; doHaddock = false; doCheck = false; homepage = "http://github.com/Soostone/retry"; description = "Retry combinators for monadic actions that may fail"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "rev-state" = callPackage - ({ mkDerivation, base, mtl, stdenv }: + ({ mkDerivation, base, lib, mtl }: mkDerivation { pname = "rev-state"; version = "0.1.2"; @@ -28366,90 +34025,164 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/DanBurton/rev-state#readme"; description = "Reverse State monad transformer"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "rfc1751" = callPackage - ({ mkDerivation, base, bytestring, cereal, stdenv, vector }: + ({ mkDerivation, base, bytestring, cereal, lib, vector }: mkDerivation { pname = "rfc1751"; - version = "0.1.2"; - sha256 = "a345e81625ffbdf3d3dc1723d322133108a5fd9ba17fbfae6e954046cd2b9aca"; + version = "0.1.3"; + sha256 = "13aa560c7c492c204e277bfbb09e40c66d83521966fdda8e168f183fb4cec8b8"; libraryHaskellDepends = [ base bytestring cereal vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/xenog/rfc1751.git#readme"; description = "RFC-1751 library for Haskell"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.mit; }) {}; "rfc5051" = callPackage - ({ mkDerivation, base, bytestring, containers, stdenv }: + ({ mkDerivation, base, containers, lib, text }: mkDerivation { pname = "rfc5051"; - version = "0.1.0.4"; - sha256 = "615daa230eabc781eff1d3ce94c42fc5ba6188dbeb115a233328454b02c1b3d3"; + version = "0.2"; + sha256 = "731cacf1402b3a432c2cfc2f884538ce063a332f22d2119f80dc575fb43c315b"; + libraryHaskellDepends = [ base containers text ]; + doHaddock = false; + doCheck = false; + description = "Simple unicode collation as per RFC5051"; + license = lib.licenses.bsd3; + }) {}; + "rhbzquery" = callPackage + ({ mkDerivation, base, bytestring, config-ini, directory + , email-validate, extra, filepath, http-types, lib + , optparse-applicative, simple-cmd, simple-cmd-args, text + }: + mkDerivation { + pname = "rhbzquery"; + version = "0.4.3"; + sha256 = "d7998d88f4d5980dd6aa5afc21ff42e9e1860b92f92acdc04a2cb4ea5f56798d"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ + base bytestring config-ini directory email-validate extra filepath + http-types optparse-applicative simple-cmd simple-cmd-args text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/juhp/rhbzquery"; + description = "Bugzilla query tool"; + license = lib.licenses.gpl2Only; + }) {}; + "rhine" = callPackage + ({ mkDerivation, base, containers, deepseq, dunai, free, lib + , MonadRandom, random, simple-affine-space, time, transformers + , vector-sized + }: + mkDerivation { + pname = "rhine"; + version = "0.7.0"; + sha256 = "e29a03b6faa4b0be2c3b1bcdf10cc0e7866f306c7177425c5a7a8f2811f9dce2"; + libraryHaskellDepends = [ + base containers deepseq dunai free MonadRandom random + simple-affine-space time transformers vector-sized + ]; + doHaddock = false; + doCheck = false; + description = "Functional Reactive Programming with type-level clocks"; + license = lib.licenses.bsd3; + }) {}; + "rhine-gloss" = callPackage + ({ mkDerivation, base, dunai, gloss, lib, rhine, transformers }: + mkDerivation { + pname = "rhine-gloss"; + version = "0.7.0"; + sha256 = "1550e909474e1385ab514a916bc3314b97f47d82ac34567ab06ca62663e2aad1"; isLibrary = true; isExecutable = true; - libraryHaskellDepends = [ base bytestring containers ]; + libraryHaskellDepends = [ base dunai gloss rhine transformers ]; + executableHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - description = "Simple unicode collation as per RFC5051"; - license = stdenv.lib.licenses.bsd3; + description = "Gloss backend for Rhine"; + license = lib.licenses.bsd3; + }) {}; + "rigel-viz" = callPackage + ({ mkDerivation, aeson, base, bytestring, colour, containers, lib + , text + }: + mkDerivation { + pname = "rigel-viz"; + version = "0.2.0.0"; + sha256 = "ba972f5ed4fde34b3d6185f311666cec93ec5618f047c28a09c5e9683d34cc7c"; + libraryHaskellDepends = [ + aeson base bytestring colour containers text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ocramz/rigel-viz"; + description = "A mid-level wrapper for vega-lite"; + license = lib.licenses.bsd3; }) {}; "rio" = callPackage ({ mkDerivation, base, bytestring, containers, deepseq, directory - , exceptions, filepath, hashable, microlens, mtl, primitive - , process, stdenv, text, time, typed-process, unix, unliftio - , unordered-containers, vector + , exceptions, filepath, hashable, lib, microlens, microlens-mtl + , mtl, primitive, process, text, time, typed-process, unix + , unliftio, unliftio-core, unordered-containers, vector }: mkDerivation { pname = "rio"; - version = "0.1.8.0"; - sha256 = "a013dd04221a1a69d5f253379443b88495be305692c06f1a060f428e98dbf5e1"; + version = "0.1.20.0"; + sha256 = "3a1887cfbf03a813d4b82ef0d0ed5fcb92bde0a458b3b569b0659de4012bab74"; libraryHaskellDepends = [ base bytestring containers deepseq directory exceptions filepath - hashable microlens mtl primitive process text time typed-process - unix unliftio unordered-containers vector + hashable microlens microlens-mtl mtl primitive process text time + typed-process unix unliftio unliftio-core unordered-containers + vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/commercialhaskell/rio#readme"; description = "A standard library for Haskell"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "rio-orphans" = callPackage - ({ mkDerivation, base, exceptions, fast-logger, monad-control - , monad-logger, resourcet, rio, stdenv, transformers-base + ({ mkDerivation, base, exceptions, fast-logger, lib, monad-control + , monad-logger, resourcet, rio, transformers-base, unliftio-core }: mkDerivation { pname = "rio-orphans"; - version = "0.1.1.0"; - sha256 = "7e8d2c6df6e7afdbca5b344c6e57c754e2d6b9c0cfb4f00e1df88dad1bd48b4e"; + version = "0.1.2.0"; + sha256 = "3c43cd96493750cb9bae3534f887ca02b47942477072bf8ade4fc599b23a8c6f"; libraryHaskellDepends = [ base exceptions fast-logger monad-control monad-logger resourcet - rio transformers-base + rio transformers-base unliftio-core ]; doHaddock = false; doCheck = false; homepage = "https://github.com/commercialhaskell/rio#readme"; description = "Orphan instances for the RIO type in the rio package"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "rng-utils" = callPackage - ({ mkDerivation, base, bytestring, random, stdenv }: + "rio-prettyprint" = callPackage + ({ mkDerivation, aeson, annotated-wl-pprint, ansi-terminal, array + , base, Cabal, colour, lib, mtl, path, rio, text + }: mkDerivation { - pname = "rng-utils"; - version = "0.3.0"; - sha256 = "0886acb1e0ae6c6ad5f594a9d4d57ea5af69c566ccc5763d0b7c690963e946ba"; - libraryHaskellDepends = [ base bytestring random ]; + pname = "rio-prettyprint"; + version = "0.1.1.0"; + sha256 = "6e7abc8a179881bb612e64e393d8876a12b3de31ccac0dec98a6ba6b081509c0"; + libraryHaskellDepends = [ + aeson annotated-wl-pprint ansi-terminal array base Cabal colour mtl + path rio text + ]; doHaddock = false; doCheck = false; - homepage = "https://bitbucket.org/soostone/rng-utils"; - description = "RNG within an IORef for convenient concurrent use"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/commercialhaskell/rio-prettyprint#readme"; + description = "Pretty-printing for RIO"; + license = lib.licenses.bsd3; }) {}; "roc-id" = callPackage - ({ mkDerivation, base, MonadRandom, Only, stdenv, text - , vector-sized + ({ mkDerivation, base, lib, MonadRandom, Only, text, vector-sized }: mkDerivation { pname = "roc-id"; @@ -28462,11 +34195,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/jonathanknowles/roc-id#readme"; description = "Implementation of the ROC National ID standard"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "rocksdb-haskell" = callPackage ({ mkDerivation, base, binary, bytestring, data-default, directory - , filepath, resourcet, rocksdb, stdenv, transformers + , filepath, lib, resourcet, rocksdb, transformers }: mkDerivation { pname = "rocksdb-haskell"; @@ -28481,27 +34214,46 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/serokell/rocksdb-haskell"; description = "Haskell bindings to RocksDB"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {inherit (pkgs) rocksdb;}; + "rocksdb-haskell-jprupp" = callPackage + ({ mkDerivation, base, bytestring, data-default, directory, lib + , rocksdb, unliftio + }: + mkDerivation { + pname = "rocksdb-haskell-jprupp"; + version = "2.1.3"; + sha256 = "fb824955b1ab598858d0bd427ab107928f157071aeb5f1446f464a6cf6391606"; + libraryHaskellDepends = [ + base bytestring data-default directory unliftio + ]; + librarySystemDepends = [ rocksdb ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jprupp/rocksdb-haskell#readme"; + description = "Haskell bindings for RocksDB"; + license = lib.licenses.bsd3; }) {inherit (pkgs) rocksdb;}; "rocksdb-query" = callPackage - ({ mkDerivation, base, bytestring, cereal, conduit, resourcet - , rocksdb-haskell, stdenv, unliftio + ({ mkDerivation, base, bytestring, cereal, conduit, lib, resourcet + , rocksdb-haskell-jprupp, unliftio }: mkDerivation { pname = "rocksdb-query"; - version = "0.2.0"; - sha256 = "8e2d645542c98fd69fa73c136d2aa4bba574354c3121bc7b461d367a17fdc206"; + version = "0.4.2"; + sha256 = "980764c917d74006ef4f82ad355bc785b471144791d76d5e1c6101bc014608ea"; libraryHaskellDepends = [ - base bytestring cereal conduit resourcet rocksdb-haskell unliftio + base bytestring cereal conduit resourcet rocksdb-haskell-jprupp + unliftio ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/xenog/rocksdb-query#readme"; + homepage = "https://github.com/jprupp/rocksdb-query#readme"; description = "RocksDB database querying library for Haskell"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.mit; }) {}; "roles" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "roles"; version = "0.2.0.0"; @@ -28511,10 +34263,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/matt-noonan/roles/"; description = "Composable class-based roles"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "rope-utf16-splay" = callPackage + ({ mkDerivation, base, lib, text }: + mkDerivation { + pname = "rope-utf16-splay"; + version = "0.3.2.0"; + sha256 = "f704b815dc8e2bdfe30b54345ad9545ff6f14f6ca53ba3a4f856948ee3f04c79"; + libraryHaskellDepends = [ base text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ollef/rope-utf16-splay"; + description = "Ropes optimised for updating using UTF-16 code units and row/column pairs"; + license = lib.licenses.bsd3; }) {}; "rosezipper" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "rosezipper"; version = "0.2"; @@ -28523,10 +34288,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Generic zipper implementation for Data.Tree"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "rot13" = callPackage - ({ mkDerivation, base, bytestring, stdenv, text }: + ({ mkDerivation, base, bytestring, lib, text }: mkDerivation { pname = "rot13"; version = "0.2.0.1"; @@ -28536,48 +34301,63 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/kvanberendonck/codec-rot13"; description = "Fast ROT13 cipher for Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "rounded" = callPackage - ({ mkDerivation, base, ghc-prim, gmp, hgmp, long-double, mpfr - , reflection, singletons, stdenv + "rp-tree" = callPackage + ({ mkDerivation, base, boxes, bytestring, conduit, containers + , deepseq, heaps, lib, mtl, serialise, splitmix + , splitmix-distributions, text, transformers, vector + , vector-algorithms }: mkDerivation { - pname = "rounded"; - version = "0.1.0.1"; - sha256 = "9abeea23692dd57e879eda210308ef5ef213169b4cb9e4e6c13de02d52a04b11"; + pname = "rp-tree"; + version = "0.6"; + sha256 = "1050efa1d45479e47b50a41d7cc72de683d97b353756511ab944e015dc648373"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - base ghc-prim hgmp long-double reflection singletons + base boxes bytestring conduit containers deepseq heaps mtl + serialise splitmix splitmix-distributions text transformers vector + vector-algorithms + ]; + executableHaskellDepends = [ + base conduit containers splitmix splitmix-distributions + transformers vector ]; - librarySystemDepends = [ gmp mpfr ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/ekmett/rounded"; - description = "Correctly-rounded arbitrary-precision floating-point arithmetic"; - license = stdenv.lib.licenses.bsd3; - }) {inherit (pkgs) gmp; inherit (pkgs) mpfr;}; + homepage = "https://github.com/ocramz/rp-tree"; + description = "Random projection trees"; + license = lib.licenses.bsd3; + }) {}; "rpmbuild-order" = callPackage - ({ mkDerivation, base, Cabal, containers, directory - , explicit-exception, fgl, filepath, process, stdenv, transformers + ({ mkDerivation, base, case-insensitive, containers, directory + , extra, fgl, filepath, graphviz, lib, optparse-applicative + , process, simple-cmd-args }: mkDerivation { pname = "rpmbuild-order"; - version = "0.2.1"; - sha256 = "b66d6078e82da6c2becf1e0082fb0f17e5a8a0052d95442dc3b0b63915a6a082"; - isLibrary = false; + version = "0.4.5"; + sha256 = "7407e112c51436e715350b00ab784222e5afe8d9769b7b5d56007bd4ace0e6d3"; + revision = "1"; + editedCabalFile = "05arkmpbh5fdqbqhkwl76isbigrsc0f54zkbdl21jap6k4g9kzsk"; + isLibrary = true; isExecutable = true; + libraryHaskellDepends = [ + base case-insensitive containers directory extra fgl filepath + graphviz process + ]; executableHaskellDepends = [ - base Cabal containers directory explicit-exception fgl filepath - process transformers + base directory extra fgl optparse-applicative simple-cmd-args ]; doHaddock = false; doCheck = false; homepage = "https://github.com/juhp/rpmbuild-order"; - description = "Order RPM packages by dependencies"; - license = stdenv.lib.licenses.bsd3; + description = "Sort RPM packages in dependency order"; + license = lib.licenses.bsd3; }) {}; "runmemo" = callPackage - ({ mkDerivation, stdenv }: + ({ mkDerivation, lib }: mkDerivation { pname = "runmemo"; version = "1.0.0.1"; @@ -28586,16 +34366,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/DanBurton/runmemo"; description = "A simple memoization helper library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "rvar" = callPackage - ({ mkDerivation, base, MonadPrompt, mtl, random-source, stdenv + ({ mkDerivation, base, lib, MonadPrompt, mtl, random-source , transformers }: mkDerivation { pname = "rvar"; - version = "0.2.0.3"; - sha256 = "d78aaf2ffdba182dda95d1692fec7abc5d77fa371120618a397b5675438c6bc0"; + version = "0.2.0.6"; + sha256 = "01e18875ffde43f9591a8acd9f60c9c51704a026e51c1a6797faecd1c7ae8cd3"; libraryHaskellDepends = [ base MonadPrompt mtl random-source transformers ]; @@ -28603,76 +34383,79 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mokus0/random-fu"; description = "Random Variables"; - license = stdenv.lib.licenses.publicDomain; - }) {}; - "s3-signer" = callPackage - ({ mkDerivation, base, base64-bytestring, blaze-builder, byteable - , bytestring, case-insensitive, cryptohash, http-types, stdenv - , time, utf8-string - }: - mkDerivation { - pname = "s3-signer"; - version = "0.5.0.0"; - sha256 = "d73671d5bda0f5f627bbd876916341985c281c3572e6f8406cdf2f14ed9188e4"; - libraryHaskellDepends = [ - base base64-bytestring blaze-builder byteable bytestring - case-insensitive cryptohash http-types time utf8-string - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/dmjio/s3-signer"; - description = "Pre-signed Amazon S3 URLs"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.publicDomain; }) {}; "safe" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "safe"; - version = "0.3.17"; - sha256 = "79c5c41e7151906969133ea21af9f7e8d25c18315886e23d0bdf6faa8b537e5c"; + version = "0.3.19"; + sha256 = "25043442c8f8aa95955bb17467d023630632b961aaa61e807e325d9b2c33f7a2"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/ndmitchell/safe#readme"; description = "Library of safe (exception free) functions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "safe-exceptions" = callPackage - ({ mkDerivation, base, deepseq, exceptions, stdenv, transformers }: + "safe-coloured-text" = callPackage + ({ mkDerivation, base, bytestring, lib, text, validity + , validity-bytestring, validity-text + }: mkDerivation { - pname = "safe-exceptions"; - version = "0.1.7.0"; - sha256 = "18cddc587b52b6faa0287fb6ad6c964d1562571ea2c8ff57a194dd54b5fba069"; - revision = "4"; - editedCabalFile = "0fid41gishzsyb47wzxhd5falandfirqcp760hcja81qjpfmqd32"; - libraryHaskellDepends = [ base deepseq exceptions transformers ]; + pname = "safe-coloured-text"; + version = "0.1.0.0"; + sha256 = "1ca8432f0c87351f1b24298e4c33ba396971eb323efbbd420e3ddd7529e598b9"; + libraryHaskellDepends = [ + base bytestring text validity validity-bytestring validity-text + ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/fpco/safe-exceptions#readme"; - description = "Safe, consistent, and easy exception handling"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/NorfairKing/safe-coloured-text#readme"; + description = "Safely output coloured text"; + license = lib.licenses.mit; }) {}; - "safe-exceptions-checked" = callPackage - ({ mkDerivation, base, deepseq, safe-exceptions, stdenv - , transformers - }: + "safe-coloured-text-terminfo" = callPackage + ({ mkDerivation, base, lib, safe-coloured-text, terminfo }: mkDerivation { - pname = "safe-exceptions-checked"; - version = "0.1.0"; - sha256 = "d807552b828de308d80805f65ee41f3e25571506b10e6b28b0b81de4aec0ca3f"; - revision = "3"; - editedCabalFile = "004id0k46j545zvkldfcv5qjgxzl35brm9h6fq72y43b9hl2y55f"; - libraryHaskellDepends = [ - base deepseq safe-exceptions transformers - ]; + pname = "safe-coloured-text-terminfo"; + version = "0.0.0.0"; + sha256 = "aba019ee2781990774c9ff4acf6232fb5e00702625e9f0d8a4b757abeaff2439"; + libraryHaskellDepends = [ base safe-coloured-text terminfo ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/safe-coloured-text#readme"; + description = "Safely output coloured text"; + license = lib.licenses.mit; + }) {}; + "safe-decimal" = callPackage + ({ mkDerivation, base, deepseq, exceptions, lib, scientific }: + mkDerivation { + pname = "safe-decimal"; + version = "0.2.1.0"; + sha256 = "bcad549bae333a4f3522ed0b2469e273eb7bfc0295ad582bec7d42586446f4e0"; + libraryHaskellDepends = [ base deepseq exceptions scientific ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/fpco/safe-decimal#readme"; + description = "Safe and very efficient arithmetic operations on fixed decimal point numbers"; + license = lib.licenses.bsd3; + }) {}; + "safe-exceptions" = callPackage + ({ mkDerivation, base, deepseq, exceptions, lib, transformers }: + mkDerivation { + pname = "safe-exceptions"; + version = "0.1.7.2"; + sha256 = "69637f794146a8e7bfbc2db2bd0501c274ec99504b597728e203187790064895"; + libraryHaskellDepends = [ base deepseq exceptions transformers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/mitchellwrosen/safe-exceptions-checked#readme"; - description = "Safe, checked exceptions"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/fpco/safe-exceptions#readme"; + description = "Safe, consistent, and easy exception handling"; + license = lib.licenses.mit; }) {}; "safe-foldable" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "safe-foldable"; version = "0.1.0.0"; @@ -28682,29 +34465,87 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/tejon/safe-foldable#readme"; description = "Safe wrappers for null-partial Foldable operations"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "safe-json" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers, dlist + , hashable, lib, scientific, tasty, tasty-hunit, tasty-quickcheck + , text, time, unordered-containers, uuid-types, vector + }: + mkDerivation { + pname = "safe-json"; + version = "1.1.1.1"; + sha256 = "430a7b0a4bcf3d5af1df3c136a819b439cd9c6e69156cc2593721c335529e972"; + revision = "1"; + editedCabalFile = "0bwdim4vslpgnh77b5lgxmfrh2xaza1rgqgnh2xz73b4jb8lg2p4"; + libraryHaskellDepends = [ + aeson base bytestring containers dlist hashable scientific tasty + tasty-hunit tasty-quickcheck text time unordered-containers + uuid-types vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/Vlix/safe-json#readme"; + description = "Automatic JSON format versioning"; + license = lib.licenses.mit; + }) {}; + "safe-money" = callPackage + ({ mkDerivation, base, binary, constraints, deepseq, hashable, lib + , QuickCheck, text, vector-space + }: + mkDerivation { + pname = "safe-money"; + version = "0.9"; + sha256 = "ee6810cc3f67da59d9300b3baa1c90f9a9d6876d0f563a070a9f3ddcbcbe7d30"; + libraryHaskellDepends = [ + base binary constraints deepseq hashable QuickCheck text + vector-space + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/k0001/safe-money"; + description = "Type-safe and lossless encoding and manipulation of money, fiat currencies, crypto currencies and precious metals"; + license = lib.licenses.bsd3; + }) {}; + "safe-tensor" = callPackage + ({ mkDerivation, base, constraints, containers, deepseq, hmatrix + , lib, mtl, singletons + }: + mkDerivation { + pname = "safe-tensor"; + version = "0.2.1.1"; + sha256 = "232b7cf36cb205d43c2a3fe058e8b8689d7cf3c53aa98bc92173c7bd69ae48d7"; + libraryHaskellDepends = [ + base constraints containers deepseq hmatrix mtl singletons + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/nilsalex/safe-tensor#readme"; + description = "Dependently typed tensor algebra"; + license = lib.licenses.mit; }) {}; "safecopy" = callPackage ({ mkDerivation, array, base, bytestring, cereal, containers - , old-time, stdenv, template-haskell, text, time, vector + , generic-data, lib, old-time, template-haskell, text, time + , transformers, vector }: mkDerivation { pname = "safecopy"; - version = "0.9.4.3"; - sha256 = "787db1a56b7024ab5619b4f25af5379133f5f2a5e1a0657e66c8dfac1a131f08"; + version = "0.10.4.2"; + sha256 = "7140a3af92a0acff8c75d88ef03c3c3dc83c7d59e790dea8ddc83d812e705564"; libraryHaskellDepends = [ - array base bytestring cereal containers old-time template-haskell - text time vector + array base bytestring cereal containers generic-data old-time + template-haskell text time transformers vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/acid-state/safecopy"; description = "Binary serialization with version control"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "safeio" = callPackage ({ mkDerivation, base, bytestring, conduit, conduit-combinators - , directory, exceptions, filepath, resourcet, stdenv, unix + , directory, exceptions, filepath, lib, resourcet, unix }: mkDerivation { pname = "safeio"; @@ -28718,55 +34559,37 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/luispedro/safeio#readme"; description = "Write output to disk atomically"; - license = stdenv.lib.licenses.mit; - }) {}; - "salak" = callPackage - ({ mkDerivation, aeson, base, directory, filepath, scientific - , stdenv, text, unordered-containers, vector, yaml - }: - mkDerivation { - pname = "salak"; - version = "0.1.6"; - sha256 = "8c250712b52358a3ee00e299e9766b271578d4944b44d3081f03e97e54a236d1"; - libraryHaskellDepends = [ - aeson base directory filepath scientific text unordered-containers - vector yaml - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/leptonyu/salak#readme"; - description = "Configuration Loader"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; "saltine" = callPackage - ({ mkDerivation, base, bytestring, libsodium, profunctors, stdenv + ({ mkDerivation, base, bytestring, hashable, lib, libsodium + , profunctors }: mkDerivation { pname = "saltine"; - version = "0.1.0.2"; - sha256 = "fd989db905f3e1d742b9fcb9501d6483ffa82620e287cf51b62e0d6d2caaa308"; - libraryHaskellDepends = [ base bytestring profunctors ]; + version = "0.1.1.1"; + sha256 = "a75b1aae629bef09c1b14364abbf8998420e0737bf2f3515ca18055ef336f9ad"; + libraryHaskellDepends = [ base bytestring hashable profunctors ]; libraryPkgconfigDepends = [ libsodium ]; doHaddock = false; doCheck = false; description = "Cryptography that's easy to digest (NaCl/libsodium bindings)"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {inherit (pkgs) libsodium;}; "salve" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "salve"; - version = "1.0.6"; - sha256 = "32c8bb50cc20360cb48751d810cac117a6b4fb83c39cf50287c61ef13c90f7ed"; + version = "1.0.11"; + sha256 = "ab07dd903cb94b47ea8cff958e6731f1a4f723776086f17e421ef29b0f520a02"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/tfausak/salve#readme"; description = "Semantic version numbers and constraints"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "sample-frame" = callPackage - ({ mkDerivation, base, QuickCheck, stdenv, storable-record }: + ({ mkDerivation, base, lib, QuickCheck, storable-record }: mkDerivation { pname = "sample-frame"; version = "0.0.3"; @@ -28778,10 +34601,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Synthesizer"; description = "Handling of samples in an (audio) signal"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "sample-frame-np" = callPackage - ({ mkDerivation, base, numeric-prelude, sample-frame, stdenv }: + ({ mkDerivation, base, lib, numeric-prelude, sample-frame }: mkDerivation { pname = "sample-frame-np"; version = "0.0.4.1"; @@ -28791,18 +34614,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Synthesizer"; description = "Orphan instances for types from sample-frame and numericprelude"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "sampling" = callPackage - ({ mkDerivation, base, containers, foldl, mwc-random, primitive - , stdenv, vector + ({ mkDerivation, base, containers, foldl, lib, mwc-random + , primitive, vector }: mkDerivation { pname = "sampling"; - version = "0.3.3"; - sha256 = "c8bedc93d61e6b1939f6802d7e21003e9e36abdd6f21a9651179d4d82aa00e0d"; - revision = "1"; - editedCabalFile = "168k8ykppa8pikfxy1gmby63kfzr833vswh8wcchz8li9vkd4w2h"; + version = "0.3.5"; + sha256 = "7b1e177bee4b137aae22687014ae5435b0372716e4f6b9ef5abe9b622ec2b38f"; libraryHaskellDepends = [ base containers foldl mwc-random primitive vector ]; @@ -28810,30 +34631,129 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/jtobin/sampling"; description = "Sample values from collections"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "sandman" = callPackage - ({ mkDerivation, base, Cabal, containers, directory, filepath - , optparse-applicative, process, stdenv, text, unix-compat + "sandwich" = callPackage + ({ mkDerivation, aeson, ansi-terminal, async, base, brick + , bytestring, colour, containers, directory, exceptions, filepath + , free, haskell-src-exts, lens, lib, lifted-async, microlens + , microlens-th, monad-control, monad-logger, mtl + , optparse-applicative, pretty-show, process, safe, safe-exceptions + , stm, string-interpolate, template-haskell, text, time + , transformers, transformers-base, unix, unliftio-core, vector, vty }: mkDerivation { - pname = "sandman"; - version = "0.2.0.1"; - sha256 = "407d283e1fc4a2a369615bac569683bf399ac14ddbce1331850bfe1d7837ce64"; - isLibrary = false; + pname = "sandwich"; + version = "0.1.0.8"; + sha256 = "5e2624ea6c5f90ecbb132f5a9cf63efe0985d4eea32b6284ed2af2827200132c"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson ansi-terminal async base brick bytestring colour containers + directory exceptions filepath free haskell-src-exts lens + lifted-async microlens microlens-th monad-control monad-logger mtl + optparse-applicative pretty-show process safe safe-exceptions stm + string-interpolate template-haskell text time transformers + transformers-base unix unliftio-core vector vty + ]; + executableHaskellDepends = [ + aeson ansi-terminal async base brick bytestring colour containers + directory exceptions filepath free haskell-src-exts lens + lifted-async microlens microlens-th monad-control monad-logger mtl + optparse-applicative pretty-show process safe safe-exceptions stm + string-interpolate template-haskell text time transformers + transformers-base unix unliftio-core vector vty + ]; + doHaddock = false; + doCheck = false; + homepage = "https://codedownio.github.io/sandwich"; + description = "Yet another test framework for Haskell"; + license = lib.licenses.bsd3; + }) {}; + "sandwich-quickcheck" = callPackage + ({ mkDerivation, base, brick, free, lib, monad-control, QuickCheck + , safe-exceptions, sandwich, string-interpolate, text, time + }: + mkDerivation { + pname = "sandwich-quickcheck"; + version = "0.1.0.5"; + sha256 = "9c1e378782ec2cdd0df8bf9a739812747c524a8ad294c8d757d7753f7079e80f"; + libraryHaskellDepends = [ + base brick free monad-control QuickCheck safe-exceptions sandwich + string-interpolate text time + ]; + doHaddock = false; + doCheck = false; + homepage = "https://codedownio.github.io/sandwich"; + description = "Sandwich integration with QuickCheck"; + license = lib.licenses.bsd3; + }) {}; + "sandwich-slack" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers, lens + , lens-aeson, lib, monad-logger, mtl, safe, safe-exceptions + , sandwich, stm, string-interpolate, text, time, vector, wreq + }: + mkDerivation { + pname = "sandwich-slack"; + version = "0.1.0.4"; + sha256 = "132b590ce10e036c54365f48cdec6c9f2cb63336d6e47bda1bd2a94e073649d0"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson base bytestring containers lens lens-aeson monad-logger mtl + safe safe-exceptions sandwich stm string-interpolate text time + vector wreq + ]; + executableHaskellDepends = [ + aeson base bytestring containers lens lens-aeson monad-logger mtl + safe safe-exceptions sandwich stm string-interpolate text time + vector wreq + ]; + doHaddock = false; + doCheck = false; + homepage = "https://codedownio.github.io/sandwich"; + description = "Sandwich integration with Slack"; + license = lib.licenses.bsd3; + }) {}; + "sandwich-webdriver" = callPackage + ({ mkDerivation, aeson, base, containers, convertible, data-default + , directory, exceptions, filepath, http-client, http-client-tls + , http-conduit, lib, lifted-base, microlens, microlens-aeson + , monad-control, monad-logger, mtl, network, process, random, retry + , safe, safe-exceptions, sandwich, string-interpolate, temporary + , text, time, transformers, unix, unordered-containers, vector + , webdriver, X11 + }: + mkDerivation { + pname = "sandwich-webdriver"; + version = "0.1.0.5"; + sha256 = "1e29073ab4ad69a8475fd2b973028c16adde2d45311297f9820f0e4762d06a84"; + isLibrary = true; isExecutable = true; + libraryHaskellDepends = [ + aeson base containers convertible data-default directory exceptions + filepath http-client http-client-tls http-conduit lifted-base + microlens microlens-aeson monad-control monad-logger mtl network + process random retry safe safe-exceptions sandwich + string-interpolate temporary text time transformers unix + unordered-containers vector webdriver X11 + ]; executableHaskellDepends = [ - base Cabal containers directory filepath optparse-applicative - process text unix-compat + aeson base containers convertible data-default directory exceptions + filepath http-client http-client-tls http-conduit lifted-base + microlens microlens-aeson monad-control monad-logger mtl network + process random retry safe safe-exceptions sandwich + string-interpolate temporary text time transformers unix + unordered-containers vector webdriver X11 ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/abhinav/sandman#readme"; - description = "Manages Cabal sandboxes to avoid rebuilding packages"; - license = stdenv.lib.licenses.mit; + homepage = "https://codedownio.github.io/sandwich"; + description = "Sandwich integration with Selenium WebDriver"; + license = lib.licenses.bsd3; }) {}; "say" = callPackage - ({ mkDerivation, base, bytestring, stdenv, text, transformers }: + ({ mkDerivation, base, bytestring, lib, text, transformers }: mkDerivation { pname = "say"; version = "0.1.0.1"; @@ -28843,18 +34763,19 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/fpco/say#readme"; description = "Send textual messages to a Handle in a thread-friendly way"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "sbp" = callPackage - ({ mkDerivation, aeson, array, base, base64-bytestring - , basic-prelude, binary, binary-conduit, bytestring, conduit - , conduit-extra, data-binary-ieee754, lens, lens-aeson, monad-loops - , resourcet, stdenv, template-haskell, text, time, yaml + ({ mkDerivation, aeson, aeson-pretty, array, base + , base64-bytestring, basic-prelude, binary, binary-conduit + , bytestring, cmdargs, conduit, conduit-extra, data-binary-ieee754 + , lens, lens-aeson, lib, monad-loops, resourcet, template-haskell + , text, time, yaml }: mkDerivation { pname = "sbp"; - version = "2.4.6"; - sha256 = "9568da4776a337236101cc534f023fe67929daafb08f52dce79eae6ee9ab1ab8"; + version = "2.6.3"; + sha256 = "316e4c2301fece2db29ffc5cbca45c00f4d20539b1a5c14e20b43c3a8ee2a20d"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -28863,73 +34784,75 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; text ]; executableHaskellDepends = [ - aeson base basic-prelude binary-conduit bytestring conduit - conduit-extra resourcet time yaml + aeson aeson-pretty base basic-prelude binary-conduit bytestring + cmdargs conduit conduit-extra resourcet time yaml ]; doHaddock = false; doCheck = false; homepage = "https://github.com/swift-nav/libsbp"; description = "SwiftNav's SBP Library"; - license = stdenv.lib.licenses.lgpl3; + license = lib.licenses.lgpl3Only; }) {}; "sbv" = callPackage - ({ mkDerivation, array, async, base, containers, crackNum, deepseq - , directory, filepath, generic-deriving, ghc, mtl, pretty, process - , QuickCheck, random, stdenv, syb, template-haskell, time + ({ mkDerivation, array, async, base, containers, deepseq, directory + , filepath, lib, libBF, mtl, pretty, process, QuickCheck, random + , syb, template-haskell, text, time, transformers, uniplate }: mkDerivation { pname = "sbv"; - version = "7.13"; - sha256 = "33bafb18a6d7476aeb3fb215077154cd4ad36fa0359c5b184a9a2ccb3500642e"; + version = "8.15"; + sha256 = "170c1bcf91eb40906f7be5c1470687404b1e9dbd7149697e676827ec9e801f87"; enableSeparateDataOutput = true; libraryHaskellDepends = [ - array async base containers crackNum deepseq directory filepath - generic-deriving ghc mtl pretty process QuickCheck random syb - template-haskell time + array async base containers deepseq directory filepath libBF mtl + pretty process QuickCheck random syb template-haskell text time + transformers uniplate ]; doHaddock = false; doCheck = false; - homepage = "http://leventerkok.github.com/sbv/"; + homepage = "http://leventerkok.github.io/sbv/"; description = "SMT Based Verification: Symbolic Haskell theorem prover using SMT solving"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "scalpel" = callPackage - ({ mkDerivation, base, bytestring, curl, data-default, scalpel-core - , stdenv, tagsoup, text + ({ mkDerivation, base, bytestring, case-insensitive, data-default + , http-client, http-client-tls, lib, scalpel-core, tagsoup, text }: mkDerivation { pname = "scalpel"; - version = "0.5.1"; - sha256 = "20df66433570a2ca754f14058a47fb00519d9a75bb822fc3fd1769a83c608b0d"; + version = "0.6.2"; + sha256 = "90c9f95ee8cad7a2f702d2d215a394179ef4f38edd256b9e1f0a76e9c1dc1012"; libraryHaskellDepends = [ - base bytestring curl data-default scalpel-core tagsoup text + base bytestring case-insensitive data-default http-client + http-client-tls scalpel-core tagsoup text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/fimad/scalpel"; description = "A high level web scraping library for Haskell"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; }) {}; "scalpel-core" = callPackage ({ mkDerivation, base, bytestring, containers, data-default, fail - , regex-base, regex-tdfa, stdenv, tagsoup, text, vector + , lib, mtl, pointedlist, regex-base, regex-tdfa, tagsoup, text + , transformers, vector }: mkDerivation { pname = "scalpel-core"; - version = "0.5.1"; - sha256 = "8c05b86853b737fbed4144dc9c7bbb7743525c305f9529f59776df97bfe229a9"; + version = "0.6.2"; + sha256 = "ae52ea1040d25537b9d00822adb1cc736665af3c6d210c3dea4b71ac9073b21e"; libraryHaskellDepends = [ - base bytestring containers data-default fail regex-base regex-tdfa - tagsoup text vector + base bytestring containers data-default fail mtl pointedlist + regex-base regex-tdfa tagsoup text transformers vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/fimad/scalpel"; description = "A high level web scraping library for Haskell"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; }) {}; "scanf" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { pname = "scanf"; version = "0.1.0.0"; @@ -28939,66 +34862,84 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/Lysxia/scanf#readme"; description = "Easy and type-safe format strings for parsing and printing"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "scanner" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, fail, lib }: mkDerivation { pname = "scanner"; - version = "0.3"; - sha256 = "a7f85147b59e443dbd986c1f880a0c3ab0190ba7b27c2ce6238da07397fd507b"; - libraryHaskellDepends = [ base bytestring ]; + version = "0.3.1"; + sha256 = "53205f5a7dcb7a0547c9394ddb28a6eeb181627f006b875bfc08a88c498218d6"; + libraryHaskellDepends = [ base bytestring fail ]; doHaddock = false; doCheck = false; homepage = "https://github.com/Yuras/scanner"; description = "Fast non-backtracking incremental combinator parsing for bytestrings"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "scheduler" = callPackage + ({ mkDerivation, atomic-primops, base, deepseq, exceptions, lib + , primitive, pvar, unliftio-core + }: + mkDerivation { + pname = "scheduler"; + version = "1.5.0"; + sha256 = "77175ca365c5f922d73c0e6a16d55b35e0377677f826284d7b54cad5fc604fa7"; + libraryHaskellDepends = [ + atomic-primops base deepseq exceptions primitive pvar unliftio-core + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/lehins/haskell-scheduler"; + description = "Work stealing scheduler"; + license = lib.licenses.bsd3; }) {}; "scientific" = callPackage ({ mkDerivation, base, binary, bytestring, containers, deepseq - , hashable, integer-gmp, integer-logarithms, primitive, stdenv - , text + , hashable, integer-gmp, integer-logarithms, lib, primitive + , template-haskell, text }: mkDerivation { pname = "scientific"; - version = "0.3.6.2"; - sha256 = "278d0afc87450254f8a76eab21b5583af63954efc9b74844a17a21a68013140f"; + version = "0.3.7.0"; + sha256 = "a3a121c4b3d68fb8b9f8c709ab012e48f090ed553609247a805ad070d6b343a9"; libraryHaskellDepends = [ base binary bytestring containers deepseq hashable integer-gmp - integer-logarithms primitive text + integer-logarithms primitive template-haskell text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/basvandijk/scientific"; description = "Numbers represented using scientific notation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "scotty" = callPackage - ({ mkDerivation, aeson, base, blaze-builder, bytestring - , case-insensitive, data-default-class, exceptions, fail - , http-types, monad-control, mtl, nats, network, regex-compat - , stdenv, text, transformers, transformers-base + ({ mkDerivation, aeson, base, base-compat-batteries, blaze-builder + , bytestring, case-insensitive, data-default-class, exceptions + , fail, http-types, lib, monad-control, mtl, nats, network + , regex-compat, text, transformers, transformers-base , transformers-compat, wai, wai-extra, warp }: mkDerivation { pname = "scotty"; - version = "0.11.3"; - sha256 = "0a9c8adb7d5f66ca3ba9e866aed52b87d940e4b8f1fc8f8aca9c663ac304a790"; + version = "0.12"; + sha256 = "e1d77ee05eaa4b1871566b33683da9ab15dda8f7c42875701d62caf7db7defd2"; + revision = "3"; + editedCabalFile = "0lvvfbjf4w73y43ax80h9yb2nvf3n2kc859j9advcmfnmdn33x5v"; libraryHaskellDepends = [ - aeson base blaze-builder bytestring case-insensitive - data-default-class exceptions fail http-types monad-control mtl - nats network regex-compat text transformers transformers-base - transformers-compat wai wai-extra warp + aeson base base-compat-batteries blaze-builder bytestring + case-insensitive data-default-class exceptions fail http-types + monad-control mtl nats network regex-compat text transformers + transformers-base transformers-compat wai wai-extra warp ]; doHaddock = false; doCheck = false; homepage = "https://github.com/scotty-web/scotty"; description = "Haskell web framework inspired by Ruby's Sinatra, using WAI and Warp"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "scrypt" = callPackage - ({ mkDerivation, base, base64-bytestring, bytestring, entropy - , stdenv + ({ mkDerivation, base, base64-bytestring, bytestring, entropy, lib }: mkDerivation { pname = "scrypt"; @@ -29011,16 +34952,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/informatikr/scrypt"; description = "Stronger password hashing via sequential memory-hard functions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "sdl2" = callPackage - ({ mkDerivation, base, bytestring, exceptions, linear, SDL2 - , StateVar, stdenv, text, transformers, vector + ({ mkDerivation, base, bytestring, exceptions, lib, linear, SDL2 + , StateVar, text, transformers, vector }: mkDerivation { pname = "sdl2"; - version = "2.4.1.0"; - sha256 = "21a569c0c19f8ff2bbe1cf1d3eb32f65e8143806de353cedd240df5e9d088b5c"; + version = "2.5.3.0"; + sha256 = "b81860ce376d64bde9827b27a52057fa7ecdc407721961d7e8f66a9116238222"; isLibrary = true; isExecutable = true; enableSeparateDataOutput = true; @@ -29031,18 +34972,20 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; libraryPkgconfigDepends = [ SDL2 ]; doHaddock = false; doCheck = false; - description = "Both high- and low-level bindings to the SDL library (version 2.0.4+)."; - license = stdenv.lib.licenses.bsd3; + description = "Both high- and low-level bindings to the SDL library (version 2.0.6+)."; + license = lib.licenses.bsd3; }) {inherit (pkgs) SDL2;}; "sdl2-gfx" = callPackage - ({ mkDerivation, base, bytestring, lifted-base, linear - , monad-control, SDL2, sdl2, SDL2_gfx, stdenv, template-haskell - , text, transformers, vector + ({ mkDerivation, base, bytestring, lib, lifted-base, linear + , monad-control, SDL2, sdl2, SDL2_gfx, template-haskell, text + , transformers, vector }: mkDerivation { pname = "sdl2-gfx"; version = "0.2"; sha256 = "8c1e10b7a675d782cd650820c75c4ef9225718ad6aaa3f8db02e869b7720c50d"; + revision = "1"; + editedCabalFile = "1gdasf1rq7gszfhin521cni8bxfzanvssznfi8m2fkgwz6ichhpv"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -29054,16 +34997,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Bindings to SDL2_gfx"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {inherit (pkgs) SDL2; inherit (pkgs) SDL2_gfx;}; "sdl2-image" = callPackage - ({ mkDerivation, base, bytestring, SDL2, sdl2, SDL2_image, stdenv + ({ mkDerivation, base, bytestring, lib, SDL2, sdl2, SDL2_image , template-haskell, text, transformers }: mkDerivation { pname = "sdl2-image"; version = "2.0.0"; sha256 = "399742b2b7e64fe4e58c9d8a44ad29b2c355589233535238f8c9b371de6c26df"; + revision = "1"; + editedCabalFile = "0471p3d1ws5n7r072xgk38n3vzs6ijjkmpv1r05vxn6qninlnq6m"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -29074,16 +35019,19 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Bindings to SDL2_image"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {inherit (pkgs) SDL2; inherit (pkgs) SDL2_image;}; "sdl2-mixer" = callPackage - ({ mkDerivation, base, bytestring, data-default-class, lifted-base - , monad-control, sdl2, SDL2_mixer, stdenv, template-haskell, vector + ({ mkDerivation, base, bytestring, data-default-class, lib + , lifted-base, monad-control, sdl2, SDL2_mixer, template-haskell + , vector }: mkDerivation { pname = "sdl2-mixer"; version = "1.1.0"; sha256 = "0f4c15a1bda7b265923278641d686756292fc2a8f1c5ced7f98916cc98df0acd"; + revision = "1"; + editedCabalFile = "06h708gbvl5z590p6fn10ck6yxjzyjjbmvk6mxcwgygbj76sw2f8"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -29095,50 +35043,63 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Bindings to SDL2_mixer"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) SDL2_mixer;}; "sdl2-ttf" = callPackage - ({ mkDerivation, base, bytestring, SDL2, sdl2, SDL2_ttf, stdenv - , template-haskell, text, transformers + ({ mkDerivation, base, bytestring, lib, SDL2, sdl2, SDL2_ttf + , template-haskell, text, th-abstraction, transformers }: mkDerivation { pname = "sdl2-ttf"; - version = "2.1.0"; - sha256 = "c7656fe923e618d3919d47ac753451b08e6d709372380e15bd3d75b39f2c80f7"; + version = "2.1.2"; + sha256 = "edae0e2722d2bc8ed361303804fb80d19c079ae3923ddad982da1cf4c86be349"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - base bytestring sdl2 template-haskell text transformers + base bytestring sdl2 template-haskell text th-abstraction + transformers ]; libraryPkgconfigDepends = [ SDL2 SDL2_ttf ]; doHaddock = false; doCheck = false; description = "Bindings to SDL2_ttf"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) SDL2; inherit (pkgs) SDL2_ttf;}; + "search-algorithms" = callPackage + ({ mkDerivation, base, containers, lib }: + mkDerivation { + pname = "search-algorithms"; + version = "0.3.1"; + sha256 = "9be6f03ff407e115d4d6101dd7da529a560a9b85c723031fb549507466bd03a0"; + libraryHaskellDepends = [ base containers ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/devonhollowood/search-algorithms#readme"; + description = "Common graph search algorithms"; + license = lib.licenses.bsd3; + }) {}; "secp256k1-haskell" = callPackage ({ mkDerivation, base, base16-bytestring, bytestring, cereal - , entropy, hashable, QuickCheck, secp256k1, stdenv - , string-conversions + , deepseq, entropy, hashable, lib, QuickCheck, secp256k1 + , string-conversions, unliftio-core }: mkDerivation { pname = "secp256k1-haskell"; - version = "0.1.4"; - sha256 = "741c9f3d51d4a9fc89c991734f71735f46dffd900f550d5d8564aebc1db0cbed"; + version = "0.5.0"; + sha256 = "edbc125b19143ffe697b483bb92774829d0c704f601ffacadcd5678e2535b7a2"; libraryHaskellDepends = [ - base base16-bytestring bytestring cereal entropy hashable - QuickCheck string-conversions + base base16-bytestring bytestring cereal deepseq entropy hashable + QuickCheck string-conversions unliftio-core ]; - librarySystemDepends = [ secp256k1 ]; + libraryPkgconfigDepends = [ secp256k1 ]; doHaddock = false; doCheck = false; homepage = "http://github.com/haskoin/secp256k1-haskell#readme"; - description = "Bindings for secp256k1 library from Bitcoin Core"; - license = stdenv.lib.licenses.publicDomain; + description = "Bindings for secp256k1"; + license = lib.licenses.mit; }) {inherit (pkgs) secp256k1;}; "securemem" = callPackage - ({ mkDerivation, base, byteable, bytestring, ghc-prim, memory - , stdenv + ({ mkDerivation, base, byteable, bytestring, ghc-prim, lib, memory }: mkDerivation { pname = "securemem"; @@ -29151,66 +35112,170 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/vincenthz/hs-securemem"; description = "abstraction to an auto scrubbing and const time eq, memory chunk"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "selda" = callPackage - ({ mkDerivation, base, bytestring, exceptions, hashable, mtl - , psqueues, stdenv, text, time, unordered-containers + ({ mkDerivation, base, bytestring, containers, exceptions, lib, mtl + , random, text, time, uuid-types }: mkDerivation { pname = "selda"; - version = "0.3.4.0"; - sha256 = "92238cfd3a557f68ccf0cb6edafa4981a5c67c91f85d471c83ba55eec1d884f3"; + version = "0.5.1.0"; + sha256 = "f465dab0199994d77cd060c7d37631709ec593a537c063f901051b8e5f73a7bd"; + revision = "1"; + editedCabalFile = "0sdzfgsmgw20idxnvvf4sbp8bkl3n7qa7qkphv63pfmqvzyplkwg"; libraryHaskellDepends = [ - base bytestring exceptions hashable mtl psqueues text time - unordered-containers + base bytestring containers exceptions mtl random text time + uuid-types ]; doHaddock = false; doCheck = false; homepage = "https://selda.link"; description = "Multi-backend, high-level EDSL for interacting with SQL databases"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "selda-json" = callPackage + ({ mkDerivation, aeson, base, bytestring, lib, selda, text }: + mkDerivation { + pname = "selda-json"; + version = "0.1.1.0"; + sha256 = "88061090d899eb831c72d39de21d6311ab1219e89188f641c777daf22b2622aa"; + revision = "1"; + editedCabalFile = "1gajzv8zhj8i3bxzjh81vjn8j2igh3nrawfpddvxg1ayb5l2d2y0"; + libraryHaskellDepends = [ aeson base bytestring selda text ]; + doHaddock = false; + doCheck = false; + homepage = "https://selda.link"; + description = "JSON support for the Selda database library"; + license = lib.licenses.mit; }) {}; "selda-postgresql" = callPackage - ({ mkDerivation, base, bytestring, exceptions, postgresql-libpq - , selda, stdenv, text + ({ mkDerivation, base, bytestring, exceptions, lib + , postgresql-binary, postgresql-libpq, selda, selda-json, text + , time, uuid-types }: mkDerivation { pname = "selda-postgresql"; - version = "0.1.7.3"; - sha256 = "ec33d2efedc5a9bf81a2acb726e866c4978c96a6ce92e313f0b83aa49b812d2b"; - revision = "2"; - editedCabalFile = "1zrj412hkjjka4cvl5zj6gdpvdafmcny6xighi1glg67n8cmpb67"; + version = "0.1.8.1"; + sha256 = "b386028b30619b1e6251e7c83320151111c87dc23f03963c0b71c9be6964be37"; + revision = "1"; + editedCabalFile = "10qlb9yswjsvpj1f7dmm0amkq52g00f1kc2xqh1d7vfkvkb2bhk6"; libraryHaskellDepends = [ - base bytestring exceptions postgresql-libpq selda text + base bytestring exceptions postgresql-binary postgresql-libpq selda + selda-json text time uuid-types ]; doHaddock = false; doCheck = false; homepage = "https://github.com/valderman/selda"; description = "PostgreSQL backend for the Selda database EDSL"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "selda-sqlite" = callPackage - ({ mkDerivation, base, direct-sqlite, directory, exceptions, selda - , stdenv, text + ({ mkDerivation, base, bytestring, direct-sqlite, directory + , exceptions, lib, selda, text, time, uuid-types }: mkDerivation { pname = "selda-sqlite"; - version = "0.1.6.1"; - sha256 = "8d60dec5376d99b30939e8d6a2d1fbc3363b7cdb12834a27a31f73c73e7e19e3"; - revision = "2"; - editedCabalFile = "0gb8raqmy8r8xwjpx238mqar5gdfd4194si2ms1a9ndcrilkkqja"; + version = "0.1.7.1"; + sha256 = "cb356c6a3d07020681845c56de7036e72a10680caba1b4516a322228c68c39a8"; + revision = "1"; + editedCabalFile = "05zdf07fizf97yby0ld4qkd5padxg9fhmpfiiii4jl7xklccnl6p"; libraryHaskellDepends = [ - base direct-sqlite directory exceptions selda text + base bytestring direct-sqlite directory exceptions selda text time + uuid-types ]; doHaddock = false; doCheck = false; homepage = "https://github.com/valderman/selda"; description = "SQLite backend for the Selda database EDSL"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "selections" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "selections"; + version = "0.3.0.0"; + sha256 = "fc369792dc019574301408c359219f51ad29285a83abea793cb55cf033ce876e"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ChrisPenner/selections#readme"; + description = "Combinators for operating with selections over an underlying functor"; + license = lib.licenses.bsd3; + }) {}; + "selective" = callPackage + ({ mkDerivation, base, containers, lib, transformers }: + mkDerivation { + pname = "selective"; + version = "0.4.2"; + sha256 = "b434ad6f6f72bed4b0bcd55a1c9372368361649fd2042fd580f21337b285e5d5"; + libraryHaskellDepends = [ base containers transformers ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/snowleopard/selective"; + description = "Selective applicative functors"; + license = lib.licenses.mit; + }) {}; + "semialign" = callPackage + ({ mkDerivation, base, containers, hashable, lib, semigroupoids + , tagged, these, transformers, unordered-containers, vector + }: + mkDerivation { + pname = "semialign"; + version = "1.1.0.1"; + sha256 = "9810bddff641bf7446a1939e5f337e368f894d06e3995a536704b3e16b241a87"; + libraryHaskellDepends = [ + base containers hashable semigroupoids tagged these transformers + unordered-containers vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/isomorphism/these"; + description = "Align and Zip type-classes from the common Semialign ancestor"; + license = lib.licenses.bsd3; + }) {}; + "semialign-indexed" = callPackage + ({ mkDerivation, base, containers, hashable, lens, lib, semialign + , these, unordered-containers, vector + }: + mkDerivation { + pname = "semialign-indexed"; + version = "1.1"; + sha256 = "60f1dd3df6b1b1bf6d835209f55d4deedf0587a26a236e0a54c8a4c9a1abcaac"; + revision = "2"; + editedCabalFile = "0vmvmnmb79cc11rbl136z74yyb16klswpx38ayxal8m52lyggqpv"; + libraryHaskellDepends = [ + base containers hashable lens semialign these unordered-containers + vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/isomorphism/these"; + description = "SemialignWithIndex, i.e. izipWith and ialignWith"; + license = lib.licenses.bsd3; + }) {}; + "semialign-optics" = callPackage + ({ mkDerivation, base, containers, hashable, lib, optics-extra + , semialign, these, unordered-containers, vector + }: + mkDerivation { + pname = "semialign-optics"; + version = "1.1"; + sha256 = "3e95b5f241c65a1124955492a8febf01cd02dc01b2a02a8bb7b66918a65dd1b9"; + revision = "2"; + editedCabalFile = "011kjr5ya0s7l1dic7gvzvgvps02rn033125v8c9r9dp2mlgyjam"; + libraryHaskellDepends = [ + base containers hashable optics-extra semialign these + unordered-containers vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/isomorphism/these"; + description = "SemialignWithIndex, i.e. izipWith and ialignWith"; + license = lib.licenses.bsd3; }) {}; "semigroupoid-extras" = callPackage - ({ mkDerivation, base, profunctors, semigroupoids, stdenv }: + ({ mkDerivation, base, lib, profunctors, semigroupoids }: mkDerivation { pname = "semigroupoid-extras"; version = "5"; @@ -29220,19 +35285,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/semigroupoid-extras"; description = "Semigroupoids that depend on PolyKinds"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "semigroupoids" = callPackage - ({ mkDerivation, base, base-orphans, bifunctors, Cabal - , cabal-doctest, comonad, containers, contravariant, distributive - , hashable, stdenv, tagged, template-haskell, transformers - , transformers-compat, unordered-containers + ({ mkDerivation, base, base-orphans, bifunctors, comonad + , containers, contravariant, distributive, hashable, lib, tagged + , template-haskell, transformers, transformers-compat + , unordered-containers }: mkDerivation { pname = "semigroupoids"; - version = "5.3.2"; - sha256 = "61a8213df437ee96a20b1c6dec8b5c573e4e0f338eb2061739a67f471d6b9d05"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "5.3.5"; + sha256 = "552f18e13ef347118911c950957e4adcda0a1f948e274f29ec449cc413d3c6b0"; libraryHaskellDepends = [ base base-orphans bifunctors comonad containers contravariant distributive hashable tagged template-haskell transformers @@ -29242,23 +35306,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/semigroupoids"; description = "Semigroupoids: Category sans id"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "semigroups" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "semigroups"; - version = "0.18.5"; - sha256 = "ab2a96af6e81e31b909c37ba65f436f1493dbf387cfe0de10b6586270c4ce29d"; + version = "0.19.1"; + sha256 = "79e761e64b862564a3470d5d356cb6b060b14452d675859aed3b2d1e14646648"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/semigroups/"; description = "Anything that associates"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "semiring-simple" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "semiring-simple"; version = "1.0.0.1"; @@ -29267,54 +35331,72 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A module for dealing with semirings"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "semirings" = callPackage - ({ mkDerivation, base, containers, hashable, integer-gmp, stdenv - , unordered-containers, vector + ({ mkDerivation, base, base-compat-batteries, containers, hashable + , lib, unordered-containers }: mkDerivation { pname = "semirings"; - version = "0.2.1.1"; - sha256 = "576a5b09e8b0045e13fab04f5a53eaead69c5b0bca99e3cdfff88be90cc64868"; + version = "0.6"; + sha256 = "99356619b137c7c4cf6597909be3c9df118f08a7dff4897549e350b95719059b"; libraryHaskellDepends = [ - base containers hashable integer-gmp unordered-containers vector + base base-compat-batteries containers hashable unordered-containers ]; doHaddock = false; doCheck = false; homepage = "http://github.com/chessai/semirings"; description = "two monoids as one, in holy haskimony"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "semver" = callPackage - ({ mkDerivation, attoparsec, base, deepseq, stdenv, text }: + ({ mkDerivation, attoparsec, base, deepseq, hashable, lib, text }: mkDerivation { pname = "semver"; - version = "0.3.3.1"; - sha256 = "36d3369706836d60f3bc517f30c6860734481866363723904b8768823b6bc8b1"; - libraryHaskellDepends = [ attoparsec base deepseq text ]; + version = "0.4.0.1"; + sha256 = "7c47e326684efe407b2dc77924aa71c57c712465a9ed39c4097e6c1e1a1ff641"; + revision = "1"; + editedCabalFile = "13c692s2fbn6xygw70aglj84a8hq549gcj1p40g11j77w68p9xx4"; + libraryHaskellDepends = [ attoparsec base deepseq hashable text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/semver"; description = "Representation, manipulation, and de/serialisation of Semantic Versions"; - license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; + license = lib.licenses.mpl20; }) {}; "sendfile" = callPackage - ({ mkDerivation, base, bytestring, network, stdenv }: + ({ mkDerivation, base, bytestring, lib, network }: mkDerivation { pname = "sendfile"; - version = "0.7.9"; - sha256 = "102fdf6db8c00f5a5981c6eed5acba1368a2d79b2970ce5b22ceb180aa0fdc42"; + version = "0.7.11.1"; + sha256 = "e0e6c45e73578d2d7139e23a965937ac4514e5d310613607bfd4afd1abd50825"; libraryHaskellDepends = [ base bytestring network ]; doHaddock = false; doCheck = false; homepage = "http://hub.darcs.net/stepcut/sendfile"; description = "A portable sendfile library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "sendgrid-v3" = callPackage + ({ mkDerivation, aeson, base, bytestring, http-client, lens, lib + , semigroups, text, wreq + }: + mkDerivation { + pname = "sendgrid-v3"; + version = "0.3.0.0"; + sha256 = "958519798512ef3ad9ce2c69362b02b7080e5c1644379bfc7bc30dfc4116352c"; + libraryHaskellDepends = [ + aeson base bytestring http-client lens semigroups text wreq + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/marcelbuesing/sendgrid-v3"; + description = "Sendgrid v3 API library"; + license = lib.licenses.mit; }) {}; "seqalign" = callPackage - ({ mkDerivation, base, bytestring, stdenv, vector }: + ({ mkDerivation, base, bytestring, lib, vector }: mkDerivation { pname = "seqalign"; version = "0.2.0.4"; @@ -29323,11 +35405,83 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Sequence Alignment"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "seqid" = callPackage + ({ mkDerivation, base, lib, mtl, transformers }: + mkDerivation { + pname = "seqid"; + version = "0.6.2"; + sha256 = "1178e5efafdf74a3c0305e35324f146dfc099821ccfad5d9b718d39173bbbd1f"; + libraryHaskellDepends = [ base mtl transformers ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/bitnomial/seqid"; + description = "Sequence ID production and consumption"; + license = lib.licenses.bsd3; + }) {}; + "seqid-streams" = callPackage + ({ mkDerivation, base, io-streams, lib, seqid }: + mkDerivation { + pname = "seqid-streams"; + version = "0.7.2"; + sha256 = "a85a55e319c321c5cc4f8c95b2308487469ff3ff30913f1b04319b2074dfa035"; + libraryHaskellDepends = [ base io-streams seqid ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/bitnomial/seqid-streams"; + description = "Sequence ID IO-Streams"; + license = lib.licenses.bsd3; + }) {}; + "sequence-formats" = callPackage + ({ mkDerivation, attoparsec, base, bytestring, containers, errors + , exceptions, foldl, lens-family, lib, pipes, pipes-attoparsec + , pipes-bytestring, pipes-safe, transformers, vector + }: + mkDerivation { + pname = "sequence-formats"; + version = "1.6.1"; + sha256 = "4a543750d8ba866b32861f0bc48dfb056ca40f0cf4a96738f402fd7495425764"; + libraryHaskellDepends = [ + attoparsec base bytestring containers errors exceptions foldl + lens-family pipes pipes-attoparsec pipes-bytestring pipes-safe + transformers vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/stschiff/sequence-formats"; + description = "A package with basic parsing utilities for several Bioinformatic data formats"; + license = lib.licenses.gpl3Only; + }) {}; + "sequenceTools" = callPackage + ({ mkDerivation, ansi-wl-pprint, base, bytestring, foldl + , lens-family, lib, optparse-applicative, pipes, pipes-group + , pipes-ordered-zip, pipes-safe, random, rio, sequence-formats + , split, vector + }: + mkDerivation { + pname = "sequenceTools"; + version = "1.5.0"; + sha256 = "cc404da3036429680aad9582cce4e9979fdad804d0de7f14f886816cd1987770"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base bytestring optparse-applicative pipes random sequence-formats + vector + ]; + executableHaskellDepends = [ + ansi-wl-pprint base bytestring foldl lens-family + optparse-applicative pipes pipes-group pipes-ordered-zip pipes-safe + random rio sequence-formats split vector + ]; + doHaddock = false; + doCheck = false; + description = "A package with tools for processing DNA sequencing data"; + license = lib.licenses.gpl3Only; }) {}; "serf" = callPackage - ({ mkDerivation, attoparsec, base, conduit, conduit-extra, mtl - , operational, process, resourcet, stdenv, text + ({ mkDerivation, attoparsec, base, conduit, conduit-extra, lib, mtl + , operational, process, resourcet, text }: mkDerivation { pname = "serf"; @@ -29341,18 +35495,20 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/sanetracker/serf"; description = "Interact with Serf via Haskell"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "serialise" = callPackage ({ mkDerivation, array, base, bytestring, cborg, containers - , ghc-prim, half, hashable, primitive, stdenv, text, time + , ghc-prim, half, hashable, lib, primitive, text, time , unordered-containers, vector }: mkDerivation { pname = "serialise"; - version = "0.2.1.0"; - sha256 = "043efc1130b4202f080c5b7d2c319098df032b060655d8193f1fcdbfa3f159a5"; - libraryHaskellDepends = [ + version = "0.2.3.0"; + sha256 = "c9789fb3c3ffd215879ce33961d61f82dd90a36ecf697d41e8b7c67ebbe7e46e"; + revision = "2"; + editedCabalFile = "1qcsp15v0swxy2qlvc40fil09zq32y3wl00y3passc2a4b4yhmr4"; + libraryHaskellDepends = [ array base bytestring cborg containers ghc-prim half hashable primitive text time unordered-containers vector ]; @@ -29360,101 +35516,79 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/well-typed/cborg"; description = "A binary serialisation library for Haskell values"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "servant" = callPackage ({ mkDerivation, aeson, attoparsec, base, base-compat, bifunctors - , bytestring, Cabal, cabal-doctest, case-insensitive, http-api-data - , http-media, http-types, mmorph, mtl, network-uri, QuickCheck - , singleton-bool, stdenv, string-conversions, tagged, text + , bytestring, case-insensitive, deepseq, http-api-data, http-media + , http-types, lib, mmorph, mtl, network-uri, QuickCheck + , singleton-bool, sop-core, string-conversions, tagged, text , transformers, vault }: mkDerivation { pname = "servant"; - version = "0.15"; - sha256 = "4f3f35c9c0f5e4ee8c2d10c9113ac4a6409a4d57759137e68f43588f5e6bfa39"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "0.18.3"; + sha256 = "b76bf198a4dddfa9b03d5ac750e5ed3a60fa24052dedb138932ba943519d7e0c"; libraryHaskellDepends = [ aeson attoparsec base base-compat bifunctors bytestring - case-insensitive http-api-data http-media http-types mmorph mtl - network-uri QuickCheck singleton-bool string-conversions tagged - text transformers vault + case-insensitive deepseq http-api-data http-media http-types mmorph + mtl network-uri QuickCheck singleton-bool sop-core + string-conversions tagged text transformers vault ]; doHaddock = false; doCheck = false; - homepage = "http://haskell-servant.readthedocs.org/"; + homepage = "http://docs.servant.dev/"; description = "A family of combinators for defining webservices APIs"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "servant-JuicyPixels" = callPackage - ({ mkDerivation, base, bytestring, http-media, JuicyPixels, servant - , servant-server, stdenv, wai, warp + "servant-auth" = callPackage + ({ mkDerivation, aeson, base, jose, lens, lib, servant, text + , unordered-containers }: mkDerivation { - pname = "servant-JuicyPixels"; - version = "0.3.0.4"; - sha256 = "7b02f00ac8b78ffda49a96f2d1f39619ec19f244822d177928e75cd533cb9981"; - revision = "1"; - editedCabalFile = "185ym0ac6gx7f98pd92ykc1ib305lswzjzvykly4ij9vk85jn0ax"; - isLibrary = true; - isExecutable = true; + pname = "servant-auth"; + version = "0.4.0.0"; + sha256 = "01cacafa34bdb0aac88ae31d9f12ee6fa349fcb76acc2592e697cba926404f6c"; + revision = "3"; + editedCabalFile = "1hq0mz4fm2f6v57jzyahk5wfip285v3yh20dawvmwdh7wq6104zr"; libraryHaskellDepends = [ - base bytestring http-media JuicyPixels servant - ]; - executableHaskellDepends = [ - base JuicyPixels servant servant-server wai warp + aeson base jose lens servant text unordered-containers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/tvh/servant-JuicyPixels"; - description = "Servant support for JuicyPixels"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "servant-auth" = callPackage - ({ mkDerivation, base, stdenv }: - mkDerivation { - pname = "servant-auth"; - version = "0.3.2.0"; - sha256 = "7bb4d5118c072cb3845aaba4287b2d5e34e5ccca96916895456a828bf7a9418b"; - revision = "1"; - editedCabalFile = "10ss4v45lclf5n0k6rch22zzs59v7p5ppd04dbc97pqxiygpbnd9"; - libraryHaskellDepends = [ base ]; - doHaddock = false; - doCheck = false; homepage = "http://github.com/haskell-servant/servant-auth#readme"; description = "Authentication combinators for servant"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "servant-auth-client" = callPackage - ({ mkDerivation, base, bytestring, containers, servant - , servant-auth, servant-client-core, stdenv, text + ({ mkDerivation, base, bytestring, containers, lib, servant + , servant-auth, servant-client-core }: mkDerivation { pname = "servant-auth-client"; - version = "0.3.3.0"; - sha256 = "490ac57150b59c567ef567120a6704cfc2184f7be8e6edaab26ad818dee5b3df"; + version = "0.4.1.0"; + sha256 = "03c1c9e1413c05ae30c269a2fef07e68bf41ff675edd180452d863d073e3359b"; revision = "2"; - editedCabalFile = "05ibhx700r0xn746g691ypysnjgxqb0lkq2gjrih5ylzc7nfvv2s"; + editedCabalFile = "0mq9nhrlh44jxkngj06pasrrjzv5193lj6d2szprnncgrk36zi31"; libraryHaskellDepends = [ base bytestring containers servant servant-auth servant-client-core - text ]; doHaddock = false; doCheck = false; homepage = "http://github.com/haskell-servant/servant-auth#readme"; description = "servant-client/servant-auth compatibility"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "servant-auth-docs" = callPackage - ({ mkDerivation, base, Cabal, cabal-doctest, lens, servant - , servant-auth, servant-docs, stdenv, text + ({ mkDerivation, base, Cabal, cabal-doctest, lens, lib, servant + , servant-auth, servant-docs, text }: mkDerivation { pname = "servant-auth-docs"; version = "0.2.10.0"; sha256 = "adf3c33ce4134a78ae7a5c06092ea5812c99d4b942ff2dd685995eb3b2b53e48"; - revision = "2"; - editedCabalFile = "0309a6pc8jj24xwqmzj1yslgij9g212hnaqh2qkcvlm6k6riffil"; + revision = "8"; + editedCabalFile = "01mb003lajxs1x82k20dbnxzdvxdla51vi4dh4f0a1xycvyhfpyi"; setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ base lens servant servant-auth servant-docs text @@ -29463,45 +35597,43 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/haskell-servant/servant-auth#readme"; description = "servant-docs/servant-auth compatibility"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "servant-auth-server" = callPackage ({ mkDerivation, aeson, base, base64-bytestring, blaze-builder - , bytestring, bytestring-conversion, case-insensitive, cookie - , crypto-api, data-default-class, entropy, http-api-data - , http-types, jose, lens, monad-time, mtl, servant, servant-auth - , servant-server, stdenv, tagged, text, time, unordered-containers - , wai + , bytestring, case-insensitive, cookie, data-default-class, entropy + , http-types, jose, lens, lib, memory, monad-time, mtl, servant + , servant-auth, servant-server, tagged, text, time + , unordered-containers, wai }: mkDerivation { pname = "servant-auth-server"; - version = "0.4.2.0"; - sha256 = "57116507c08c97d152b9701563f64343d2ccef2b87be537b558805dd7efc1a00"; + version = "0.4.6.0"; + sha256 = "73de660d9babb2610fd6a928d702397081ebdeda22e301df457a39f8ff4d5447"; revision = "3"; - editedCabalFile = "1zjxqlfyw3wwlyq2faiq9gqhfixn2mvfsv8dapalxs9fph7a2nzj"; + editedCabalFile = "0iasfns12wab45hf4qkwm5bx1z63ass9n5sh926wnn82g1v6qdyw"; libraryHaskellDepends = [ aeson base base64-bytestring blaze-builder bytestring - bytestring-conversion case-insensitive cookie crypto-api - data-default-class entropy http-api-data http-types jose lens - monad-time mtl servant servant-auth servant-server tagged text time - unordered-containers wai + case-insensitive cookie data-default-class entropy http-types jose + lens memory monad-time mtl servant servant-auth servant-server + tagged text time unordered-containers wai ]; doHaddock = false; doCheck = false; homepage = "http://github.com/haskell-servant/servant-auth#readme"; description = "servant-server/servant-auth compatibility"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "servant-auth-swagger" = callPackage - ({ mkDerivation, base, lens, servant, servant-auth, servant-swagger - , stdenv, swagger2, text + ({ mkDerivation, base, lens, lib, servant, servant-auth + , servant-swagger, swagger2, text }: mkDerivation { pname = "servant-auth-swagger"; - version = "0.2.10.0"; - sha256 = "50a783639eb882fd5047d69245f7770817658814d8c409b547ebdddae05acd12"; - revision = "1"; - editedCabalFile = "105rniz4cmmwr0ynyv75s4ap1fgfwxy2k5mvvj66gwpvzmj55cnx"; + version = "0.2.10.1"; + sha256 = "bea98514817ad718a9402658deb5de36ff7856c0ec2d23a04289f2cec9da3609"; + revision = "3"; + editedCabalFile = "1hkszdp7c7c34b2yp2gb7khzlzq8iw5ma066r30kq2nw5jj895k0"; libraryHaskellDepends = [ base lens servant servant-auth servant-swagger swagger2 text ]; @@ -29509,100 +35641,49 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/haskell-servant/servant-auth#readme"; description = "servant-swagger/servant-auth compatibility"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "servant-blaze" = callPackage - ({ mkDerivation, base, blaze-html, http-media, servant, stdenv }: - mkDerivation { - pname = "servant-blaze"; - version = "0.8"; - sha256 = "46ea88550123d765b2d09073370d0530a51878e7fdf2cf20b070be1f2f10ae94"; - revision = "2"; - editedCabalFile = "1cfla60vn4kk5gb7fawlp34jr2k6b2fprysq05561wdfv990x4bj"; - libraryHaskellDepends = [ base blaze-html http-media servant ]; - doHaddock = false; - doCheck = false; - homepage = "http://haskell-servant.readthedocs.org/"; - description = "Blaze-html support for servant"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "servant-cassava" = callPackage - ({ mkDerivation, base, base-compat, bytestring, cassava, http-media - , servant, stdenv, vector - }: - mkDerivation { - pname = "servant-cassava"; - version = "0.10"; - sha256 = "9b2c5d906f3a4bb2767b2ce91f12a74e24adceadd296220b5d7216c5e1f3560e"; - revision = "4"; - editedCabalFile = "0kk7vqnh5ycrvhrvhi3ahva6v56fvi17k3qrh8a8qnhx25094jaj"; - libraryHaskellDepends = [ - base base-compat bytestring cassava http-media servant vector - ]; - doHaddock = false; - doCheck = false; - homepage = "http://haskell-servant.readthedocs.org/"; - description = "Servant CSV content-type for cassava"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "servant-checked-exceptions" = callPackage - ({ mkDerivation, aeson, base, bytestring, deepseq, http-media - , http-types, profunctors, servant, servant-checked-exceptions-core - , servant-client, servant-client-core, servant-docs, servant-server - , stdenv, tagged, text, wai, world-peace + "servant-auth-wordpress" = callPackage + ({ mkDerivation, base, lib, mtl, servant-server, text, time, wai + , wordpress-auth }: mkDerivation { - pname = "servant-checked-exceptions"; - version = "2.0.0.0"; - sha256 = "a7f282857e56d5d1a59d055cf1936cab96a2cdc2f94a79ff736f7ef1cf56f688"; - isLibrary = true; - isExecutable = true; + pname = "servant-auth-wordpress"; + version = "1.0.0.2"; + sha256 = "b6ec0b62228ddfc6a614ecf54a3f0c4953d6027874f94ad963420d4ead2a9648"; libraryHaskellDepends = [ - aeson base bytestring deepseq http-media http-types profunctors - servant servant-checked-exceptions-core servant-client - servant-client-core servant-docs servant-server tagged text wai - world-peace + base mtl servant-server text time wai wordpress-auth ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/cdepillabout/servant-checked-exceptions"; - description = "Checked exceptions for Servant APIs"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/prikhi/wordpress-auth#readme"; + description = "Authenticate Routes Using Wordpress Cookies"; + license = lib.licenses.bsd3; }) {}; - "servant-checked-exceptions-core" = callPackage - ({ mkDerivation, aeson, base, bytestring, deepseq, http-media - , http-types, profunctors, servant, servant-docs, stdenv, tagged - , text, world-peace - }: + "servant-blaze" = callPackage + ({ mkDerivation, base, blaze-html, http-media, lib, servant }: mkDerivation { - pname = "servant-checked-exceptions-core"; - version = "2.0.0.0"; - sha256 = "aad3513403241bb06aadc605e6af88a5f3aaa0f1f208aafed6d69e15a23ab248"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - aeson base bytestring deepseq http-media http-types profunctors - servant servant-docs tagged text world-peace - ]; + pname = "servant-blaze"; + version = "0.9.1"; + sha256 = "264aa17b95400a13cf23f7421f54b3a3160119c15380a31a96bdfc4a40f2db21"; + libraryHaskellDepends = [ base blaze-html http-media servant ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/cdepillabout/servant-checked-exceptions"; - description = "Checked exceptions for Servant APIs"; - license = stdenv.lib.licenses.bsd3; + homepage = "http://haskell-servant.readthedocs.org/"; + description = "Blaze-html support for servant"; + license = lib.licenses.bsd3; }) {}; "servant-client" = callPackage ({ mkDerivation, base, base-compat, bytestring, containers, deepseq , exceptions, http-client, http-media, http-types, kan-extensions - , monad-control, mtl, semigroupoids, servant, servant-client-core - , stdenv, stm, text, time, transformers, transformers-base - , transformers-compat + , lib, monad-control, mtl, semigroupoids, servant + , servant-client-core, stm, text, time, transformers + , transformers-base, transformers-compat }: mkDerivation { pname = "servant-client"; - version = "0.15"; - sha256 = "2a6c731a479f68ea8f7fe3e124b8b87d14ca9c385ed0751a70461a3c59540a25"; - revision = "1"; - editedCabalFile = "1h3j8mpnrbpc1i4appf8g4zn7h30f6ybg6fg3w057kz18bk9y76f"; + version = "0.18.3"; + sha256 = "4076a5c71c74af688a4d18e47b37c1e318bc0b52a60b6aac9fd37ef1533fb635"; libraryHaskellDepends = [ base base-compat bytestring containers deepseq exceptions http-client http-media http-types kan-extensions monad-control mtl @@ -29611,322 +35692,336 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; ]; doHaddock = false; doCheck = false; - homepage = "http://haskell-servant.readthedocs.org/"; + homepage = "http://docs.servant.dev/"; description = "Automatic derivation of querying functions for servant"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "servant-client-core" = callPackage ({ mkDerivation, aeson, base, base-compat, base64-bytestring - , bytestring, containers, deepseq, exceptions, free, generics-sop - , http-media, http-types, network-uri, safe, servant, stdenv + , bytestring, containers, deepseq, exceptions, free, http-media + , http-types, lib, network-uri, safe, servant, sop-core , template-haskell, text, transformers }: mkDerivation { pname = "servant-client-core"; - version = "0.15"; - sha256 = "9b8e49e5e3cdda9216c393164e7c4b6d693bb159959dd52648f27f7adbca7960"; + version = "0.18.3"; + sha256 = "4df712ac78a6ffa7fd802cf6f32dba919a809ffcb7760e561cb3d6eabb2296c6"; libraryHaskellDepends = [ aeson base base-compat base64-bytestring bytestring containers - deepseq exceptions free generics-sop http-media http-types - network-uri safe servant template-haskell text transformers + deepseq exceptions free http-media http-types network-uri safe + servant sop-core template-haskell text transformers ]; doHaddock = false; doCheck = false; - homepage = "http://haskell-servant.readthedocs.org/"; + homepage = "http://docs.servant.dev/"; description = "Core functionality and class for client function generation for servant APIs"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "servant-conduit" = callPackage + ({ mkDerivation, base, bytestring, conduit, lib, mtl, resourcet + , servant, unliftio-core + }: + mkDerivation { + pname = "servant-conduit"; + version = "0.15.1"; + sha256 = "97b7adc02b666badbd1410aa0ad88828a1c131100167139a17f583753d8cc3ef"; + revision = "1"; + editedCabalFile = "0j7jrwyj6vnfr8wyyzjjm6gakx401aylrq8shc2y9ciy0mhf8lrv"; + libraryHaskellDepends = [ + base bytestring conduit mtl resourcet servant unliftio-core + ]; + doHaddock = false; + doCheck = false; + homepage = "http://docs.servant.dev/"; + description = "Servant Stream support for conduit"; + license = lib.licenses.bsd3; }) {}; "servant-docs" = callPackage ({ mkDerivation, aeson, aeson-pretty, base, base-compat, bytestring - , case-insensitive, control-monad-omega, hashable, http-media - , http-types, lens, servant, stdenv, string-conversions, text + , case-insensitive, hashable, http-media, http-types, lens, lib + , servant, string-conversions, text, universe-base , unordered-containers }: mkDerivation { pname = "servant-docs"; - version = "0.11.3"; - sha256 = "07eb88550b5a5354aed4bfe74f0e4099e17fae99477e0db83a072b50070cda33"; + version = "0.11.9"; + sha256 = "d31281e32f0a7ee6f5d976d755052a26dc7c92c2d8e72c522b52ac4fbbf7d27a"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ aeson aeson-pretty base base-compat bytestring case-insensitive - control-monad-omega hashable http-media http-types lens servant - string-conversions text unordered-containers + hashable http-media http-types lens servant string-conversions text + universe-base unordered-containers ]; executableHaskellDepends = [ aeson base lens servant string-conversions text ]; doHaddock = false; doCheck = false; - homepage = "http://haskell-servant.readthedocs.org/"; + homepage = "http://docs.servant.dev/"; description = "generate API docs for your servant webservice"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "servant-elm" = callPackage - ({ mkDerivation, base, elm-export, lens, servant, servant-foreign - , stdenv, text, wl-pprint-text + ({ mkDerivation, aeson, base, directory, elm-bridge, lens, lib + , servant, servant-foreign, text, wl-pprint-text }: mkDerivation { pname = "servant-elm"; - version = "0.5.0.0"; - sha256 = "d9d96eeaf209f93791f3c81a5b2afad7be443f9af29f362ec17661436895b950"; + version = "0.7.2"; + sha256 = "1e732dc208c645b7527740d7157c764fb5913fd42bdf4509b3ba7045fec4c7c2"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - base elm-export lens servant servant-foreign text wl-pprint-text + aeson base directory elm-bridge lens servant servant-foreign text + wl-pprint-text ]; doHaddock = false; doCheck = false; homepage = "http://github.com/mattjbray/servant-elm#readme"; description = "Automatically derive Elm functions to query servant webservices"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "servant-errors" = callPackage + ({ mkDerivation, aeson, base, base-compat, bytestring + , http-api-data, http-media, http-types, lib, scientific, servant + , string-conversions, text, unordered-containers, wai + }: + mkDerivation { + pname = "servant-errors"; + version = "0.1.6.0"; + sha256 = "3b41ff67cefca634580a03f7eb0082a68d6dd6cbfd61fea242845ec816475761"; + libraryHaskellDepends = [ + aeson base base-compat bytestring http-api-data http-media + http-types scientific servant string-conversions text + unordered-containers wai + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/epicallan/servant-errors"; + description = "Servant Errors wai-middlware"; + license = lib.licenses.mit; }) {}; "servant-exceptions" = callPackage - ({ mkDerivation, aeson, base, exceptions, http-media, http-types - , mtl, servant, servant-server, stdenv, text, wai, warp + ({ mkDerivation, aeson, base, exceptions, http-types, lib, servant + , text }: mkDerivation { pname = "servant-exceptions"; - version = "0.1.1"; - sha256 = "652b9fdc463200ebb8c2b2e0757f9d90662408bf45a657b3f719d0a36d34abe1"; - isLibrary = true; - isExecutable = true; + version = "0.2.1"; + sha256 = "2b11bbf1e53647e9b7796c7ededd173ece96b188ae634a6179ce8e7e1053fdaf"; libraryHaskellDepends = [ - aeson base exceptions http-media http-types mtl servant - servant-server text wai - ]; - executableHaskellDepends = [ - aeson base exceptions http-types servant-server text warp + aeson base exceptions http-types servant text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/ch1bo/servant-exceptions#readme"; - license = stdenv.lib.licenses.bsd3; + description = "Extensible exceptions for servant APIs"; + license = lib.licenses.bsd3; }) {}; - "servant-foreign" = callPackage - ({ mkDerivation, base, base-compat, http-types, lens, servant - , stdenv, text + "servant-exceptions-server" = callPackage + ({ mkDerivation, base, exceptions, http-media, http-types, lib, mtl + , servant, servant-exceptions, servant-server, text, wai }: mkDerivation { - pname = "servant-foreign"; - version = "0.15"; - sha256 = "f1197f1319a735b37c5fdd991556bf34b780a9b87d0e57d936a42ae6734bbd73"; + pname = "servant-exceptions-server"; + version = "0.2.1"; + sha256 = "2f798e32f20eb42c89ef642a12fbbe51056d28c49ec376fd0cbd26d0a168a9b3"; libraryHaskellDepends = [ - base base-compat http-types lens servant text + base exceptions http-media http-types mtl servant + servant-exceptions servant-server text wai ]; doHaddock = false; doCheck = false; - homepage = "http://haskell-servant.readthedocs.org/"; - description = "Helpers for generating clients for servant APIs in any programming language"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/ch1bo/servant-exceptions#readme"; + description = "Extensible exceptions for servant API servers"; + license = lib.licenses.bsd3; }) {}; - "servant-js" = callPackage - ({ mkDerivation, base, base-compat, charset, lens, servant - , servant-foreign, stdenv, text + "servant-foreign" = callPackage + ({ mkDerivation, base, base-compat, http-types, lens, lib, servant + , text }: mkDerivation { - pname = "servant-js"; - version = "0.9.4"; - sha256 = "f86ba73d38644a74ccec50c378df66ab4863664e83359b8866cf17fbf08b3c10"; - isLibrary = true; - isExecutable = true; + pname = "servant-foreign"; + version = "0.15.4"; + sha256 = "bf1e6665156c638db861e34cb513f74031a7f184af5f62cf9bcfbd95c759f62f"; libraryHaskellDepends = [ - base base-compat charset lens servant servant-foreign text + base base-compat http-types lens servant text ]; doHaddock = false; doCheck = false; - homepage = "http://haskell-servant.readthedocs.org/"; - description = "Automatically derive javascript functions to query servant webservices"; - license = stdenv.lib.licenses.bsd3; + homepage = "http://docs.servant.dev/"; + description = "Helpers for generating clients for servant APIs in any programming language"; + license = lib.licenses.bsd3; }) {}; - "servant-kotlin" = callPackage - ({ mkDerivation, base, containers, directory, formatting, lens - , servant, servant-foreign, stdenv, text, time, wl-pprint-text + "servant-http-streams" = callPackage + ({ mkDerivation, base, base-compat, bytestring, case-insensitive + , containers, deepseq, exceptions, http-common, http-media + , http-streams, http-types, io-streams, kan-extensions, lib + , monad-control, mtl, semigroupoids, servant, servant-client-core + , text, time, transformers, transformers-base, transformers-compat }: mkDerivation { - pname = "servant-kotlin"; - version = "0.1.1.5"; - sha256 = "dbf2f037523d25ca2c81c82490ebad8c8e616c760d092e39ad047965981ffd71"; + pname = "servant-http-streams"; + version = "0.18.3"; + sha256 = "ca159d06d34975fdae8849fd45f10850cf3975e0e63ce7cbf5c112fc57c58431"; libraryHaskellDepends = [ - base containers directory formatting lens servant servant-foreign - text time wl-pprint-text + base base-compat bytestring case-insensitive containers deepseq + exceptions http-common http-media http-streams http-types + io-streams kan-extensions monad-control mtl semigroupoids servant + servant-client-core text time transformers transformers-base + transformers-compat ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/matsubara0507/servant-kotlin#readme"; - description = "Automatically derive Kotlin class to query servant webservices"; - license = stdenv.lib.licenses.mit; + homepage = "http://docs.servant.dev/"; + description = "Automatic derivation of querying functions for servant"; + license = lib.licenses.bsd3; }) {}; - "servant-lucid" = callPackage - ({ mkDerivation, base, http-media, lucid, servant, stdenv, text }: + "servant-machines" = callPackage + ({ mkDerivation, base, bytestring, lib, machines, mtl, servant }: mkDerivation { - pname = "servant-lucid"; - version = "0.8.1"; - sha256 = "6671d5d5e29b05911bb8855f42168839c2dbb8ee113a10cef6dd372fc267113d"; + pname = "servant-machines"; + version = "0.15.1"; + sha256 = "44b5672204a188aaeb4874646838cf854c6865ef53d62d1cfbab6871185b0a4d"; revision = "1"; - editedCabalFile = "0jna96jy6nmhk6w5zxdd3qn3vlrnhnvh4s3f2bqkn3c0had5py7d"; - libraryHaskellDepends = [ base http-media lucid servant text ]; + editedCabalFile = "0zplgs1kqfmnnx8yv8ay594misiamgmvy41b8w1h3mr7n4vrgk8j"; + libraryHaskellDepends = [ base bytestring machines mtl servant ]; doHaddock = false; doCheck = false; - homepage = "http://haskell-servant.readthedocs.org/"; - description = "Servant support for lucid"; - license = stdenv.lib.licenses.bsd3; + homepage = "http://docs.servant.dev/"; + description = "Servant Stream support for machines"; + license = lib.licenses.bsd3; }) {}; - "servant-mock" = callPackage - ({ mkDerivation, aeson, base, base-compat, bytestring, http-types - , QuickCheck, servant, servant-server, stdenv, transformers, wai - , warp + "servant-multipart" = callPackage + ({ mkDerivation, base, bytestring, directory, lens, lib, resourcet + , servant, servant-docs, servant-foreign, servant-multipart-api + , servant-server, string-conversions, text, wai, wai-extra }: mkDerivation { - pname = "servant-mock"; - version = "0.8.5"; - sha256 = "ae547026ddc5d15bec0af9ea9324954f88dd605cae0775c81c45b1723dc77b81"; - isLibrary = true; - isExecutable = true; + pname = "servant-multipart"; + version = "0.12.1"; + sha256 = "c5236fa4922a869947988d52ab9f5b0a19abf57bb0467e2eb34560f8c79aa5dc"; libraryHaskellDepends = [ - base base-compat bytestring http-types QuickCheck servant - servant-server transformers wai + base bytestring directory lens resourcet servant servant-docs + servant-foreign servant-multipart-api servant-server + string-conversions text wai wai-extra ]; - executableHaskellDepends = [ - aeson base QuickCheck servant-server warp + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell-servant/servant-multipart#readme"; + description = "multipart/form-data (e.g file upload) support for servant"; + license = lib.licenses.bsd3; + }) {}; + "servant-multipart-api" = callPackage + ({ mkDerivation, base, bytestring, lib, servant, text, transformers + }: + mkDerivation { + pname = "servant-multipart-api"; + version = "0.12.1"; + sha256 = "92d5c3b1ccbcde7abcff6eb639d7dbb836222452a965e73ebd40bf775e522ebe"; + libraryHaskellDepends = [ + base bytestring servant text transformers ]; doHaddock = false; doCheck = false; - homepage = "http://haskell-servant.readthedocs.org/"; - description = "Derive a mock server for free from your servant API types"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/haskell-servant/servant-multipart#readme"; + description = "multipart/form-data (e.g file upload) support for servant"; + license = lib.licenses.bsd3; }) {}; - "servant-pandoc" = callPackage - ({ mkDerivation, base, bytestring, case-insensitive, http-media - , lens, pandoc-types, servant-docs, stdenv, string-conversions - , text, unordered-containers + "servant-openapi3" = callPackage + ({ mkDerivation, aeson, aeson-pretty, base, base-compat, bytestring + , Cabal, cabal-doctest, hspec, http-media + , insert-ordered-containers, lens, lib, openapi3, QuickCheck + , servant, singleton-bool, text, unordered-containers }: mkDerivation { - pname = "servant-pandoc"; - version = "0.5.0.0"; - sha256 = "12d709fced47bb3e017b83dcc5dafb1186720e5318c1b5ebeb886d4439540463"; + pname = "servant-openapi3"; + version = "2.0.1.2"; + sha256 = "b760519204933c1882bce947f8a5ebbc189b0865b4e9d5d488a027b217f31bd3"; + revision = "2"; + editedCabalFile = "0cb41wx0lgssda2v26cn36c32j2g0q6gsif7jyy3c5fhaqmn3svv"; + setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ - base bytestring case-insensitive http-media lens pandoc-types - servant-docs string-conversions text unordered-containers + aeson aeson-pretty base base-compat bytestring hspec http-media + insert-ordered-containers lens openapi3 QuickCheck servant + singleton-bool text unordered-containers ]; doHaddock = false; doCheck = false; - description = "Use Pandoc to render servant API documentation"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/biocad/servant-openapi3"; + description = "Generate a Swagger/OpenAPI/OAS 3.0 specification for your servant API."; + license = lib.licenses.bsd3; }) {}; - "servant-rawm" = callPackage - ({ mkDerivation, base, bytestring, filepath, http-client - , http-media, http-types, lens, resourcet, servant-client - , servant-client-core, servant-docs, servant-server, stdenv, wai - , wai-app-static + "servant-pipes" = callPackage + ({ mkDerivation, base, bytestring, lib, monad-control, mtl, pipes + , pipes-safe, servant }: mkDerivation { - pname = "servant-rawm"; - version = "0.3.0.0"; - sha256 = "e9feee415891b8db2c1c032d6a4b934522354bc9cb2491b0ee59f989e94b6a27"; - isLibrary = true; - isExecutable = true; + pname = "servant-pipes"; + version = "0.15.3"; + sha256 = "366088f5d22b716b4bf9136308228051ff903adfe261dc3e502acf5c920ba0e9"; libraryHaskellDepends = [ - base bytestring filepath http-client http-media http-types lens - resourcet servant-client servant-client-core servant-docs - servant-server wai wai-app-static + base bytestring monad-control mtl pipes pipes-safe servant ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/cdepillabout/servant-rawm"; - description = "Embed a raw 'Application' in a Servant API"; - license = stdenv.lib.licenses.bsd3; + homepage = "http://docs.servant.dev/"; + description = "Servant Stream support for pipes"; + license = lib.licenses.bsd3; }) {}; - "servant-ruby" = callPackage - ({ mkDerivation, base, casing, servant-foreign, stdenv, text }: + "servant-rawm" = callPackage + ({ mkDerivation, base, lib, servant }: mkDerivation { - pname = "servant-ruby"; - version = "0.9.0.0"; - sha256 = "63787834369f2fce2216af3a38157af9370a0e4d02965ccd407ec493a62127f4"; - libraryHaskellDepends = [ base casing servant-foreign text ]; + pname = "servant-rawm"; + version = "1.0.0.0"; + sha256 = "73858a113d9281ad69e46bc1d3abd491589b0fe9ca82a9577b87ff7d7c10fb15"; + libraryHaskellDepends = [ base servant ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/joneshf/servant-ruby#readme"; - description = "Generate a Ruby client from a Servant API with Net::HTTP"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/cdepillabout/servant-rawm"; + description = "Embed a raw 'Application' in a Servant API"; + license = lib.licenses.bsd3; }) {}; "servant-server" = callPackage ({ mkDerivation, aeson, base, base-compat, base64-bytestring - , bytestring, Cabal, cabal-doctest, containers, exceptions - , filepath, http-api-data, http-media, http-types, monad-control - , mtl, network, network-uri, resourcet, servant, stdenv - , string-conversions, tagged, text, transformers, transformers-base - , wai, wai-app-static, warp, word8 + , bytestring, containers, exceptions, filepath, http-api-data + , http-media, http-types, lib, monad-control, mtl, network + , network-uri, resourcet, servant, sop-core, string-conversions + , tagged, text, transformers, transformers-base, wai + , wai-app-static, warp, word8 }: mkDerivation { pname = "servant-server"; - version = "0.15"; - sha256 = "98034e618ff844f18dbedeb663e1a88a87ce3bc3792e9a40d7e17ca1e96b93e2"; + version = "0.18.3"; + sha256 = "136acdd982769ab4450325783a2fe88ed747b1ea29789eaf2a44ab826c04cfbe"; isLibrary = true; isExecutable = true; - setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ base base-compat base64-bytestring bytestring containers exceptions filepath http-api-data http-media http-types monad-control mtl - network network-uri resourcet servant string-conversions tagged - text transformers transformers-base wai wai-app-static word8 + network network-uri resourcet servant sop-core string-conversions + tagged text transformers transformers-base wai wai-app-static word8 ]; executableHaskellDepends = [ aeson base base-compat servant text wai warp ]; doHaddock = false; doCheck = false; - homepage = "http://haskell-servant.readthedocs.org/"; + homepage = "http://docs.servant.dev/"; description = "A family of combinators for defining webservices APIs and serving them"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "servant-static-th" = callPackage - ({ mkDerivation, base, blaze-html, bytestring, containers - , directory, filepath, http-media, semigroups, servant - , servant-blaze, servant-server, stdenv, template-haskell, text - }: - mkDerivation { - pname = "servant-static-th"; - version = "0.2.2.0"; - sha256 = "5bec0129407580bde3b5bc49fc75737c916b6eaf0ea421bf72f5bf029342741b"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - base blaze-html bytestring containers directory filepath http-media - semigroups servant servant-blaze servant-server template-haskell - text - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/cdepillabout/servant-static-th"; - description = "Embed a directory of static files in your Servant server"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "servant-streaming" = callPackage - ({ mkDerivation, base, http-types, servant, stdenv }: - mkDerivation { - pname = "servant-streaming"; - version = "0.3.0.0"; - sha256 = "980d486577658697891360479195ed493859e2279f76334101a45c880f7c5a4c"; - revision = "3"; - editedCabalFile = "04mc3k97sk0r90m8ca34gqpb2bz8yljp3j613xx7xz90sffqc1hq"; - libraryHaskellDepends = [ base http-types servant ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/plow-technologies/servant-streaming#readme"; - description = "Servant combinators for the 'streaming' package"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "servant-swagger" = callPackage ({ mkDerivation, aeson, aeson-pretty, base, base-compat, bytestring , Cabal, cabal-doctest, hspec, http-media - , insert-ordered-containers, lens, QuickCheck, servant - , singleton-bool, stdenv, swagger2, text, unordered-containers + , insert-ordered-containers, lens, lib, QuickCheck, servant + , singleton-bool, swagger2, text, unordered-containers }: mkDerivation { pname = "servant-swagger"; - version = "1.1.7"; - sha256 = "e31a1020553c2879047e7d15cd1b57b4ec216606554fdecd62e0f4521e81de36"; + version = "1.1.10"; + sha256 = "0a1d1ce67cad0c403a5ddc2a1b495b027a80d957229256ce77167ca221f5df78"; setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ aeson aeson-pretty base base-compat bytestring hspec http-media @@ -29936,181 +36031,94 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-servant/servant-swagger"; - description = "Generate Swagger specification for your servant API"; - license = stdenv.lib.licenses.bsd3; + description = "Generate a Swagger/OpenAPI/OAS 2.0 specification for your servant API."; + license = lib.licenses.bsd3; }) {}; "servant-swagger-ui" = callPackage - ({ mkDerivation, base, bytestring, file-embed-lzma, servant - , servant-server, servant-swagger-ui-core, stdenv, swagger2, text + ({ mkDerivation, aeson, base, bytestring, file-embed-lzma, lib + , servant, servant-server, servant-swagger-ui-core, text }: mkDerivation { pname = "servant-swagger-ui"; - version = "0.3.2.3.19.3"; - sha256 = "87ddb5982ce6b12698f9eff28b5d6fc2ebd00cb406bd48c8d0ff1951a1335e68"; + version = "0.3.5.3.47.1"; + sha256 = "ba3292c833aac76e00b82fd9c6e809ade8f7d3447f40525efda9d97c909c7501"; revision = "1"; - editedCabalFile = "0k2s6y93ii3d1myacq70ifpjf9q0mglxdr97wmxll6ixzsn7fjpl"; + editedCabalFile = "1dn93dhr8qaxr3raz5myrps1bkhlr6bha8q3kwhyj4q7ahdvj4nj"; libraryHaskellDepends = [ - base bytestring file-embed-lzma servant servant-server - servant-swagger-ui-core swagger2 text + aeson base bytestring file-embed-lzma servant servant-server + servant-swagger-ui-core text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-servant/servant-swagger-ui"; description = "Servant swagger ui"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "servant-swagger-ui-core" = callPackage - ({ mkDerivation, base, blaze-markup, bytestring, http-media - , servant, servant-blaze, servant-server, stdenv, swagger2, text - , transformers, transformers-compat, wai-app-static + ({ mkDerivation, aeson, base, blaze-markup, bytestring, http-media + , lib, servant, servant-blaze, servant-server, text, transformers + , transformers-compat, wai-app-static }: mkDerivation { pname = "servant-swagger-ui-core"; - version = "0.3.2"; - sha256 = "a2cd0e8e68c5de21aea54735f891c4c6e54007c85e93dffd42b89aba419a3ca8"; + version = "0.3.5"; + sha256 = "ed0bf0b2fbdb1751350df6780335de00ae08dd90ac4728a88369f4b132cf7b32"; revision = "1"; - editedCabalFile = "0dd97qvi5w1y90ln58pk0y2vb5f1bhwsix9ym3cnnq8h0snfda4p"; + editedCabalFile = "0fk7bj8fndxf1aw8xhhacjp8rrvx10gj7kh9d2pvjavnz310ymxg"; libraryHaskellDepends = [ - base blaze-markup bytestring http-media servant servant-blaze - servant-server swagger2 text transformers transformers-compat - wai-app-static + aeson base blaze-markup bytestring http-media servant servant-blaze + servant-server text transformers transformers-compat wai-app-static ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-servant/servant-swagger-ui"; description = "Servant swagger ui core components"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "servant-swagger-ui-redoc" = callPackage - ({ mkDerivation, base, bytestring, file-embed-lzma, servant - , servant-server, servant-swagger-ui-core, stdenv, swagger2, text - }: - mkDerivation { - pname = "servant-swagger-ui-redoc"; - version = "0.3.2.1.22.2"; - sha256 = "e09919e7518f8f5b00868eac0c4f80212b5a4950d2c10112696f52446e369934"; - revision = "1"; - editedCabalFile = "030zf1z5h96d40ifwagxblz1dij2ypbcqyy0wpqvjqbianyqgcim"; - libraryHaskellDepends = [ - base bytestring file-embed-lzma servant servant-server - servant-swagger-ui-core swagger2 text - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/haskell-servant/servant-swagger-ui"; - description = "Servant swagger ui: ReDoc theme"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "servant-tracing" = callPackage - ({ mkDerivation, aeson, async, base, bytestring, bytestring-lexing - , containers, hashable, http-api-data, http-client, lifted-base - , monad-control, mtl, random, servant, servant-server, stdenv, text - , time, transformers, unordered-containers, wai, warp - }: - mkDerivation { - pname = "servant-tracing"; - version = "0.1.0.2"; - sha256 = "3edf2e58c60b6624a81c57bbc606889d779ba0cc57fc785240cb353f9caaea62"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - aeson async base bytestring bytestring-lexing containers hashable - http-api-data http-client lifted-base monad-control mtl random - servant servant-server text time unordered-containers wai - ]; - executableHaskellDepends = [ - async base bytestring containers http-client lifted-base - monad-control mtl servant servant-server text transformers wai warp - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/ChrisCoffey/haskell-opentracing-light#readme"; - license = stdenv.lib.licenses.mit; - }) {}; - "servant-websockets" = callPackage - ({ mkDerivation, aeson, async, base, bytestring, conduit - , exceptions, resourcet, servant-server, stdenv, text, wai - , wai-websockets, warp, websockets - }: - mkDerivation { - pname = "servant-websockets"; - version = "1.1.0"; - sha256 = "63384c89db83bd03e00f2f6796c391fc133ffb3c2bc72976778d476ed82f0a51"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - aeson async base bytestring conduit exceptions resourcet - servant-server text wai wai-websockets warp websockets - ]; - executableHaskellDepends = [ - aeson base conduit servant-server text wai warp websockets - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/moesenle/servant-websockets#readme"; - description = "Small library providing WebSocket endpoints for servant"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "servant-yaml" = callPackage - ({ mkDerivation, base, bytestring, http-media, servant, stdenv - , yaml - }: - mkDerivation { - pname = "servant-yaml"; - version = "0.1.0.1"; - sha256 = "01547419509cd0424885146734c08acede329a660022f534ac9b19cc685bf601"; - libraryHaskellDepends = [ - base bytestring http-media servant yaml - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/haskell-servant/servant-yaml#readme"; - description = "Servant support for yaml"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "serverless-haskell" = callPackage - ({ mkDerivation, aeson, aeson-casing, aeson-extra, amazonka-core + ({ mkDerivation, aeson, aeson-casing, amazonka-core , amazonka-kinesis, amazonka-s3, base, bytestring, case-insensitive - , http-types, iproute, lens, network, network-simple, stdenv, text - , time, unix, unordered-containers + , containers, http-client, http-types, iproute, lens, lib + , safe-exceptions, text, time, unix, unordered-containers }: mkDerivation { pname = "serverless-haskell"; - version = "0.8.5"; - sha256 = "0fe307cadc5f0297e11e7dcac15b9371ad98f04683db7f6f5e1faf03cb17d84a"; + version = "0.12.6"; + sha256 = "d02267392c01548352278d9a34283d99468d2e2aaa3faa748ef7de1d1dfd60be"; libraryHaskellDepends = [ - aeson aeson-casing aeson-extra amazonka-core amazonka-kinesis - amazonka-s3 base bytestring case-insensitive http-types iproute - lens network network-simple text time unix unordered-containers + aeson aeson-casing amazonka-core amazonka-kinesis amazonka-s3 base + bytestring case-insensitive containers http-client http-types + iproute lens safe-exceptions text time unix unordered-containers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/seek-oss/serverless-haskell#readme"; description = "Deploying Haskell code onto AWS Lambda using Serverless"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "serversession" = callPackage ({ mkDerivation, aeson, base, base64-bytestring, bytestring - , data-default, hashable, nonce, path-pieces, stdenv, text, time - , transformers, unordered-containers + , data-default, hashable, lib, nonce, path-pieces, persistent-test + , text, time, transformers, unordered-containers }: mkDerivation { pname = "serversession"; - version = "1.0.1"; - sha256 = "3ffbefd87017e8d46fbbe380f59e24672aa9c06b999da5f9ae0b052094d94822"; + version = "1.0.2"; + sha256 = "4e82feb7c3d8857e26b7354b0385a51fe60cbc42daa2e6456fadd867f083d60b"; libraryHaskellDepends = [ aeson base base64-bytestring bytestring data-default hashable nonce - path-pieces text time transformers unordered-containers + path-pieces persistent-test text time transformers + unordered-containers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/yesodweb/serversession"; description = "Secure, modular server-side sessions"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "serversession-frontend-wai" = callPackage - ({ mkDerivation, base, bytestring, cookie, data-default - , path-pieces, serversession, stdenv, text, time, transformers + ({ mkDerivation, base, bytestring, cookie, data-default, lib + , path-pieces, serversession, text, time, transformers , unordered-containers, vault, wai, wai-session }: mkDerivation { @@ -30125,32 +36133,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/yesodweb/serversession"; description = "wai-session bindings for serversession"; - license = stdenv.lib.licenses.mit; - }) {}; - "servius" = callPackage - ({ mkDerivation, base, blaze-builder, blaze-html, bytestring - , cmark-gfm, http-types, shakespeare, stdenv, text, wai - , wai-app-static - }: - mkDerivation { - pname = "servius"; - version = "1.2.3.0"; - sha256 = "72c4b63e85df0cb51935bec85e31d44c6ee5cafd0015bd5e6ff44286e9e18b27"; - isLibrary = false; - isExecutable = true; - executableHaskellDepends = [ - base blaze-builder blaze-html bytestring cmark-gfm http-types - shakespeare text wai wai-app-static - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/snoyberg/servius#readme"; - description = "Warp web server with template rendering"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "ses-html" = callPackage ({ mkDerivation, base, base64-bytestring, blaze-html, byteable - , bytestring, cryptohash, HsOpenSSL, http-streams, stdenv, tagsoup + , bytestring, cryptohash, HsOpenSSL, http-streams, lib, tagsoup , time }: mkDerivation { @@ -30164,10 +36151,33 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Send HTML formatted emails using Amazon's SES REST API with blaze"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "set-cover" = callPackage + ({ mkDerivation, array, base, containers, enummapset, lib + , non-empty, prelude-compat, psqueues, semigroups, transformers + , utility-ht + }: + mkDerivation { + pname = "set-cover"; + version = "0.1.1"; + sha256 = "fc51e7e66a2166624e1099290c982ccaa3556e0337a49e89f85f014a65655212"; + revision = "1"; + editedCabalFile = "0x5hn43xcfsygjc048mvzk6g8dx51pr5csvvqr6pns8jmz5awkf8"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + array base containers enummapset non-empty prelude-compat psqueues + semigroups transformers utility-ht + ]; + doHaddock = false; + doCheck = false; + homepage = "http://hub.darcs.net/thielema/set-cover/"; + description = "Solve exact set cover problems like Sudoku, 8 Queens, Soma Cube, Tetris Cube"; + license = lib.licenses.bsd3; }) {}; "setenv" = callPackage - ({ mkDerivation, base, stdenv, unix }: + ({ mkDerivation, base, lib, unix }: mkDerivation { pname = "setenv"; version = "0.1.1.3"; @@ -30178,91 +36188,144 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A cross-platform library for setting environment variables"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "setlocale" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "setlocale"; - version = "1.0.0.8"; - sha256 = "6dd148e47714707c311d20af606284ab392392a84ffb71da4004010e67d5b969"; + version = "1.0.0.10"; + sha256 = "3972ff10c22318f5451215dc886c1535fea5ab7dfefe5ce461b1603865423ba7"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://bitbucket.org/IchUndNichtDu/haskell-setlocale"; + homepage = "https://gitlab.com/Kritzefitz/haskell-setlocale/"; description = "Haskell bindings to setlocale"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "sexp-grammar" = callPackage + ({ mkDerivation, alex, array, base, bytestring, containers + , data-fix, deepseq, happy, invertible-grammar, lib, prettyprinter + , recursion-schemes, scientific, semigroups, text, utf8-string + }: + mkDerivation { + pname = "sexp-grammar"; + version = "2.3.1"; + sha256 = "a41afe31c02eb18d0d578050df76bd68c98418016d228288923cc8cf514a7217"; + libraryHaskellDepends = [ + array base bytestring containers data-fix deepseq + invertible-grammar prettyprinter recursion-schemes scientific + semigroups text utf8-string + ]; + libraryToolDepends = [ alex happy ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/esmolanka/sexp-grammar"; + description = "Invertible grammar combinators for S-expressions"; + license = lib.licenses.bsd3; }) {}; "shake" = callPackage ({ mkDerivation, base, binary, bytestring, deepseq, directory - , extra, filepath, hashable, heaps, js-flot, js-jquery, primitive - , process, random, stdenv, time, transformers, unix - , unordered-containers, utf8-string + , extra, filepath, filepattern, hashable, heaps, js-dgtable + , js-flot, js-jquery, lib, primitive, process, random, time + , transformers, unix, unordered-containers, utf8-string }: mkDerivation { pname = "shake"; - version = "0.17.4"; - sha256 = "beaddfbd55559ecd2b00eaaa660c2c79925bbe22619e2f5c4dc8b8ef678575aa"; + version = "0.19.5"; + sha256 = "695dcbaac4e858d06d0f95ccc3b0a6d29a73f6f2f7d62507f69f9563b77baa80"; isLibrary = true; isExecutable = true; enableSeparateDataOutput = true; libraryHaskellDepends = [ - base binary bytestring deepseq directory extra filepath hashable - heaps js-flot js-jquery primitive process random time transformers - unix unordered-containers utf8-string + base binary bytestring deepseq directory extra filepath filepattern + hashable heaps js-dgtable js-flot js-jquery primitive process + random time transformers unix unordered-containers utf8-string ]; executableHaskellDepends = [ - base binary bytestring deepseq directory extra filepath hashable - heaps js-flot js-jquery primitive process random time transformers - unix unordered-containers utf8-string + base binary bytestring deepseq directory extra filepath filepattern + hashable heaps js-dgtable js-flot js-jquery primitive process + random time transformers unix unordered-containers utf8-string ]; doHaddock = false; doCheck = false; homepage = "https://shakebuild.com"; description = "Build system library, like Make, but more accurate dependencies"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "shake-language-c" = callPackage - ({ mkDerivation, base, data-default-class, fclabels, process, shake - , split, stdenv, unordered-containers + ({ mkDerivation, base, data-default-class, fclabels, lib, process + , shake, split, unordered-containers + }: + mkDerivation { + pname = "shake-language-c"; + version = "0.12.0"; + sha256 = "661e350179e55c930c3c36f53853db2bc2697d88c5265049085cea09f5aa1ab0"; + libraryHaskellDepends = [ + base data-default-class fclabels process shake split + unordered-containers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/samplecount/shake-language-c"; + description = "Utilities for cross-compiling with Shake"; + license = lib.licenses.asl20; + }) {}; + "shake-plus" = callPackage + ({ mkDerivation, base, extra, lib, path, rio, shake }: + mkDerivation { + pname = "shake-plus"; + version = "0.3.3.1"; + sha256 = "e596b0b070bb9569ed9d1fc13eb390d4b989f15ad14738bc85ba550aafb2f127"; + libraryHaskellDepends = [ base extra path rio shake ]; + doHaddock = false; + doCheck = false; + description = "Re-export of Shake using well-typed paths and ReaderT"; + license = lib.licenses.mit; + }) {}; + "shake-plus-extended" = callPackage + ({ mkDerivation, aeson, base, binary-instances, comonad, extra + , http-conduit, ixset-typed, ixset-typed-binary-instance + , ixset-typed-hashable-instance, lib, path, path-binary-instance + , rio, shake, shake-plus, within }: mkDerivation { - pname = "shake-language-c"; - version = "0.12.0"; - sha256 = "661e350179e55c930c3c36f53853db2bc2697d88c5265049085cea09f5aa1ab0"; + pname = "shake-plus-extended"; + version = "0.4.1.0"; + sha256 = "2b87815bfc2ee1220faea719737c76431795c2ed7a5c0a6d273cae411165f1a1"; libraryHaskellDepends = [ - base data-default-class fclabels process shake split - unordered-containers + aeson base binary-instances comonad extra http-conduit ixset-typed + ixset-typed-binary-instance ixset-typed-hashable-instance path + path-binary-instance rio shake shake-plus within ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/samplecount/shake-language-c"; - description = "Utilities for cross-compiling with Shake"; - license = stdenv.lib.licenses.asl20; + description = "Experimental extensions to shake-plus"; + license = lib.licenses.mit; }) {}; "shakespeare" = callPackage ({ mkDerivation, aeson, base, blaze-html, blaze-markup, bytestring - , containers, directory, exceptions, ghc-prim, parsec, process - , scientific, stdenv, template-haskell, text, time, transformers + , containers, directory, exceptions, ghc-prim, lib, parsec, process + , scientific, template-haskell, text, th-lift, time, transformers , unordered-containers, vector }: mkDerivation { pname = "shakespeare"; - version = "2.0.20"; - sha256 = "f50ebff8e585851a1e3af36885d6a6d1218b19dcde1d7459f02272d6925d9e03"; + version = "2.0.25"; + sha256 = "4427b923ee466525352ab5209eae2faabc929c1b14c0d8463ba815419e1f5bba"; libraryHaskellDepends = [ aeson base blaze-html blaze-markup bytestring containers directory exceptions ghc-prim parsec process scientific template-haskell text - time transformers unordered-containers vector + th-lift time transformers unordered-containers vector ]; doHaddock = false; doCheck = false; homepage = "http://www.yesodweb.com/book/shakespearean-templates"; description = "A toolkit for making compile-time interpolated templates"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "shared-memory" = callPackage - ({ mkDerivation, base, stdenv, unix }: + ({ mkDerivation, base, lib, unix }: mkDerivation { pname = "shared-memory"; version = "0.2.0.0"; @@ -30272,18 +36335,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/nh2/shared-memory"; description = "POSIX shared memory"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "shell-conduit" = callPackage ({ mkDerivation, async, base, bytestring, conduit, conduit-extra - , directory, filepath, monads-tf, process, resourcet, semigroups - , split, stdenv, template-haskell, text, transformers, unix + , directory, filepath, lib, monads-tf, process, resourcet + , semigroups, split, template-haskell, text, transformers, unix , unliftio }: mkDerivation { pname = "shell-conduit"; - version = "4.7.0"; - sha256 = "6f31c5b6fb46219c4da575b4405f1a5af51eed1f22073d315df80c8a40ddbe30"; + version = "5.0.0"; + sha256 = "3c90074c3ece6784ddf00300f99b7f25bb8479be302eb2c8cca013b3f2a3f10b"; libraryHaskellDepends = [ async base bytestring conduit conduit-extra directory filepath monads-tf process resourcet semigroups split template-haskell text @@ -30293,11 +36356,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/psibi/shell-conduit"; description = "Write shell scripts with Conduit"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "shell-escape" = callPackage - ({ mkDerivation, base, binary, bytestring, containers, stdenv - , vector + ({ mkDerivation, base, binary, bytestring, containers, lib, vector }: mkDerivation { pname = "shell-escape"; @@ -30310,12 +36372,42 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/solidsnack/shell-escape"; description = "Shell escaping library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "shell-utility" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "shell-utility"; + version = "0.1"; + sha256 = "b1867af59978e44e2a0bea52896c30ace4aed227cf30e9eb67bbcfbd15d825d8"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "http://hub.darcs.net/thielema/shell-utility/"; + description = "Utility functions for writing command-line programs"; + license = lib.licenses.bsd3; + }) {}; + "shellmet" = callPackage + ({ mkDerivation, base, lib, markdown-unlit, process, text }: + mkDerivation { + pname = "shellmet"; + version = "0.0.4.0"; + sha256 = "1b51a7beec91c25e71cfb562ec1249f22a52a30f8e20672a506c743b41513bdb"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base process text ]; + executableHaskellDepends = [ base text ]; + executableToolDepends = [ markdown-unlit ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/kowainik/shellmet"; + description = "Out of the shell solution for scripting in Haskell"; + license = lib.licenses.mpl20; }) {}; "shelltestrunner" = callPackage ({ mkDerivation, base, cmdargs, Diff, directory, filemanip - , filepath, HUnit, parsec, pretty-show, process, regex-tdfa, safe - , stdenv, test-framework, test-framework-hunit, utf8-string + , filepath, HUnit, lib, parsec, pretty-show, process, regex-tdfa + , safe, test-framework, test-framework-hunit, utf8-string }: mkDerivation { pname = "shelltestrunner"; @@ -30336,34 +36428,32 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; }) {}; "shelly" = callPackage ({ mkDerivation, async, base, bytestring, containers, directory - , enclosed-exceptions, exceptions, lifted-async, lifted-base - , monad-control, mtl, process, stdenv, system-fileio - , system-filepath, text, time, transformers, transformers-base - , unix, unix-compat + , enclosed-exceptions, exceptions, filepath, lib, lifted-async + , lifted-base, monad-control, mtl, process, text, time + , transformers, transformers-base, unix, unix-compat }: mkDerivation { pname = "shelly"; - version = "1.8.1"; - sha256 = "de8814879c7a5e7f1f7f0d9c56c1dfee30d6d63ba1140946e5ed158dd75e6e08"; + version = "1.9.0"; + sha256 = "5eb5fd4fc105e218cef6cfa10971d299ad660324e6a6006b8cccc31edf39aace"; revision = "1"; - editedCabalFile = "0crf0m077wky76f5nav2p9q4fa5q4yhv5l4bq9hd073dzdaywhz0"; + editedCabalFile = "0827p6wq8j92svrvmx02gdk961xx42g1ng4j6g7nflrfks9hw0zf"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ async base bytestring containers directory enclosed-exceptions - exceptions lifted-async lifted-base monad-control mtl process - system-fileio system-filepath text time transformers - transformers-base unix unix-compat + exceptions filepath lifted-async lifted-base monad-control mtl + process text time transformers transformers-base unix unix-compat ]; doHaddock = false; doCheck = false; homepage = "https://github.com/yesodweb/Shelly.hs"; description = "shell-like (systems) programming in Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "shikensu" = callPackage ({ mkDerivation, aeson, base, bytestring, directory, filepath, flow - , Glob, stdenv, text, unordered-containers + , Glob, lib, text, unordered-containers }: mkDerivation { pname = "shikensu"; @@ -30377,23 +36467,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/icidasset/shikensu#readme"; description = "Run a sequence of functions on in-memory representations of files"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "shortcut-links" = callPackage - ({ mkDerivation, base, stdenv, text }: + ({ mkDerivation, base, lib, text }: mkDerivation { pname = "shortcut-links"; - version = "0.4.2.1"; - sha256 = "0d36ecfabc8e2d3a4c0015b521b6cb8efa8469bbd518a509326f07a3aa24deff"; + version = "0.5.1.1"; + sha256 = "202dcb95ddd3f4077711adbe4e8405e0d90838a702b7030d506e10eaf78bc714"; libraryHaskellDepends = [ base text ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/aelve/shortcut-links"; + homepage = "http://github.com/kowainik/shortcut-links"; description = "Link shortcuts for use in text markup"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mpl20; }) {}; "should-not-typecheck" = callPackage - ({ mkDerivation, base, deepseq, HUnit, stdenv }: + ({ mkDerivation, base, deepseq, HUnit, lib }: mkDerivation { pname = "should-not-typecheck"; version = "2.1.0"; @@ -30403,40 +36493,25 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/CRogers/should-not-typecheck"; description = "A HUnit/hspec assertion library to verify that an expression does not typecheck"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "show-combinators" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "show-combinators"; - version = "0.1.1.0"; - sha256 = "d53abf2b289a3075555f1ede76f5beba0fadce352cd94efbad610bc1eb76020a"; + version = "0.2.0.0"; + sha256 = "c902dbaf0e9cf7056d786d44fbdea2781bc65524089639242c2624dae841ba1d"; + revision = "2"; + editedCabalFile = "0n3xlpm41wpw1ybmacg9s7150nx00qrdlw2rq4fzz7iw7333cyjx"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/Lysxia/show-combinators#readme"; description = "Combinators to write Show instances"; - license = stdenv.lib.licenses.mit; - }) {}; - "show-prettyprint" = callPackage - ({ mkDerivation, ansi-wl-pprint, base, prettyprinter, stdenv - , trifecta - }: - mkDerivation { - pname = "show-prettyprint"; - version = "0.2.2"; - sha256 = "f07d860b9bb4176a4e46038c5100ecf07d443daa1b15455ca4c2bd4d10e9af55"; - libraryHaskellDepends = [ - ansi-wl-pprint base prettyprinter trifecta - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/quchen/show-prettyprint#readme"; - description = "Robust prettyprinter for output of auto-generated Show instances"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; "siggy-chardust" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "siggy-chardust"; version = "1.0.0"; @@ -30448,10 +36523,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/blockscope/flare-timing/tree/master/siggy-chardust#readme"; description = "Rounding rationals to significant digits and decimal places"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "signal" = callPackage - ({ mkDerivation, base, stdenv, unix }: + ({ mkDerivation, base, lib, unix }: mkDerivation { pname = "signal"; version = "0.1.0.4"; @@ -30464,43 +36539,89 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/pmlodawski/signal"; description = "Multiplatform signal support for Haskell"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "silently" = callPackage - ({ mkDerivation, base, deepseq, directory, stdenv }: + ({ mkDerivation, base, deepseq, directory, lib }: mkDerivation { pname = "silently"; - version = "1.2.5"; - sha256 = "cef625635053a46032ca53b43d311921875a437910b6568ded17027fdca83839"; + version = "1.2.5.1"; + sha256 = "7fc9baf6f47ffc082e7e05c9dade1451bdee06a0c4e2d882e8e0b692f50bfad1"; libraryHaskellDepends = [ base deepseq directory ]; doHaddock = false; doCheck = false; homepage = "https://github.com/hspec/silently"; description = "Prevent or capture writing to stdout and other handles"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "simple-affine-space" = callPackage + ({ mkDerivation, base, deepseq, lib }: + mkDerivation { + pname = "simple-affine-space"; + version = "0.1.1"; + sha256 = "89a0d1afa3a0f287cbfc41716a9673481c3a6005c1d896bfb10b5f1d27b25e9c"; + libraryHaskellDepends = [ base deepseq ]; + doHaddock = false; + doCheck = false; + homepage = "http://www.haskell.org/haskellwiki/Yampa"; + description = "A simple library for affine and vector spaces"; + license = lib.licenses.bsd3; + }) {}; + "simple-cabal" = callPackage + ({ mkDerivation, base, bytestring, Cabal, directory, filepath, lib + }: + mkDerivation { + pname = "simple-cabal"; + version = "0.1.3"; + sha256 = "fd649c2f1fb7f9d9fd9090363352bf202877ccc041b73203ebe241f13510b00c"; + libraryHaskellDepends = [ + base bytestring Cabal directory filepath + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/juhp/simple-cabal"; + description = "Cabal file wrapper library"; + license = lib.licenses.bsd3; }) {}; "simple-cmd" = callPackage - ({ mkDerivation, base, directory, filepath, process, stdenv }: + ({ mkDerivation, base, directory, extra, filepath, lib, process + , unix + }: mkDerivation { pname = "simple-cmd"; - version = "0.1.2"; - sha256 = "e6a15592fbbcc5667b7e45563b55d08228ea483241a3b80aef9f7df802f54d82"; - libraryHaskellDepends = [ base directory filepath process ]; + version = "0.2.3"; + sha256 = "5bf6a972c0cd360438d97ae429e04bba0cd19bfc435399df7612ddffd1b619e5"; + libraryHaskellDepends = [ + base directory extra filepath process unix + ]; doHaddock = false; doCheck = false; description = "Simple String-based process commands"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "simple-cmd-args" = callPackage + ({ mkDerivation, base, lib, optparse-applicative }: + mkDerivation { + pname = "simple-cmd-args"; + version = "0.1.7"; + sha256 = "ec763d07f09fd15db8ac7960657130d1ea72aa13496e95a0174f0bb0a3bfc051"; + libraryHaskellDepends = [ base optparse-applicative ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/juhp/simple-cmd-args"; + description = "Simple command args parsing and execution"; + license = lib.licenses.bsd3; }) {}; "simple-log" = callPackage ({ mkDerivation, async, base, base-unicode-symbols, containers , data-default, deepseq, directory, exceptions, filepath, hformat - , microlens, microlens-platform, mmorph, mtl, SafeSemaphore, stdenv + , lib, microlens, microlens-platform, mmorph, mtl, SafeSemaphore , text, time, transformers }: mkDerivation { pname = "simple-log"; - version = "0.9.10"; - sha256 = "b398e8649e06a05e88b84532f0ced426a7f18bafe1eeab6b178574773db6ffa5"; + version = "0.9.12"; + sha256 = "5c1074229a41ee2c2b1d6eb7036a82927e6585e9ef81d8c6e721fac497566880"; libraryHaskellDepends = [ async base base-unicode-symbols containers data-default deepseq directory exceptions filepath hformat microlens microlens-platform @@ -30510,10 +36631,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/mvoidex/simple-log"; description = "Simple log for Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "simple-reflect" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "simple-reflect"; version = "0.3.3"; @@ -30523,37 +36644,68 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://twanvl.nl/blog/haskell/simple-reflection-of-expressions"; description = "Simple reflection of expressions containing variables"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "simple-sendfile" = callPackage - ({ mkDerivation, base, bytestring, network, stdenv, unix }: + ({ mkDerivation, base, bytestring, lib, network, unix }: mkDerivation { pname = "simple-sendfile"; - version = "0.2.27"; - sha256 = "f68572592099a2db3f7212ac7d133447ae5bbb2605285d3de1a29a52d9c79caf"; - revision = "1"; - editedCabalFile = "040adccwis3yy8af783vjz3a2yb3fcmm49cpzdgikm2293pwyj0p"; + version = "0.2.30"; + sha256 = "b6864d2b3c62ff8ea23fa24e9e26f751bfe5253c8efb1f1e4fee2ba91d065284"; libraryHaskellDepends = [ base bytestring network unix ]; doHaddock = false; doCheck = false; description = "Cross platform library for the sendfile system call"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "simple-templates" = callPackage + ({ mkDerivation, aeson, attoparsec, base, lib, scientific, text + , unordered-containers, vector + }: + mkDerivation { + pname = "simple-templates"; + version = "1.0.0"; + sha256 = "2ed3a76419cec93227ff16c93d0f59dd3785eb66e20f6dc96ede952a9b03a36e"; + libraryHaskellDepends = [ + aeson attoparsec base scientific text unordered-containers vector + ]; + doHaddock = false; + doCheck = false; + homepage = "http://simple.cx"; + description = "A basic template language for the Simple web framework"; + license = lib.licenses.lgpl3Only; }) {}; "simple-vec3" = callPackage - ({ mkDerivation, base, QuickCheck, stdenv, vector }: + ({ mkDerivation, base, lib, QuickCheck, vector }: mkDerivation { pname = "simple-vec3"; - version = "0.4.0.9"; - sha256 = "ff024c5b224037414168c2c19c2c05179bd28251a31bfc5aee9796b35db4a4e7"; + version = "0.6.0.1"; + sha256 = "7584e59663fbd9e9b61be3b9c64c61959a84d4350f927e7f5f89db0710512a54"; libraryHaskellDepends = [ base QuickCheck vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/dzhus/simple-vec3#readme"; description = "Three-dimensional vectors of doubles with basic operations"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "simplistic-generics" = callPackage + ({ mkDerivation, base, containers, deepseq, kind-apply, lib, mtl + , template-haskell + }: + mkDerivation { + pname = "simplistic-generics"; + version = "2.0.0"; + sha256 = "d8ac757b89704a9f41d6f928e5918b362dfcd8e53102fd8e220fc11e00f11a9d"; + libraryHaskellDepends = [ + base containers deepseq kind-apply mtl template-haskell + ]; + doHaddock = false; + doCheck = false; + description = "Generic programming without too many type classes"; + license = lib.licenses.bsd3; }) {}; "since" = callPackage - ({ mkDerivation, base, stdenv, time }: + ({ mkDerivation, base, lib, time }: mkDerivation { pname = "since"; version = "0.0.0"; @@ -30563,45 +36715,47 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/athanclark/since#readme"; description = "Get the number of seconds since the last invocation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "singleton-bool" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, dec, lib }: mkDerivation { pname = "singleton-bool"; - version = "0.1.4"; - sha256 = "0195c6e2be1e149e5b687ec3be84fd5089b377345fddd333a9d681eacdfafb2a"; - revision = "1"; - editedCabalFile = "0ccd49z9xwa8gr8sclmmn0zc4xq39yyjws4zr6lrw3xjql130nsx"; - libraryHaskellDepends = [ base ]; + version = "0.1.5"; + sha256 = "405dd57dea92857c04f539c3394894c40c8103ea0c4f3f0fdbfbd8acccde899f"; + revision = "3"; + editedCabalFile = "11rhzpy4xiry39bbxzwrqff75f0f4g7z0vkr3v9l8rv3w40jlf7x"; + libraryHaskellDepends = [ base dec ]; doHaddock = false; doCheck = false; homepage = "https://github.com/phadej/singleton-bool#readme"; description = "Type level booleans"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "singleton-nats" = callPackage - ({ mkDerivation, base, singletons, stdenv }: + ({ mkDerivation, base, lib, singletons }: mkDerivation { pname = "singleton-nats"; - version = "0.4.2"; - sha256 = "8f8169b013a5e4725be9682bf413019cdaf6e020455839612c145ba6849e9cf1"; + version = "0.4.5"; + sha256 = "615af27a19a78d0c2179a6048e2bd549743d68a9b400fd19c309b28ca4c3b362"; libraryHaskellDepends = [ base singletons ]; doHaddock = false; doCheck = false; homepage = "https://github.com/AndrasKovacs/singleton-nats"; description = "Unary natural numbers relying on the singletons infrastructure"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "singletons" = callPackage ({ mkDerivation, base, Cabal, containers, directory, filepath - , ghc-boot-th, mtl, pretty, stdenv, syb, template-haskell, text + , ghc-boot-th, lib, mtl, pretty, syb, template-haskell, text , th-desugar, transformers }: mkDerivation { pname = "singletons"; - version = "2.5.1"; - sha256 = "20b00a3a732812ec1141014d2f8d379e392165ce7881fa7de9add8db0e22f147"; + version = "2.7"; + sha256 = "e12bd6e695eaf444eb6b1fd07372818aaff8703aa71265f677f3af3cb412e22b"; + revision = "1"; + editedCabalFile = "18vd0jnr3skf2fmj13g06gjjzgmw5rnsjqwivsmqs3pkfv9qi3sm"; setupHaskellDepends = [ base Cabal directory filepath ]; libraryHaskellDepends = [ base containers ghc-boot-th mtl pretty syb template-haskell text @@ -30611,10 +36765,29 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.github.com/goldfirere/singletons"; description = "A framework for generating singleton types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "singletons-presburger" = callPackage + ({ mkDerivation, base, ghc-typelits-presburger, lib, mtl + , reflection, singletons + }: + mkDerivation { + pname = "singletons-presburger"; + version = "0.6.0.0"; + sha256 = "c3a819f6e513b5963788c8b87293612550b47291319952a13f010906cea1e1f9"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base ghc-typelits-presburger mtl reflection singletons + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/konn/ghc-typelits-presburger#readme"; + description = "Presburger Arithmetic Solver for GHC Type-level natural numbers with Singletons package"; + license = lib.licenses.bsd3; }) {}; "siphash" = callPackage - ({ mkDerivation, base, bytestring, cpu, stdenv }: + ({ mkDerivation, base, bytestring, cpu, lib }: mkDerivation { pname = "siphash"; version = "1.0.3"; @@ -30627,46 +36800,45 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/vincenthz/hs-siphash"; description = "siphash: a fast short input PRF"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "size-based" = callPackage - ({ mkDerivation, base, dictionary-sharing, stdenv, template-haskell - , testing-type-modifiers - }: + "sitemap-gen" = callPackage + ({ mkDerivation, base, lib, text, time, xmlgen }: mkDerivation { - pname = "size-based"; - version = "0.1.2.0"; - sha256 = "779ff6c45476d20ffd2ad7327b44cefaaf0436ed89f43b2967761c0b58a4151a"; - libraryHaskellDepends = [ - base dictionary-sharing template-haskell testing-type-modifiers - ]; + pname = "sitemap-gen"; + version = "0.1.0.0"; + sha256 = "1f7cb16fc3ea547e3320fecb35900804de032cce6f7d8c94ad26c6d0a33f0837"; + libraryHaskellDepends = [ base text time xmlgen ]; doHaddock = false; doCheck = false; - description = "Sized functors, for size-based enumerations"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/prikhi/sitemap-gen#readme"; + description = "Generate XML Sitemaps & Sitemap Indexes"; + license = lib.licenses.bsd3; }) {}; - "sized-grid" = callPackage - ({ mkDerivation, adjunctions, aeson, base, comonad, constraints - , distributive, generics-sop, lens, mtl, random, stdenv, vector - , vector-space + "sized" = callPackage + ({ mkDerivation, base, constraints, containers, deepseq + , equational-reasoning, ghc-typelits-knownnat + , ghc-typelits-presburger, hashable, lens, lib, mono-traversable + , subcategories, these, type-natural, vector }: mkDerivation { - pname = "sized-grid"; - version = "0.1.1.6"; - sha256 = "4907af7a4ac56a838d599f319b2096a63c4f30eaf84cac0a5a22d937605c0b1b"; + pname = "sized"; + version = "1.0.0.0"; + sha256 = "677a327a351aed4656e669aa531a08f0f3f18b75104217ffe42262303da0d838"; + revision = "3"; + editedCabalFile = "13v3dkfdnzg2y7pfkn2dnvczd9y40izlm30vcssn2a5b1v7vy3bz"; libraryHaskellDepends = [ - adjunctions aeson base comonad constraints distributive - generics-sop lens mtl random vector vector-space + base constraints containers deepseq equational-reasoning + ghc-typelits-knownnat ghc-typelits-presburger hashable lens + mono-traversable subcategories these type-natural vector ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/edwardwas/sized-grid"; - description = "Multidimensional grids with sized specified at compile time"; - license = stdenv.lib.licenses.mit; + description = "Sized sequence data-types"; + license = lib.licenses.bsd3; }) {}; "skein" = callPackage - ({ mkDerivation, base, bytestring, cereal, crypto-api, stdenv - , tagged + ({ mkDerivation, base, bytestring, cereal, crypto-api, lib, tagged }: mkDerivation { pname = "skein"; @@ -30679,155 +36851,294 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/meteficha/skein"; description = "Skein, a family of cryptographic hash functions. Includes Skein-MAC as well."; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "skews" = callPackage - ({ mkDerivation, base, bytestring, deque, stdenv, websockets }: + ({ mkDerivation, base, bytestring, deque, lib, websockets }: mkDerivation { pname = "skews"; - version = "0.1.0.1"; - sha256 = "b544480c3e7d676f008faccd1d31639114f773aac8d2b8828be48122a120b60d"; - revision = "1"; - editedCabalFile = "0zvqfr9dfcap3ljpkq5hq95npmhrmndlh0gs4pa2zm8bwrh1nl66"; + version = "0.1.0.3"; + sha256 = "56c313e7d819c49665b8b6fce20d7cee408a0974a1cf2fd59dbb1eb4a68f94e7"; libraryHaskellDepends = [ base bytestring deque websockets ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/iij-ii/skews#readme"; + homepage = "https://github.com/iij-ii/direct-hs/tree/master/skews"; description = "A very quick-and-dirty WebSocket server"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "skip-var" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "skip-var"; version = "0.1.1.0"; sha256 = "bfbce57abd47c9c892f734b5c7d2bccad90fa5f8f8a6d4747cca15d2a493d41e"; + revision = "1"; + editedCabalFile = "0vl2y19l7xhlq08f91ggycj4imfdxvkj2fsaz8ifc0waxk3q7ja8"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/leohaskell/skip-var#readme"; + homepage = "https://github.com/dtaskoff/skip-var#readme"; description = "Skip variables"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "skylighting" = callPackage - ({ mkDerivation, aeson, ansi-terminal, attoparsec, base - , base64-bytestring, binary, blaze-html, bytestring - , case-insensitive, colour, containers, directory, filepath, hxt - , mtl, regex-pcre-builtin, safe, skylighting-core, stdenv, text - , utf8-string + ({ mkDerivation, base, binary, blaze-html, bytestring, containers + , lib, pretty-show, skylighting-core, text }: mkDerivation { pname = "skylighting"; - version = "0.7.5"; - sha256 = "7de100e42e7dac3687372f85225a6d905d534f75990c5a25c6e640acf0ad1320"; + version = "0.10.5.2"; + sha256 = "f07fc652938c280b2ea90beb08ca48cc50a8b80ca7d0e680979d00787ce45e94"; + configureFlags = [ "-fexecutable" ]; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - aeson ansi-terminal attoparsec base base64-bytestring binary - blaze-html bytestring case-insensitive colour containers directory - filepath hxt mtl regex-pcre-builtin safe skylighting-core text - utf8-string + base binary containers skylighting-core + ]; + executableHaskellDepends = [ + base blaze-html bytestring containers pretty-show text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/jgm/skylighting"; description = "syntax highlighting library"; - license = stdenv.lib.licenses.gpl2; + license = lib.licenses.gpl2Only; }) {}; "skylighting-core" = callPackage ({ mkDerivation, aeson, ansi-terminal, attoparsec, base , base64-bytestring, binary, blaze-html, bytestring - , case-insensitive, colour, containers, directory, filepath, hxt - , mtl, regex-pcre-builtin, safe, stdenv, text, transformers - , utf8-string + , case-insensitive, colour, containers, directory, filepath, lib + , mtl, safe, text, transformers, utf8-string, xml-conduit }: mkDerivation { pname = "skylighting-core"; - version = "0.7.5"; - sha256 = "f706a2eb5d37d1323525d9c4944da2ad8d29c1ccf7d0ae7b433695d981413889"; + version = "0.10.5.2"; + sha256 = "6dbca23e1f356493f274b48ef9a6e435e4d589d649594ec470d63cfb4064532f"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ aeson ansi-terminal attoparsec base base64-bytestring binary blaze-html bytestring case-insensitive colour containers directory - filepath hxt mtl regex-pcre-builtin safe text transformers - utf8-string + filepath mtl safe text transformers utf8-string xml-conduit ]; doHaddock = false; doCheck = false; homepage = "https://github.com/jgm/skylighting"; description = "syntax highlighting library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "slack-web" = callPackage - ({ mkDerivation, aeson, base, containers, errors, http-api-data - , http-client, http-client-tls, megaparsec, mtl, servant - , servant-client, servant-client-core, stdenv, text, time - , transformers + "slack-api" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers, errors + , hashable, io-streams, lens, lens-aeson, lib, monad-loops, mtl + , network, network-uri, text, time, time-locale-compat, tls + , transformers, websockets, wreq, wuss }: mkDerivation { - pname = "slack-web"; - version = "0.2.0.9"; - sha256 = "421d2cd3a1626b637224e94c800312673b1a0f0c980d7346c0061e71bb8287d3"; + pname = "slack-api"; + version = "0.12"; + sha256 = "9b5cde3cbeb67a020614e0b9e10c316dd6dc378b03144944b99846ee75c2bc36"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson base bytestring containers errors hashable io-streams lens + lens-aeson monad-loops mtl network network-uri text time + time-locale-compat tls transformers websockets wreq wuss + ]; + executableHaskellDepends = [ base lens mtl text ]; + doHaddock = false; + doCheck = false; + description = "Bindings to the Slack RTM API"; + license = lib.licenses.mit; + }) {}; + "slack-progressbar" = callPackage + ({ mkDerivation, aeson, base, bytestring, interpolate, lens + , lens-aeson, lib, mtl, network-uri, text, transformers, wreq + }: + mkDerivation { + pname = "slack-progressbar"; + version = "0.1.0.1"; + sha256 = "2df5b2f01e2193b52b79b3bda22e4fedf4992a3ee9ac5b8c660fcc5d41433e8a"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson base bytestring interpolate lens lens-aeson mtl network-uri + text transformers wreq + ]; + executableHaskellDepends = [ + aeson base bytestring interpolate lens lens-aeson mtl network-uri + text transformers wreq + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/codedownio/slack-progressbar#readme"; + license = lib.licenses.mit; + }) {}; + "slick" = callPackage + ({ mkDerivation, aeson, base, bytestring, directory, extra, lib + , mustache, pandoc, shake, text, unordered-containers + }: + mkDerivation { + pname = "slick"; + version = "1.1.1.0"; + sha256 = "ed9080c2d9b15abf11fac534c96a3e3076ecbe495b97ae96860599210b7af8a7"; + libraryHaskellDepends = [ + aeson base bytestring directory extra mustache pandoc shake text + unordered-containers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ChrisPenner/slick#readme"; + description = "A quick & easy static site builder built with shake and pandoc"; + license = lib.licenses.bsd3; + }) {}; + "slist" = callPackage + ({ mkDerivation, base, containers, lib }: + mkDerivation { + pname = "slist"; + version = "0.2.0.0"; + sha256 = "266d59c2e46059c7c7f613fcf29da24eef08b3f4cf4bd85422b7e73120e73aaa"; + libraryHaskellDepends = [ base containers ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/kowainik/slist"; + description = "Sized list"; + license = lib.licenses.mpl20; + }) {}; + "slynx" = callPackage + ({ mkDerivation, attoparsec, base, bytestring, containers + , elynx-markov, elynx-seq, elynx-tools, elynx-tree, hmatrix, lib + , monad-logger, mwc-random, optparse-applicative, statistics, text + , transformers, vector + }: + mkDerivation { + pname = "slynx"; + version = "0.5.1.1"; + sha256 = "ac220602e520d03f70b085cddf00931603c4aa6c8c036fe340144894a84346e2"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - aeson base containers errors http-api-data http-client - http-client-tls megaparsec mtl servant servant-client - servant-client-core text time transformers + attoparsec base bytestring containers elynx-markov elynx-seq + elynx-tools elynx-tree hmatrix monad-logger mwc-random + optparse-applicative statistics text transformers vector ]; + executableHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/jpvillaisaza/slack-web"; - description = "Bindings for the Slack web API"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/dschrempf/elynx#readme"; + description = "Handle molecular sequences"; + license = lib.licenses.gpl3Plus; }) {}; "smallcheck" = callPackage - ({ mkDerivation, base, ghc-prim, logict, mtl, pretty, stdenv }: + ({ mkDerivation, base, lib, logict, mtl, pretty }: mkDerivation { pname = "smallcheck"; - version = "1.1.5"; - sha256 = "9020e67895a57bde02d7df2c0af06a4c769eff56d48b6a830f6d803df891aea4"; - libraryHaskellDepends = [ base ghc-prim logict mtl pretty ]; + version = "1.2.1"; + sha256 = "e41f9d11b50e0526dd28c9bc6cf6dddf98cebd782911a00c3e5cbe4ce53fc869"; + libraryHaskellDepends = [ base logict mtl pretty ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/feuerbach/smallcheck"; + homepage = "https://github.com/Bodigrim/smallcheck"; description = "A property-based testing library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "smash" = callPackage + ({ mkDerivation, base, bifunctors, binary, deepseq, hashable, lib + , mtl, template-haskell + }: + mkDerivation { + pname = "smash"; + version = "0.1.2"; + sha256 = "1c2865484ae79629a64a9f982db6776fb5b002dad881980a08c35f845852129d"; + revision = "1"; + editedCabalFile = "0i5ba4zn11b075fy32pawfhjy81731pjiy5f88f6z8zzbbgwfyny"; + libraryHaskellDepends = [ + base bifunctors binary deepseq hashable mtl template-haskell + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/emilypi/smash"; + description = "Smash products, wedge products, and pointed products"; + license = lib.licenses.bsd3; + }) {}; + "smash-aeson" = callPackage + ({ mkDerivation, aeson, base, lib, smash, unordered-containers }: + mkDerivation { + pname = "smash-aeson"; + version = "0.1.0.0"; + sha256 = "1ae71446f23691e2af33bdaa56a6b72d6e9dbfeb3572df3ee1aae3eb87feaa6e"; + revision = "1"; + editedCabalFile = "1y0k6gz9qlr98f543607zkx6a97fnzh3zrbi2b59rlljp0rjvdw8"; + libraryHaskellDepends = [ aeson base smash unordered-containers ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/emilypi/smash"; + description = "Aeson support for the smash library"; + license = lib.licenses.bsd3; + }) {}; + "smash-lens" = callPackage + ({ mkDerivation, base, lens, lib, smash }: + mkDerivation { + pname = "smash-lens"; + version = "0.1.0.1"; + sha256 = "c6606f95d1249c05adfa69c7c4e90f514f9b5d9b99eb76e01e172a35c219fbc8"; + libraryHaskellDepends = [ base lens smash ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/emilypi/smash"; + description = "Optics for the `smash` library"; + license = lib.licenses.bsd3; + }) {}; + "smash-microlens" = callPackage + ({ mkDerivation, base, lib, microlens, smash }: + mkDerivation { + pname = "smash-microlens"; + version = "0.1.0.0"; + sha256 = "80c64c66dad61ab3cc9431ef931ab88c3cb8fc6f766a04c839076bf7f2ae9b98"; + revision = "1"; + editedCabalFile = "020r04bxhml84lgl1bvf2s6gjahswdxpzcrla43rqhx0paz0n0cs"; + libraryHaskellDepends = [ base microlens smash ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/emilypi/smash"; + description = "Optics for the `smash` library"; + license = lib.licenses.bsd3; }) {}; "smoothie" = callPackage - ({ mkDerivation, aeson, base, linear, stdenv, text, vector }: + ({ mkDerivation, aeson, base, lib, linear, text, vector }: mkDerivation { pname = "smoothie"; - version = "0.4.2.9"; - sha256 = "d3cafbc34a5d03363ddd41e59bd681168cd2d0aa8be4678db9ae1904ad202a4f"; + version = "0.4.2.11"; + sha256 = "0cb503dafe86f28fc98fed3aee88032d578727c700dc4f826eae7ef79ee092ca"; enableSeparateDataOutput = true; libraryHaskellDepends = [ aeson base linear text vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/phaazon/smoothie"; description = "Smooth curves via several interpolation modes"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "smtp-mail" = callPackage ({ mkDerivation, array, base, base16-bytestring, base64-bytestring - , bytestring, cryptohash, filepath, mime-mail, network, stdenv - , text + , bytestring, connection, cryptonite, filepath, lib, memory + , mime-mail, network, network-bsd, text }: mkDerivation { pname = "smtp-mail"; - version = "0.1.4.6"; - sha256 = "86dacbef87a2519222a1165b49401a437887a249f5bfd63a99702198dad214bc"; + version = "0.3.0.0"; + sha256 = "a4ab56a4d4e58d5fa441b67dfdbcd182e3c13b41c9d4af82038d0d122ba90161"; libraryHaskellDepends = [ array base base16-bytestring base64-bytestring bytestring - cryptohash filepath mime-mail network text + connection cryptonite filepath memory mime-mail network network-bsd + text ]; doHaddock = false; doCheck = false; homepage = "http://github.com/jhickner/smtp-mail"; description = "Simple email sending via SMTP"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "snap-blaze" = callPackage - ({ mkDerivation, base, blaze-html, snap-core, stdenv }: + ({ mkDerivation, base, blaze-html, lib, snap-core }: mkDerivation { pname = "snap-blaze"; version = "0.2.1.5"; @@ -30837,22 +37148,22 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/jaspervdj/snap-blaze"; description = "blaze-html integration for Snap"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "snap-core" = callPackage ({ mkDerivation, attoparsec, base, bytestring, bytestring-builder , case-insensitive, containers, directory, filepath, hashable - , HUnit, io-streams, lifted-base, monad-control, mtl, network - , network-uri, old-locale, random, readable, regex-posix, stdenv - , text, time, transformers, transformers-base, unix-compat + , HUnit, io-streams, lib, lifted-base, monad-control, mtl, network + , network-uri, old-locale, random, readable, regex-posix, text + , time, transformers, transformers-base, unix-compat , unordered-containers, vector }: mkDerivation { pname = "snap-core"; - version = "1.0.3.2"; - sha256 = "4c4398476fe882122ce8adc03f69509588d071fc011f50162cd69706093dd88c"; - revision = "3"; - editedCabalFile = "0wlhn33r7c9g7j23y006ddq9d87lkmianvvfrbl8jd8mvjvj2gfa"; + version = "1.0.4.2"; + sha256 = "1abbc13b00a165620ac905ec8c92f7e960f8c7f7949c128e9d0b9cc94987ad7f"; + revision = "1"; + editedCabalFile = "065v61clskzikywv0gy9n4fjaszi2fnjklal83kqbzhzzgkf83ng"; libraryHaskellDepends = [ attoparsec base bytestring bytestring-builder case-insensitive containers directory filepath hashable HUnit io-streams lifted-base @@ -30864,21 +37175,19 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://snapframework.com/"; description = "Snap: A Haskell Web Framework (core interfaces and types)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "snap-server" = callPackage ({ mkDerivation, attoparsec, base, blaze-builder, bytestring , bytestring-builder, case-insensitive, clock, containers, filepath - , HsOpenSSL, io-streams, io-streams-haproxy, lifted-base, mtl - , network, old-locale, openssl-streams, snap-core, stdenv, text - , time, unix, unix-compat, vector + , HsOpenSSL, io-streams, io-streams-haproxy, lib, lifted-base, mtl + , network, old-locale, openssl-streams, snap-core, text, time + , transformers, unix, unix-compat, vector }: mkDerivation { pname = "snap-server"; - version = "1.1.0.0"; - sha256 = "249ea390a4e54899b310c0dd13b91af007a2b685bd0d9769c3e208dd914d7c6f"; - revision = "3"; - editedCabalFile = "0a9d3nqb5rvgm25nak68lp6yj9m6cwhbgdbg5l7ib5i2czcg7yjh"; + version = "1.1.2.0"; + sha256 = "92306f4148fd9eca06a608b9a8d46a95e928aee231ab320650f5d25854da9e70"; configureFlags = [ "-fopenssl" ]; isLibrary = true; isExecutable = true; @@ -30886,16 +37195,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; attoparsec base blaze-builder bytestring bytestring-builder case-insensitive clock containers filepath HsOpenSSL io-streams io-streams-haproxy lifted-base mtl network old-locale - openssl-streams snap-core text time unix unix-compat vector + openssl-streams snap-core text time transformers unix unix-compat + vector ]; doHaddock = false; doCheck = false; homepage = "http://snapframework.com/"; description = "A web server for the Snap Framework"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "snowflake" = callPackage - ({ mkDerivation, base, stdenv, time }: + ({ mkDerivation, base, lib, time }: mkDerivation { pname = "snowflake"; version = "0.1.1.1"; @@ -30906,12 +37216,12 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A loose port of Twitter Snowflake to Haskell. Generates arbitrary precision, unique, time-sortable identifiers."; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; }) {}; "soap" = callPackage ({ mkDerivation, base, bytestring, conduit, configurator - , data-default, exceptions, http-client, http-types, iconv, mtl - , resourcet, stdenv, text, unordered-containers, xml-conduit + , data-default, exceptions, http-client, http-types, iconv, lib + , mtl, resourcet, text, unordered-containers, xml-conduit , xml-conduit-writer, xml-types }: mkDerivation { @@ -30927,17 +37237,39 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://bitbucket.org/dpwiz/haskell-soap"; description = "SOAP client tools"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "soap-openssl" = callPackage + ({ mkDerivation, base, configurator, data-default, HsOpenSSL + , http-client, http-client-openssl, lib, soap, text + }: + mkDerivation { + pname = "soap-openssl"; + version = "0.1.0.2"; + sha256 = "2008547f4fd22063479ce1cd1c483db926f5f08a2ff6fb0c60fb2f0f7d42830f"; + revision = "2"; + editedCabalFile = "0zhl8x57y35ymhpznrsn2yrgc3bigjn5mabwl4nvprpznb2x44vn"; + libraryHaskellDepends = [ + base configurator data-default HsOpenSSL http-client + http-client-openssl soap text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://bitbucket.org/dpwiz/haskell-soap"; + description = "TLS-enabled SOAP transport (using openssl bindings)"; + license = lib.licenses.mit; }) {}; "soap-tls" = callPackage ({ mkDerivation, base, configurator, connection, data-default - , http-client, http-client-tls, soap, stdenv, text, tls, x509 + , http-client, http-client-tls, lib, soap, text, tls, x509 , x509-store, x509-validation }: mkDerivation { pname = "soap-tls"; version = "0.1.1.4"; sha256 = "ce8b33cd4bb2cc60093df4de231967edd789fd9da44a261a539a221116853a14"; + revision = "1"; + editedCabalFile = "11djy824gaw3cbsvphq263hxjrn1b3v5p1kdivsvlyn7q9bgvms9"; libraryHaskellDepends = [ base configurator connection data-default http-client http-client-tls soap text tls x509 x509-store x509-validation @@ -30946,48 +37278,66 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://bitbucket.org/dpwiz/haskell-soap"; description = "TLS-enabled SOAP transport (using tls package)"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "socket-activation" = callPackage - ({ mkDerivation, base, network, stdenv, transformers, unix }: + "socket" = callPackage + ({ mkDerivation, base, bytestring, lib }: mkDerivation { - pname = "socket-activation"; - version = "0.1.0.2"; - sha256 = "b99e7b4f296cd462aac84e5bb61fb02953e2080d1351e9e10a63d35dc34eb43b"; - libraryHaskellDepends = [ base network transformers unix ]; + pname = "socket"; + version = "0.8.3.0"; + sha256 = "796573319d7381691e84c58aec601e94c084013d3cca61d9ae91fe5b0dcfa03d"; + libraryHaskellDepends = [ base bytestring ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/ddfisher/haskell-socket-activation"; - description = "systemd socket activation library"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/lpeterse/haskell-socket"; + description = "An extensible socket library"; + license = lib.licenses.mit; }) {}; "socks" = callPackage - ({ mkDerivation, base, bytestring, cereal, network, stdenv }: + ({ mkDerivation, base, basement, bytestring, cereal, lib, network + }: mkDerivation { pname = "socks"; - version = "0.5.6"; - sha256 = "fa63cd838025e18864c59755750c0cfc4ea76e140a542f07a5c682488ec78438"; - libraryHaskellDepends = [ base bytestring cereal network ]; + version = "0.6.1"; + sha256 = "734447558bb061ce768f53a0df1f2401902c6bee396cc96ce627edd986ef6a73"; + libraryHaskellDepends = [ + base basement bytestring cereal network + ]; doHaddock = false; doCheck = false; homepage = "http://github.com/vincenthz/hs-socks"; description = "Socks proxy (ver 5)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "some" = callPackage + ({ mkDerivation, base, deepseq, lib }: + mkDerivation { + pname = "some"; + version = "1.0.2"; + sha256 = "ccf8a4b07d5236a6f966649ebef39e764f1f6bb52217647e2e96d0cdfe2bbb8a"; + libraryHaskellDepends = [ base deepseq ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/phadej/some"; + description = "Existential type: Some"; + license = lib.licenses.bsd3; }) {}; "sop-core" = callPackage - ({ mkDerivation, base, deepseq, stdenv }: + ({ mkDerivation, base, deepseq, lib }: mkDerivation { pname = "sop-core"; - version = "0.4.0.0"; - sha256 = "a381b0efb8e2dedb6627da6adb0a2b72421f87d43d9b53d68d5b2e866015911d"; + version = "0.5.0.1"; + sha256 = "dac367f1608c9bd6c5dd1697e2a30e1b760617023b96e1df7d44c6c017999db0"; + revision = "1"; + editedCabalFile = "1d4sagrlhmvai3f4hvb9rn8aqsjbvi00z0mzv1gds9nblshk83xd"; libraryHaskellDepends = [ base deepseq ]; doHaddock = false; doCheck = false; description = "True Sums of Products"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "sort" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "sort"; version = "1.0.0.0"; @@ -30997,10 +37347,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/cdornan/sort"; description = "A Haskell sorting toolkit"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "sorted-list" = callPackage - ({ mkDerivation, base, deepseq, stdenv }: + ({ mkDerivation, base, deepseq, lib }: mkDerivation { pname = "sorted-list"; version = "0.2.1.0"; @@ -31010,18 +37360,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/Daniel-Diaz/sorted-list/blob/master/README.md"; description = "Type-enforced sorted lists and related functions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "sourcemap" = callPackage - ({ mkDerivation, aeson, attoparsec, base, bytestring, process - , stdenv, text, unordered-containers, utf8-string + ({ mkDerivation, aeson, attoparsec, base, bytestring, lib, process + , text, unordered-containers, utf8-string }: mkDerivation { pname = "sourcemap"; - version = "0.1.6"; - sha256 = "b9a04cccb4fe7eea8b37a2eaf2bc776eae5640038ab76fb948c5a3ea09a9ce7a"; - revision = "1"; - editedCabalFile = "1f7q44ar6qfip8fsllg43jyn7r15ifn2r0vz32cbmx0sb0d38dax"; + version = "0.1.6.1"; + sha256 = "0ab9153088666f43bcaa82f023825c0acaaea847180b85892ecfebd2d8ede84f"; libraryHaskellDepends = [ aeson attoparsec base bytestring process text unordered-containers utf8-string @@ -31029,11 +37377,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Implementation of source maps as proposed by Google and Mozilla"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "sox" = callPackage ({ mkDerivation, base, containers, explicit-exception - , extensible-exceptions, process, sample-frame, semigroups, stdenv + , extensible-exceptions, lib, process, sample-frame, semigroups , transformers, unix, utility-ht }: mkDerivation { @@ -31052,7 +37400,7 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; }) {}; "soxlib" = callPackage ({ mkDerivation, base, bytestring, explicit-exception - , extensible-exceptions, sample-frame, sox, stdenv, storablevector + , extensible-exceptions, lib, sample-frame, sox, storablevector , transformers, utility-ht }: mkDerivation { @@ -31065,17 +37413,41 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; base bytestring explicit-exception extensible-exceptions sample-frame storablevector transformers utility-ht ]; - libraryPkgconfigDepends = [ sox ]; + libraryPkgconfigDepends = [ sox ]; + doHaddock = false; + doCheck = false; + homepage = "http://www.haskell.org/haskellwiki/Sox"; + description = "Write, read, convert audio signals using libsox"; + license = lib.licenses.bsd3; + }) {inherit (pkgs) sox;}; + "spacecookie" = callPackage + ({ mkDerivation, aeson, async, attoparsec, base, bytestring + , containers, directory, fast-logger, filepath-bytestring + , hxt-unicode, lib, mtl, socket, systemd, text, transformers, unix + }: + mkDerivation { + pname = "spacecookie"; + version = "1.0.0.0"; + sha256 = "c05254bc6a92c01135ac5e6d6e5026f4c3d24ee40486d2da91d565e654b1c16c"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + async attoparsec base bytestring containers directory + filepath-bytestring hxt-unicode mtl socket text transformers unix + ]; + executableHaskellDepends = [ + aeson attoparsec base bytestring containers directory fast-logger + filepath-bytestring mtl socket systemd text transformers unix + ]; doHaddock = false; doCheck = false; - homepage = "http://www.haskell.org/haskellwiki/Sox"; - description = "Write, read, convert audio signals using libsox"; - license = stdenv.lib.licenses.bsd3; - }) {inherit (pkgs) sox;}; + homepage = "https://github.com/sternenseemann/spacecookie"; + description = "Gopher server library and daemon"; + license = lib.licenses.gpl3Only; + }) {}; "sparse-linear-algebra" = callPackage - ({ mkDerivation, base, containers, exceptions, hspec, mtl - , primitive, QuickCheck, stdenv, transformers, vector - , vector-algorithms + ({ mkDerivation, base, containers, exceptions, hspec, lib, mtl + , primitive, QuickCheck, transformers, vector, vector-algorithms }: mkDerivation { pname = "sparse-linear-algebra"; @@ -31090,11 +37462,46 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/ocramz/sparse-linear-algebra"; description = "Numerical computing in native Haskell"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; + }) {}; + "sparse-tensor" = callPackage + ({ mkDerivation, ad, base, bytestring, Cabal, cereal, containers + , deepseq, ghc-typelits-knownnat, ghc-typelits-natnormalise + , hmatrix, lib, parallel, tf-random, zlib + }: + mkDerivation { + pname = "sparse-tensor"; + version = "0.2.1.5"; + sha256 = "a473cb7075547a379c30d3a575f0b6b3b8a84adb1680bdbd0b6a42010a878914"; + setupHaskellDepends = [ base Cabal ]; + libraryHaskellDepends = [ + ad base bytestring cereal containers deepseq ghc-typelits-knownnat + ghc-typelits-natnormalise hmatrix parallel tf-random zlib + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/TobiReinhart/sparse-tensor#readme"; + description = "typesafe tensor algebra library"; + license = lib.licenses.mit; + }) {}; + "spatial-math" = callPackage + ({ mkDerivation, base, binary, cereal, ghc-prim, lens, lib, linear + , TypeCompose + }: + mkDerivation { + pname = "spatial-math"; + version = "0.5.0.1"; + sha256 = "c91cf29157c2a3425f40afdd6fb763f2fc4299eb4c32725ac64d2ba568c2a410"; + libraryHaskellDepends = [ + base binary cereal ghc-prim lens linear TypeCompose + ]; + doHaddock = false; + doCheck = false; + description = "3d math including quaternions/euler angles/dcms and utility functions"; + license = lib.licenses.bsd3; }) {}; "special-values" = callPackage - ({ mkDerivation, base, bytestring, ieee754, scientific, stdenv - , text + ({ mkDerivation, base, bytestring, ieee754, lib, scientific, text }: mkDerivation { pname = "special-values"; @@ -31107,29 +37514,32 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/minad/special-values#readme"; description = "Typeclass providing special values"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "speculate" = callPackage - ({ mkDerivation, base, cmdargs, containers, leancheck, stdenv }: + ({ mkDerivation, base, cmdargs, containers, express, leancheck, lib + }: mkDerivation { pname = "speculate"; - version = "0.3.5"; - sha256 = "706cb2ac18b2d646bc20cc80135bad10e30bd0096ab479308cd110077035ea44"; - libraryHaskellDepends = [ base cmdargs containers leancheck ]; + version = "0.4.10"; + sha256 = "c84af3d46e26cb20ceafa56bf259a141f542dd2d29ecf511ad32960948bcde17"; + libraryHaskellDepends = [ + base cmdargs containers express leancheck + ]; doHaddock = false; doCheck = false; homepage = "https://github.com/rudymatela/speculate#readme"; description = "discovery of properties about Haskell functions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "speedy-slice" = callPackage - ({ mkDerivation, base, kan-extensions, lens, mcmc-types - , mwc-probability, pipes, primitive, stdenv, transformers + ({ mkDerivation, base, kan-extensions, lens, lib, mcmc-types + , mwc-probability, pipes, primitive, transformers }: mkDerivation { pname = "speedy-slice"; - version = "0.3.0"; - sha256 = "efbf8a10b681b940078f70fb9aca43fec8ba436c82f3faf719bbe495ba152899"; + version = "0.3.2"; + sha256 = "7fe099f076aa60f76bcb5333cab46494330883ff754d16a6c68b3f9c3304beae"; libraryHaskellDepends = [ base kan-extensions lens mcmc-types mwc-probability pipes primitive transformers @@ -31138,28 +37548,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/jtobin/speedy-slice"; description = "Speedy slice sampling"; - license = stdenv.lib.licenses.mit; - }) {}; - "sphinx" = callPackage - ({ mkDerivation, base, binary, bytestring, data-binary-ieee754 - , network, stdenv, text, text-icu, xml - }: - mkDerivation { - pname = "sphinx"; - version = "0.6.0.2"; - sha256 = "76a977c6ce6e71c220bd5fed7acd0be500c2a1b5c8d081a29564a8e37ba7a6df"; - libraryHaskellDepends = [ - base binary bytestring data-binary-ieee754 network text text-icu - xml - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/gregwebs/haskell-sphinx-client"; - description = "Haskell bindings to the Sphinx full-text searching daemon"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; "splice" = callPackage - ({ mkDerivation, base, network, stdenv }: + ({ mkDerivation, base, lib, network }: mkDerivation { pname = "splice"; version = "0.6.1.1"; @@ -31169,38 +37561,65 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://corsis.github.com/splice/"; description = "Cross-platform Socket to Socket Data Splicing"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "splint" = callPackage + ({ mkDerivation, base, containers, ghc, hlint, lib, stm }: + mkDerivation { + pname = "splint"; + version = "1.0.1.4"; + sha256 = "b56a5c8bea2b154a3692efd915ba03ca2267fd5953313dcee4e4804afc20f5e8"; + libraryHaskellDepends = [ base containers ghc hlint stm ]; + doHaddock = false; + doCheck = false; + description = "HLint as a GHC source plugin"; + license = lib.licenses.isc; }) {}; "split" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "split"; - version = "0.2.3.3"; - sha256 = "1dcd674f7c5f276f33300f5fd59e49d1ac6fc92ae949fd06a0f6d3e9d9ac1413"; + version = "0.2.3.4"; + sha256 = "271fe5104c9f40034aa9a1aad6269bcecc9454bc5a57c247e69e17de996c1f2a"; revision = "1"; - editedCabalFile = "0vz2ylx81nfq2981msig080j7n41xf2lrxzf3hj1x3g3cllb3izi"; + editedCabalFile = "06pmlvyrz4rr7rsrghpyrdypprphm9522rvnz4l3i8333n4pb304"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; description = "Combinator library for splitting lists"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "splitmix" = callPackage - ({ mkDerivation, base, deepseq, random, stdenv, time }: + ({ mkDerivation, base, deepseq, lib }: mkDerivation { pname = "splitmix"; - version = "0.0.1"; - sha256 = "2a6c8003a941640ceab9dc358aadf69e08800e2cb10a267422e4436fe1e8772f"; - revision = "1"; - editedCabalFile = "0c38sajdpqcmicdh4lfy6vpg8wnzpiyamvbximdsqs605frs3mqs"; - libraryHaskellDepends = [ base deepseq random time ]; + version = "0.1.0.3"; + sha256 = "46009f4b000c9e6613377767b8718bf38476469f2a8e2162d98cc246882d5a35"; + libraryHaskellDepends = [ base deepseq ]; doHaddock = false; doCheck = false; description = "Fast Splittable PRNG"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "splitmix-distributions" = callPackage + ({ mkDerivation, base, containers, erf, exceptions, lib, mtl + , splitmix, transformers + }: + mkDerivation { + pname = "splitmix-distributions"; + version = "0.9.0.0"; + sha256 = "ff66d2bcf9b9b6b344cf76b4752c65c74b8b0842de65fb6f72b3d1f5e648db78"; + libraryHaskellDepends = [ + base containers erf exceptions mtl splitmix transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ocramz/splitmix-distributions#readme"; + description = "Random samplers for some common distributions, based on splitmix"; + license = lib.licenses.bsd3; }) {}; "spoon" = callPackage - ({ mkDerivation, base, deepseq, stdenv }: + ({ mkDerivation, base, deepseq, lib }: mkDerivation { pname = "spoon"; version = "0.3.1"; @@ -31211,10 +37630,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Catch errors thrown from pure computations"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "spreadsheet" = callPackage - ({ mkDerivation, base, explicit-exception, stdenv, transformers + ({ mkDerivation, base, explicit-exception, lib, transformers , utility-ht }: mkDerivation { @@ -31230,30 +37649,58 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Spreadsheet"; description = "Read and write spreadsheets from and to CSV files in a lazy way"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "sql-words" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "sql-words"; - version = "0.1.6.2"; - sha256 = "3f6a5a0cf8f8aaf452caa2389db54e09494be3fd9dce111fbf06df2b7eddeb38"; + version = "0.1.6.4"; + sha256 = "c0731ee741afd6d5bd321c1c87022ace4aa8e506b87f19f4d8fc9b82e1cca2e5"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "http://khibino.github.io/haskell-relational-record/"; description = "SQL keywords data constructors into OverloadedString"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "sqlcli" = callPackage + ({ mkDerivation, base, lib, logging, text, transformers, unixODBC + }: + mkDerivation { + pname = "sqlcli"; + version = "0.2.2.0"; + sha256 = "edf11892d91fba10567a8bb67c03d1297cd73c7a5b1cbc4bc1a7331228e24ccf"; + libraryHaskellDepends = [ base logging text transformers ]; + librarySystemDepends = [ unixODBC ]; + doHaddock = false; + doCheck = false; + homepage = "http://hub.darcs.net/mihaigiurgeanu/sqlcli"; + description = "Bindings for SQL/CLI (ODBC) C API"; + license = lib.licenses.bsd3; + }) {inherit (pkgs) unixODBC;}; + "sqlcli-odbc" = callPackage + ({ mkDerivation, base, lib, logging, sqlcli }: + mkDerivation { + pname = "sqlcli-odbc"; + version = "0.2.0.1"; + sha256 = "656db4ca182d443c29f43e9d2cb351dd98add31d2942b92c3a6c570e946ad0e5"; + libraryHaskellDepends = [ base logging sqlcli ]; + doHaddock = false; + doCheck = false; + homepage = "https://hub.darcs.net/mihaigiurgeanu/sqlcli-odbc"; + description = "ODBC specific definitions to be used by SQL CLI clients"; + license = lib.licenses.bsd3; }) {}; "sqlite-simple" = callPackage ({ mkDerivation, attoparsec, base, blaze-builder, blaze-textual - , bytestring, containers, direct-sqlite, Only, semigroups, stdenv + , bytestring, containers, direct-sqlite, lib, Only, semigroups , template-haskell, text, time, transformers }: mkDerivation { pname = "sqlite-simple"; - version = "0.4.16.0"; - sha256 = "60d2a188d1967ebc0d3ec9175776c45a6e1e6e7a4d44567548cb7fe6961d30de"; + version = "0.4.18.0"; + sha256 = "f73f1866f672db1941a2cb60b18532c185ef45b0950a538a6598e57791d32c02"; libraryHaskellDepends = [ attoparsec base blaze-builder blaze-textual bytestring containers direct-sqlite Only semigroups template-haskell text time @@ -31263,70 +37710,105 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/nurpax/sqlite-simple"; description = "Mid-Level SQLite client library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "sqlite-simple-errors" = callPackage - ({ mkDerivation, base, parsec, sqlite-simple, stdenv, text }: + "squeal-postgresql" = callPackage + ({ mkDerivation, aeson, base, binary, binary-parser, bytestring + , bytestring-strict-builder, deepseq, exceptions, free-categories + , generics-sop, lib, mmorph, monad-control, mtl, network-ip + , postgresql-binary, postgresql-libpq, profunctors, records-sop + , resource-pool, scientific, text, time, transformers + , transformers-base, unliftio, unliftio-pool, uuid-types, vector + }: mkDerivation { - pname = "sqlite-simple-errors"; - version = "0.6.1.0"; - sha256 = "5101f84a6d74d658398cc4ef557ad3c6158d53e9c948301cc47ed0cc3eaa716f"; - libraryHaskellDepends = [ base parsec sqlite-simple text ]; + pname = "squeal-postgresql"; + version = "0.7.0.1"; + sha256 = "1994d58badfc2d849d169ef4012a6141fac8cdad8d5103a018b92e611d8c1965"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson base binary binary-parser bytestring + bytestring-strict-builder deepseq exceptions free-categories + generics-sop mmorph monad-control mtl network-ip postgresql-binary + postgresql-libpq profunctors records-sop resource-pool scientific + text time transformers transformers-base unliftio unliftio-pool + uuid-types vector + ]; + executableHaskellDepends = [ + base bytestring generics-sop mtl text transformers vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/morphismtech/squeal"; + description = "Squeal PostgreSQL Library"; + license = lib.licenses.bsd3; + }) {}; + "squeather" = callPackage + ({ mkDerivation, base, bytestring, lib, text }: + mkDerivation { + pname = "squeather"; + version = "0.8.0.0"; + sha256 = "26a763d288216a2d15e6adbb910ae37a72f68f844b747636b93223fc4ec251de"; + libraryHaskellDepends = [ base bytestring text ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/caneroj1/sqlite-simple-errors"; - description = "Wrapper around errors from sqlite-simple"; - license = stdenv.lib.licenses.bsd3; + description = "Use databases with the version 3 series of the SQLite C library"; + license = lib.licenses.bsd3; }) {}; "srcloc" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "srcloc"; - version = "0.5.1.2"; - sha256 = "069edbce6bb72e0771cece3aa5a6b67b9e0b0bd0148e9404842fa43035fec06e"; + version = "0.6"; + sha256 = "6b693603ea6582f7d79d46ffdb1836cb08722fc00a139a80673a97e8de4e97ed"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mainland/srcloc"; description = "Data types for managing source code locations"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "stache" = callPackage ({ mkDerivation, aeson, base, bytestring, containers, deepseq - , directory, filepath, megaparsec, mtl, stdenv, template-haskell - , text, unordered-containers, vector + , directory, filepath, gitrev, lib, megaparsec, mtl + , optparse-applicative, template-haskell, text + , unordered-containers, vector, yaml }: mkDerivation { pname = "stache"; - version = "2.0.1"; - sha256 = "739ff0d0a882f46bbcd391a2b1ee271906e9c049c463fb8846c1d32d3f829e2b"; - revision = "2"; - editedCabalFile = "17da7jih43nl3zqgpmlk3n2kpwjmb2np4w8ldpq2vyi9ab8p6vjm"; + version = "2.3.0"; + sha256 = "992513756ba5ee2af2571feb9e420be1c54b0361155b71253df527cc5ecad5bd"; + isLibrary = true; + isExecutable = true; enableSeparateDataOutput = true; libraryHaskellDepends = [ aeson base bytestring containers deepseq directory filepath megaparsec mtl template-haskell text unordered-containers vector ]; + executableHaskellDepends = [ + aeson base filepath gitrev optparse-applicative text + unordered-containers yaml + ]; doHaddock = false; doCheck = false; homepage = "https://github.com/stackbuilders/stache"; description = "Mustache templates for Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "stack" = callPackage - ({ mkDerivation, aeson, annotated-wl-pprint, ansi-terminal, async - , attoparsec, base, base64-bytestring, bindings-uname, bytestring - , Cabal, conduit, conduit-extra, containers, cryptonite - , cryptonite-conduit, deepseq, directory, echo, exceptions, extra - , file-embed, filelock, filepath, fsnotify, generic-deriving - , hackage-security, hashable, hpack, hpc, http-client - , http-client-tls, http-conduit, http-types, memory, microlens - , mintty, monad-logger, mono-traversable, mtl, mustache - , neat-interpolation, network-uri, open-browser - , optparse-applicative, path, path-io, persistent - , persistent-sqlite, persistent-template, pretty, primitive - , process, project-template, regex-applicative-text, resourcet - , retry, rio, semigroups, split, stdenv, stm, store, store-core + ({ mkDerivation, aeson, annotated-wl-pprint, ansi-terminal, array + , async, attoparsec, base, base64-bytestring, bytestring, Cabal + , casa-client, casa-types, colour, conduit, conduit-extra + , containers, cryptonite, cryptonite-conduit, deepseq, directory + , echo, exceptions, extra, file-embed, filelock, filepath, fsnotify + , generic-deriving, hackage-security, hashable, hi-file-parser + , hpack, hpc, http-client, http-client-tls, http-conduit + , http-download, http-types, lib, memory, microlens, mintty + , mono-traversable, mtl, mustache, neat-interpolation, network-uri + , open-browser, optparse-applicative, pantry, path, path-io + , persistent, persistent-sqlite, persistent-template, pretty + , primitive, process, project-template, regex-applicative-text + , retry, rio, rio-prettyprint, semigroups, split, stm , streaming-commons, tar, template-haskell, temporary, text , text-metrics, th-reify-many, time, tls, transformers , typed-process, unicode-transforms, unix, unix-compat, unliftio @@ -31334,10 +37816,8 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; }: mkDerivation { pname = "stack"; - version = "1.9.3"; - sha256 = "8e11e315f7f27f670ede9f55ab9e2a0501c15b16eb4346ff2a59b6715fca8b06"; - revision = "3"; - editedCabalFile = "0rycd09sk0c269izk35hby179ja77yya41ql7j3hp7s9ja7j6vfg"; + version = "2.7.1"; + sha256 = "605bd8368b6fef9323ea71b79b08dd62270c49089a86b79fe67355f6b82cbc26"; configureFlags = [ "-fdisable-git-info" "-fhide-dependency-versions" "-fsupported-build" @@ -31346,38 +37826,38 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; isExecutable = true; setupHaskellDepends = [ base Cabal filepath ]; libraryHaskellDepends = [ - aeson annotated-wl-pprint ansi-terminal async attoparsec base - base64-bytestring bindings-uname bytestring Cabal conduit - conduit-extra containers cryptonite cryptonite-conduit deepseq - directory echo exceptions extra file-embed filelock filepath - fsnotify generic-deriving hackage-security hashable hpack hpc - http-client http-client-tls http-conduit http-types memory - microlens mintty monad-logger mono-traversable mtl mustache - neat-interpolation network-uri open-browser optparse-applicative - path path-io persistent persistent-sqlite persistent-template - pretty primitive process project-template regex-applicative-text - resourcet retry rio semigroups split stm store store-core - streaming-commons tar template-haskell temporary text text-metrics - th-reify-many time tls transformers typed-process - unicode-transforms unix unix-compat unliftio unordered-containers - vector yaml zip-archive zlib + aeson annotated-wl-pprint ansi-terminal array async attoparsec base + base64-bytestring bytestring Cabal casa-client casa-types colour + conduit conduit-extra containers cryptonite cryptonite-conduit + deepseq directory echo exceptions extra file-embed filelock + filepath fsnotify generic-deriving hackage-security hashable + hi-file-parser hpack hpc http-client http-client-tls http-conduit + http-download http-types memory microlens mintty mono-traversable + mtl mustache neat-interpolation network-uri open-browser + optparse-applicative pantry path path-io persistent + persistent-sqlite persistent-template pretty primitive process + project-template regex-applicative-text retry rio rio-prettyprint + semigroups split stm streaming-commons tar template-haskell + temporary text text-metrics th-reify-many time tls transformers + typed-process unicode-transforms unix unix-compat unliftio + unordered-containers vector yaml zip-archive zlib ]; executableHaskellDepends = [ - aeson annotated-wl-pprint ansi-terminal async attoparsec base - base64-bytestring bindings-uname bytestring Cabal conduit - conduit-extra containers cryptonite cryptonite-conduit deepseq - directory echo exceptions extra file-embed filelock filepath - fsnotify generic-deriving hackage-security hashable hpack hpc - http-client http-client-tls http-conduit http-types memory - microlens mintty monad-logger mono-traversable mtl mustache - neat-interpolation network-uri open-browser optparse-applicative - path path-io persistent persistent-sqlite persistent-template - pretty primitive process project-template regex-applicative-text - resourcet retry rio semigroups split stm store store-core - streaming-commons tar template-haskell temporary text text-metrics - th-reify-many time tls transformers typed-process - unicode-transforms unix unix-compat unliftio unordered-containers - vector yaml zip-archive zlib + aeson annotated-wl-pprint ansi-terminal array async attoparsec base + base64-bytestring bytestring Cabal casa-client casa-types colour + conduit conduit-extra containers cryptonite cryptonite-conduit + deepseq directory echo exceptions extra file-embed filelock + filepath fsnotify generic-deriving hackage-security hashable + hi-file-parser hpack hpc http-client http-client-tls http-conduit + http-download http-types memory microlens mintty mono-traversable + mtl mustache neat-interpolation network-uri open-browser + optparse-applicative pantry path path-io persistent + persistent-sqlite persistent-template pretty primitive process + project-template regex-applicative-text retry rio rio-prettyprint + semigroups split stm streaming-commons tar template-haskell + temporary text text-metrics th-reify-many time tls transformers + typed-process unicode-transforms unix unix-compat unliftio + unordered-containers vector yaml zip-archive zlib ]; doHaddock = false; doCheck = false; @@ -31389,63 +37869,45 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; ''; homepage = "http://haskellstack.org"; description = "The Haskell Tool Stack"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "stack2nix" = callPackage - ({ mkDerivation, async, base, bytestring, Cabal, cabal2nix - , containers, directory, distribution-nixpkgs, filepath, hackage-db - , language-nix, lens, optparse-applicative, path, pretty, process - , regex-pcre, SafeSemaphore, stack, stdenv, temporary, text, time - }: + "stack-templatizer" = callPackage + ({ mkDerivation, base, bytestring, directory, filepath, lib }: mkDerivation { - pname = "stack2nix"; - version = "0.2.2"; - src = ./.; - configureFlags = [ "--ghc-option=-Werror" ]; - isLibrary = true; + pname = "stack-templatizer"; + version = "0.1.0.2"; + sha256 = "dc10b2c56dd155ab22891584a9303407209acb9fcdff710d388609fd87eae973"; + isLibrary = false; isExecutable = true; - libraryHaskellDepends = [ - async base bytestring Cabal cabal2nix containers directory - distribution-nixpkgs filepath hackage-db language-nix lens - optparse-applicative path pretty process regex-pcre SafeSemaphore - stack temporary text time - ]; - executableHaskellDepends = [ - base Cabal optparse-applicative time - ]; - doHaddock = false; - doCheck = false; - description = "Convert stack.yaml files into Nix build instructions."; - license = stdenv.lib.licenses.mit; - }) {}; - "starter" = callPackage - ({ mkDerivation, base, fsnotify, stdenv }: - mkDerivation { - pname = "starter"; - version = "0.3.0"; - sha256 = "fd569cd27cfd62fb9d3e544e222450ec2734c44a3293994f35a26af982ce3d93"; - libraryHaskellDepends = [ base fsnotify ]; + executableHaskellDepends = [ base bytestring directory filepath ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/rkaippully/starter#readme"; - description = "Develop applications without restarts"; - license = stdenv.lib.licenses.mpl20; + homepage = "https://github.com/prikhi/stack-templatizer#readme"; + description = "Generate a stack template from a folder"; + license = lib.licenses.bsd3; }) {}; - "state-codes" = callPackage - ({ mkDerivation, aeson, base, shakespeare, stdenv, text }: + "stackcollapse-ghc" = callPackage + ({ mkDerivation, base, bytestring, containers, extra, foldl, lib + , recursion-schemes, rosezipper, safe, text, transformers + }: mkDerivation { - pname = "state-codes"; - version = "0.1.3"; - sha256 = "1667dc977607fc89a0ca736294b2f0a19608fbe861f03f404c3f8ee91fd0f4a1"; - libraryHaskellDepends = [ aeson base shakespeare text ]; + pname = "stackcollapse-ghc"; + version = "0.0.1.3"; + sha256 = "b3d5759fb7e3e84d50f39ca963cc2527acafb4342e55a7ab98518975480f4714"; + isLibrary = false; + isExecutable = true; + executableHaskellDepends = [ + base bytestring containers extra foldl recursion-schemes rosezipper + safe text transformers + ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/acamino/state-codes#README"; - description = "ISO 3166-2:US state codes and i18n names"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/marcin-rzeznicki/stackcollapse-ghc"; + description = "Program to fold GHC prof files into flamegraph input"; + license = lib.licenses.gpl3Only; }) {}; "stateref" = callPackage - ({ mkDerivation, base, mtl, stdenv, stm }: + ({ mkDerivation, base, lib, mtl, stm }: mkDerivation { pname = "stateref"; version = "0.3"; @@ -31455,34 +37917,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://code.haskell.org/~mokus/stateref/"; description = "Abstraction for things that work like IORef"; - license = stdenv.lib.licenses.publicDomain; - }) {}; - "statestack" = callPackage - ({ mkDerivation, base, mtl, stdenv, transformers - , transformers-compat - }: - mkDerivation { - pname = "statestack"; - version = "0.2.0.5"; - sha256 = "f4eadcf9b08c14cb084436f81e16edf78d6eeda77a3f93e38ba5d7e263ea5f66"; - revision = "3"; - editedCabalFile = "0s9v88gcc5wnfj4c6xq86asadmh4y8z8ycv2wz5nwfwfazfgzcy3"; - libraryHaskellDepends = [ - base mtl transformers transformers-compat - ]; - doHaddock = false; - doCheck = false; - description = "Simple State-like monad transformer with saveable and restorable state"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.publicDomain; }) {}; "static-text" = callPackage - ({ mkDerivation, base, bytestring, stdenv, template-haskell, text + ({ mkDerivation, base, bytestring, lib, template-haskell, text , vector }: mkDerivation { pname = "static-text"; - version = "0.2.0.3"; - sha256 = "599d7a3e432f37128aa6d5ffa985bea7d35961698fc0df7c1cba7e3875413da1"; + version = "0.2.0.6"; + sha256 = "f1ff8dae57fad50bace497ff70c8aa7c960b204725d2c28021d5d8b0c48ae693"; libraryHaskellDepends = [ base bytestring template-haskell text vector ]; @@ -31490,20 +37934,20 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/dzhus/static-text#readme"; description = "Lists, Texts, ByteStrings and Vectors of statically known length"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "statistics" = callPackage - ({ mkDerivation, aeson, base, base-orphans, binary - , data-default-class, deepseq, dense-linear-algebra, math-functions - , monad-par, mwc-random, primitive, stdenv, vector + ({ mkDerivation, aeson, async, base, base-orphans, binary + , data-default-class, deepseq, dense-linear-algebra, lib + , math-functions, monad-par, mwc-random, primitive, vector , vector-algorithms, vector-binary-instances, vector-th-unbox }: mkDerivation { pname = "statistics"; - version = "0.15.0.0"; - sha256 = "95e9c45c95e81a35c7bd7443e8d6626fd100505a567de47622185fe9c8be6472"; + version = "0.15.2.0"; + sha256 = "c496dbb8767a65ea3c352fd08ce1918200a0cc9d8f8b5f262aebbb43dee22a49"; libraryHaskellDepends = [ - aeson base base-orphans binary data-default-class deepseq + aeson async base base-orphans binary data-default-class deepseq dense-linear-algebra math-functions monad-par mwc-random primitive vector vector-algorithms vector-binary-instances vector-th-unbox ]; @@ -31511,31 +37955,56 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/bos/statistics"; description = "A library of statistical types, data, and functions"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; + }) {}; + "status-notifier-item" = callPackage + ({ mkDerivation, base, byte-order, bytestring, bytestring-to-vector + , containers, dbus, dbus-hslogger, filepath, hslogger, lens, lib + , optparse-applicative, template-haskell, text, transformers + , vector + }: + mkDerivation { + pname = "status-notifier-item"; + version = "0.3.0.5"; + sha256 = "01200ea65d8ce5ffc570e006aa566cfa0a7849316852783ef1b783c5c36bb398"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base byte-order bytestring bytestring-to-vector containers dbus + filepath hslogger lens template-haskell text transformers vector + ]; + executableHaskellDepends = [ + base dbus dbus-hslogger hslogger optparse-applicative + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/IvanMalison/status-notifier-item#readme"; + description = "A wrapper over the StatusNotifierItem/libappindicator dbus specification"; + license = lib.licenses.bsd3; }) {}; "stb-image-redux" = callPackage - ({ mkDerivation, base, stdenv, vector }: + ({ mkDerivation, base, lib, vector }: mkDerivation { pname = "stb-image-redux"; - version = "0.2.1.2"; - sha256 = "3bf41af8950ecf0ac5645634fdd233f941a904c6c56222ff4efb03f5d17043e8"; + version = "0.2.1.3"; + sha256 = "24da421150f269ebb6679d7ea2c18dcea5cd253b3e27bf4bded656e7e90eb507"; libraryHaskellDepends = [ base vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/typedrat/stb-image-redux#readme"; description = "Image loading and writing microlibrary"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "step-function" = callPackage ({ mkDerivation, base, base-compat-batteries, containers, deepseq - , QuickCheck, stdenv + , lib, QuickCheck }: mkDerivation { pname = "step-function"; version = "0.2"; sha256 = "d260fcb72bd3afe3c2b0a80f3f3a5c7afae63d98138d137a80ed8ba131fee7d5"; - revision = "1"; - editedCabalFile = "03ga9vwaxsf0c73fciavkm925l7lkgya1a6xghyb8ainrav0bfq4"; + revision = "5"; + editedCabalFile = "03xg6n7dyz73y3llbbahnlh46xfy2iq29s1jwjp22qxd4z6xndsa"; libraryHaskellDepends = [ base base-compat-batteries containers deepseq QuickCheck ]; @@ -31543,23 +38012,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/jonpetterbergman/step-function"; description = "Staircase functions or piecewise constant functions"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "stm" = callPackage - ({ mkDerivation, array, base, stdenv }: - mkDerivation { - pname = "stm"; - version = "2.5.0.0"; - sha256 = "59e3685c66cbc54770d423f097ce50661005c99160be0f43a2b7fef7916494c6"; - libraryHaskellDepends = [ array base ]; - doHaddock = false; - doCheck = false; - homepage = "https://wiki.haskell.org/Software_transactional_memory"; - description = "Software Transactional Memory"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "stm-chans" = callPackage - ({ mkDerivation, base, Cabal, stdenv, stm }: + ({ mkDerivation, base, Cabal, lib, stm }: mkDerivation { pname = "stm-chans"; version = "3.0.0.4"; @@ -31572,12 +38028,12 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://code.haskell.org/~wren/"; description = "Additional types of channels for STM"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "stm-conduit" = callPackage ({ mkDerivation, async, base, cereal, cereal-conduit, conduit - , conduit-extra, directory, exceptions, monad-loops, resourcet - , stdenv, stm, stm-chans, transformers, unliftio + , conduit-extra, directory, exceptions, lib, monad-loops, resourcet + , stm, stm-chans, transformers, unliftio }: mkDerivation { pname = "stm-conduit"; @@ -31592,10 +38048,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/cgaebel/stm-conduit"; description = "Introduces conduits to channels, and promotes using conduits concurrently"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "stm-delay" = callPackage - ({ mkDerivation, base, stdenv, stm }: + ({ mkDerivation, base, lib, stm }: mkDerivation { pname = "stm-delay"; version = "0.1.1.1"; @@ -31605,10 +38061,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/joeyadams/haskell-stm-delay"; description = "Updatable one-shot timer polled with STM"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "stm-extras" = callPackage - ({ mkDerivation, base, stdenv, stm }: + ({ mkDerivation, base, lib, stm }: mkDerivation { pname = "stm-extras"; version = "0.1.0.3"; @@ -31618,10 +38074,22 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/louispan/stm-extras#readme"; description = "Extra STM functions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "stm-lifted" = callPackage + ({ mkDerivation, base, lib, stm, transformers }: + mkDerivation { + pname = "stm-lifted"; + version = "2.5.0.0"; + sha256 = "a818313be5acbf089b0ea6b4b76d49b70f16fcda58b647a0588f2124f4804a7f"; + libraryHaskellDepends = [ base stm transformers ]; + doHaddock = false; + doCheck = false; + description = "Software Transactional Memory lifted to MonadIO"; + license = lib.licenses.bsd3; }) {}; "stm-split" = callPackage - ({ mkDerivation, base, stdenv, stm }: + ({ mkDerivation, base, lib, stm }: mkDerivation { pname = "stm-split"; version = "0.0.2.1"; @@ -31630,23 +38098,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "TMVars, TVars and TChans with distinguished input and output side"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "stopwatch" = callPackage - ({ mkDerivation, base, clock, stdenv, transformers }: + ({ mkDerivation, base, clock, lib, transformers }: mkDerivation { pname = "stopwatch"; - version = "0.1.0.5"; - sha256 = "461ed69edf8d68cdadd8d0c6159e9c2fef71d1a440c6feded0b07c77d9113461"; + version = "0.1.0.6"; + sha256 = "5018769e91e551086bc96457da44faa3a03b4470a55212505102bc09518174bf"; libraryHaskellDepends = [ base clock transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/debug-ito/stopwatch"; description = "A simple stopwatch utility"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "storable-complex" = callPackage - ({ mkDerivation, base, base-orphans, stdenv }: + ({ mkDerivation, base, base-orphans, lib }: mkDerivation { pname = "storable-complex"; version = "0.2.3.0"; @@ -31656,15 +38124,28 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/cartazio/storable-complex"; description = "Storable instance for Complex"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "storable-endian" = callPackage + ({ mkDerivation, base, byteorder, lib }: + mkDerivation { + pname = "storable-endian"; + version = "0.2.6"; + sha256 = "3743ac8f084ed3187b83f17b4fac280e77c5df01f7910f42b6a1bf09d5a65489"; + revision = "1"; + editedCabalFile = "12f8sscsvsarlwz3p6kk9vbvqsbyhs8lhafgn9h7c0z6pz1amrya"; + libraryHaskellDepends = [ base byteorder ]; + doHaddock = false; + doCheck = false; + description = "Storable instances with endianness"; + license = lib.licenses.bsd3; }) {}; "storable-record" = callPackage - ({ mkDerivation, base, semigroups, stdenv, transformers, utility-ht - }: + ({ mkDerivation, base, lib, semigroups, transformers, utility-ht }: mkDerivation { pname = "storable-record"; - version = "0.0.4"; - sha256 = "ceffb2f08d8abc37e338ad924b264c230d5e54ecccaf1c22802c3107ea0c5a42"; + version = "0.0.5"; + sha256 = "8edf155d2151b53996d72b0f51131ab46f5a60c9f92247f565c98437fa02ce9e"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -31674,10 +38155,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://code.haskell.org/~thielema/storable-record/"; description = "Elegant definition of Storable instances for records"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "storable-tuple" = callPackage - ({ mkDerivation, base, base-orphans, stdenv, storable-record + ({ mkDerivation, base, base-orphans, lib, storable-record , utility-ht }: mkDerivation { @@ -31691,16 +38172,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://code.haskell.org/~thielema/storable-tuple/"; description = "Storable instance for pairs and triples"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "storablevector" = callPackage - ({ mkDerivation, base, deepseq, non-negative, QuickCheck - , semigroups, stdenv, syb, transformers, unsafe, utility-ht + ({ mkDerivation, base, deepseq, lib, non-negative, QuickCheck + , semigroups, syb, transformers, unsafe, utility-ht }: mkDerivation { pname = "storablevector"; - version = "0.2.13"; - sha256 = "f83742d572aca9431f8ee6325d29169bc630beb2d8ab1957f7165abed138b9fe"; + version = "0.2.13.1"; + sha256 = "5ce4c2f5b03c57a33e2cda2fa02507bb5728993d92fbdece8e95efc2eceacf19"; libraryHaskellDepends = [ base deepseq non-negative QuickCheck semigroups syb transformers unsafe utility-ht @@ -31709,47 +38190,46 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Storable_Vector"; description = "Fast, packed, strict storable arrays with a list interface like ByteString"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "store" = callPackage ({ mkDerivation, array, async, base, base-orphans , base64-bytestring, bifunctors, bytestring, containers , contravariant, cryptohash, deepseq, directory, filepath, free - , ghc-prim, hashable, hspec, hspec-smallcheck, integer-gmp - , lifted-base, monad-control, mono-traversable, network, primitive - , resourcet, safe, semigroups, smallcheck, stdenv, store-core, syb + , ghc-prim, hashable, hspec, hspec-smallcheck, integer-gmp, lib + , lifted-base, monad-control, mono-traversable, nats, network + , primitive, resourcet, safe, smallcheck, store-core, syb , template-haskell, text, th-lift, th-lift-instances, th-orphans , th-reify-many, th-utilities, time, transformers , unordered-containers, vector, void }: mkDerivation { pname = "store"; - version = "0.5.0.1"; - sha256 = "238e8585de3cc551a39003499b4f8ade161630ef18525b30a790a22bca39f536"; + version = "0.7.11"; + sha256 = "99d3c9f1a84b0d71440e472a476c35f611c2359964c73a8bac6ee18e427b290e"; libraryHaskellDepends = [ array async base base-orphans base64-bytestring bifunctors bytestring containers contravariant cryptohash deepseq directory filepath free ghc-prim hashable hspec hspec-smallcheck integer-gmp - lifted-base monad-control mono-traversable network primitive - resourcet safe semigroups smallcheck store-core syb - template-haskell text th-lift th-lift-instances th-orphans - th-reify-many th-utilities time transformers unordered-containers - vector void + lifted-base monad-control mono-traversable nats network primitive + resourcet safe smallcheck store-core syb template-haskell text + th-lift th-lift-instances th-orphans th-reify-many th-utilities + time transformers unordered-containers vector void ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/fpco/store#readme"; + homepage = "https://github.com/mgsloan/store#readme"; description = "Fast binary serialization"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "store-core" = callPackage - ({ mkDerivation, base, bytestring, ghc-prim, primitive, stdenv - , text, transformers + ({ mkDerivation, base, bytestring, ghc-prim, lib, primitive, text + , transformers }: mkDerivation { pname = "store-core"; - version = "0.4.4"; - sha256 = "5baecf8c074ff8dca4633630adc979696d7e8ee0a58e143e4d6d0f5c79f30991"; + version = "0.4.4.4"; + sha256 = "1e204ffb4c494808ac64bec2381f2a2c4d18fac70ad325559a7cc11bcae54140"; libraryHaskellDepends = [ base bytestring ghc-prim primitive text transformers ]; @@ -31757,17 +38237,35 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/fpco/store#readme"; description = "Fast and lightweight binary serialization"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "store-streaming" = callPackage + ({ mkDerivation, async, base, bytestring, conduit, free, lib + , resourcet, store, store-core, streaming-commons, text + , transformers + }: + mkDerivation { + pname = "store-streaming"; + version = "0.2.0.3"; + sha256 = "7820b1d5cb95fd27c6b7f0b46ae655362e97cb8da3521c33c92a3fac7b24262c"; + libraryHaskellDepends = [ + async base bytestring conduit free resourcet store store-core + streaming-commons text transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/fpco/store#readme"; + description = "Streaming interfaces for `store`"; + license = lib.licenses.mit; }) {}; "stratosphere" = callPackage ({ mkDerivation, aeson, aeson-pretty, base, bytestring, containers - , hashable, lens, stdenv, template-haskell, text - , unordered-containers + , hashable, lens, lib, template-haskell, text, unordered-containers }: mkDerivation { pname = "stratosphere"; - version = "0.29.1"; - sha256 = "9fe63f0e848ef42bd1f9d9aabd69b25caef9edd49609c4a0f51d253213587548"; + version = "0.59.1"; + sha256 = "bbef27bea714555527c38bb416341c371eafbce852285cb22c89487f1ffa9bbd"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -31778,36 +38276,33 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/frontrowed/stratosphere#readme"; description = "EDSL for AWS CloudFormation"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "streaming" = callPackage - ({ mkDerivation, base, containers, ghc-prim, mmorph, mtl - , semigroups, stdenv, transformers, transformers-base + ({ mkDerivation, base, containers, ghc-prim, lib, mmorph, mtl + , transformers, transformers-base }: mkDerivation { pname = "streaming"; - version = "0.2.2.0"; - sha256 = "5a6b7744695a2651e9835789a7c4ce48dbd5f13ee99f35f63261f9501ce1cd11"; + version = "0.2.3.0"; + sha256 = "b4008eee1fcee6a9f63d0d31eebefd6cf72731fab65d943831338c3961fafd62"; libraryHaskellDepends = [ - base containers ghc-prim mmorph mtl semigroups transformers - transformers-base + base containers ghc-prim mmorph mtl transformers transformers-base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-streaming/streaming"; description = "an elementary streaming prelude and general stream type"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "streaming-attoparsec" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, stdenv, streaming + ({ mkDerivation, attoparsec, base, bytestring, lib, streaming , streaming-bytestring }: mkDerivation { pname = "streaming-attoparsec"; - version = "1.0.0"; - sha256 = "ff28925269ed98f03ef10a482980030dd7c8ef4c05ef6e32d147db9331df6102"; - revision = "2"; - editedCabalFile = "07hqs8nn1rhsqckqmw46yp19kd0vk35q139al6yq0k1dzpvsrcsx"; + version = "1.0.0.1"; + sha256 = "1ec9f3570dd7e27803053b3c682de94a32c2a1026d14b91c0fb0a98577942f94"; libraryHaskellDepends = [ attoparsec base bytestring streaming streaming-bytestring ]; @@ -31815,34 +38310,35 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/haskell-streaming/streaming-attoparsec"; description = "Attoparsec integration for the streaming ecosystem"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "streaming-bytestring" = callPackage - ({ mkDerivation, base, bytestring, deepseq, exceptions, mmorph, mtl - , resourcet, stdenv, streaming, transformers, transformers-base + ({ mkDerivation, base, bytestring, deepseq, exceptions, ghc-prim + , lib, mmorph, mtl, resourcet, streaming, transformers + , transformers-base }: mkDerivation { pname = "streaming-bytestring"; - version = "0.1.6"; - sha256 = "c1d723fc9676b85f62f9fc937d756af61d81f69c9c6591e5d38c9b09b7a253d3"; + version = "0.2.1"; + sha256 = "beaff8a1435f877ee7748c630e3d592244b2b525e0595584a2d189cec11331fb"; libraryHaskellDepends = [ - base bytestring deepseq exceptions mmorph mtl resourcet streaming - transformers transformers-base + base bytestring deepseq exceptions ghc-prim mmorph mtl resourcet + streaming transformers transformers-base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell-streaming/streaming-bytestring"; - description = "effectful byte steams, or: bytestring io done right"; - license = stdenv.lib.licenses.bsd3; + description = "Fast, effectful byte streams"; + license = lib.licenses.bsd3; }) {}; "streaming-commons" = callPackage - ({ mkDerivation, array, async, base, bytestring, directory, network - , process, random, stdenv, stm, text, transformers, unix, zlib + ({ mkDerivation, array, async, base, bytestring, directory, lib + , network, process, random, stm, text, transformers, unix, zlib }: mkDerivation { pname = "streaming-commons"; - version = "0.2.1.0"; - sha256 = "d8d1fe588924479ea7eefce8c6af77dfb373ee6bde7f4691bdfcbd782b36d68d"; + version = "0.2.2.1"; + sha256 = "306940bf4878a0b714e6746a7f934d018100efc86332c176a648014bfe1e81dd"; libraryHaskellDepends = [ array async base bytestring directory network process random stm text transformers unix zlib @@ -31851,62 +38347,36 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/fpco/streaming-commons"; description = "Common lower-level functions needed by various streaming data libraries"; - license = stdenv.lib.licenses.mit; - }) {}; - "streaming-wai" = callPackage - ({ mkDerivation, base, bytestring, bytestring-builder, http-types - , stdenv, streaming, wai - }: - mkDerivation { - pname = "streaming-wai"; - version = "0.1.1"; - sha256 = "35b4182386cc1d23731b3eac78dda79a1b7878c0b6bd78fd99907c776dbfaf30"; - libraryHaskellDepends = [ - base bytestring bytestring-builder http-types streaming wai - ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/jb55/streaming-wai"; - description = "Streaming Wai utilities"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "streamly" = callPackage - ({ mkDerivation, atomic-primops, base, clock, containers - , exceptions, ghc-prim, heaps, lockfree-queue, monad-control, mtl - , stdenv, transformers, transformers-base + ({ mkDerivation, atomic-primops, base, containers, deepseq + , directory, exceptions, fusion-plugin-types, ghc-prim, heaps, lib + , lockfree-queue, monad-control, mtl, network, primitive + , transformers, transformers-base }: mkDerivation { pname = "streamly"; - version = "0.5.2"; - sha256 = "e649c07776c6f04ca2975912c8fc9ced53ddc243b092efc5fec6416fca488ade"; + version = "0.7.3"; + sha256 = "63b232a425881f58bc83b635690a15220178a5234808110e7fb190c3b0f77285"; + revision = "1"; + editedCabalFile = "1fbhk59p5hjkxf4dnghs8wb70pyv0kx6br5sf4csf4vk1rkqyljw"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - atomic-primops base clock containers exceptions ghc-prim heaps - lockfree-queue monad-control mtl transformers transformers-base + atomic-primops base containers deepseq directory exceptions + fusion-plugin-types ghc-prim heaps lockfree-queue monad-control mtl + network primitive transformers transformers-base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/composewell/streamly"; description = "Beautiful Streaming, Concurrent and Reactive Composition"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "streamproc" = callPackage - ({ mkDerivation, base, stdenv }: - mkDerivation { - pname = "streamproc"; - version = "1.6.2"; - sha256 = "e76effaaff83e6a066df949415db109b405bda0aaeb95f0710906c65892584f2"; - libraryHaskellDepends = [ base ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/peti/streamproc"; - description = "Stream Processer Arrow"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "streams" = callPackage - ({ mkDerivation, adjunctions, base, comonad, distributive - , semigroupoids, semigroups, stdenv + ({ mkDerivation, adjunctions, base, comonad, distributive, lib + , semigroupoids, semigroups }: mkDerivation { pname = "streams"; @@ -31919,54 +38389,95 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/streams/issues"; description = "Various Haskell 2010 stream comonads"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "streamt" = callPackage + ({ mkDerivation, base, lib, logict, mtl }: + mkDerivation { + pname = "streamt"; + version = "0.5.0.0"; + sha256 = "05a5e37b69154ac19730597bb85e690523b1a47a350adb7ee5b0a0b962365964"; + libraryHaskellDepends = [ base logict mtl ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/davidar/streamt"; + description = "Simple, Fair and Terminating Backtracking Monad Transformer"; + license = lib.licenses.bsd3; }) {}; "strict" = callPackage - ({ mkDerivation, array, base, stdenv }: + ({ mkDerivation, assoc, base, binary, bytestring, deepseq, ghc-prim + , hashable, lib, text, these, transformers + }: mkDerivation { pname = "strict"; - version = "0.3.2"; - sha256 = "2cd35a67938db635a87617d9576d5df0158b581e8e5694f07487c0f4b1549221"; - libraryHaskellDepends = [ array base ]; + version = "0.4.0.1"; + sha256 = "dff6abc08ad637e51891bb8b475778c40926c51219eda60fd64f0d9680226241"; + libraryHaskellDepends = [ + assoc base binary bytestring deepseq ghc-prim hashable text these + transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell-strict/strict"; + description = "Strict data types and String IO"; + license = lib.licenses.bsd3; + }) {}; + "strict-concurrency" = callPackage + ({ mkDerivation, base, deepseq, lib }: + mkDerivation { + pname = "strict-concurrency"; + version = "0.2.4.3"; + sha256 = "02d934ec5053d3d42031798e5a3cd25547ccde5973d562f9fc943d635d9956c0"; + libraryHaskellDepends = [ base deepseq ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ygale/strict-concurrency"; + description = "Strict concurrency abstractions"; + license = lib.licenses.bsd3; + }) {}; + "strict-list" = callPackage + ({ mkDerivation, base, hashable, lib, semigroupoids }: + mkDerivation { + pname = "strict-list"; + version = "0.1.5"; + sha256 = "ba7338766ba5fbb4069b748e5bdce12866379c32f1ab1c6015d45dbd1010bb1a"; + libraryHaskellDepends = [ base hashable semigroupoids ]; doHaddock = false; doCheck = false; - homepage = "http://www.cse.unsw.edu.au/~rl/code/strict.html"; - description = "Strict data types and String IO"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/nikita-volkov/strict-list"; + description = "Strict linked list"; + license = lib.licenses.mit; }) {}; - "strict-base-types" = callPackage - ({ mkDerivation, aeson, base, bifunctors, binary, deepseq, ghc-prim - , hashable, lens, QuickCheck, stdenv, strict - }: + "strict-tuple" = callPackage + ({ mkDerivation, base, bifunctors, deepseq, hashable, lib }: mkDerivation { - pname = "strict-base-types"; - version = "0.6.1"; - sha256 = "f8866a3acc7d61f1fbffc2823c24d35b4f63f90612bf0c63292f3d25a3dc307a"; - libraryHaskellDepends = [ - aeson base bifunctors binary deepseq ghc-prim hashable lens - QuickCheck strict - ]; + pname = "strict-tuple"; + version = "0.1.4"; + sha256 = "384382a81ff0e92c159e031e634b6dcaadf790190796d6dced850d3a5171de19"; + libraryHaskellDepends = [ base bifunctors deepseq hashable ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/meiersi/strict-base-types"; - description = "Strict variants of the types provided in base"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/mitchellwrosen/strict-tuple"; + description = "Strict tuples"; + license = lib.licenses.bsd3; }) {}; - "strict-concurrency" = callPackage - ({ mkDerivation, base, deepseq, stdenv }: + "strict-tuple-lens" = callPackage + ({ mkDerivation, base, lens, lib, strict-tuple }: mkDerivation { - pname = "strict-concurrency"; - version = "0.2.4.3"; - sha256 = "02d934ec5053d3d42031798e5a3cd25547ccde5973d562f9fc943d635d9956c0"; - libraryHaskellDepends = [ base deepseq ]; + pname = "strict-tuple-lens"; + version = "0.1.0.1"; + sha256 = "8f0314bfa782b60ece7a604234f4349c05701d7fe83dcfb4397d6ee7d75f70ef"; + revision = "1"; + editedCabalFile = "0875r7kva6ym17fdklh18vm4s04sd9pj0w55km8jv2kmbkmfja8k"; + libraryHaskellDepends = [ base lens strict-tuple ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/ygale/strict-concurrency"; - description = "Strict concurrency abstractions"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/emilypi/strict-tuple-lens"; + description = "Optics for the `strict-tuple` library"; + license = lib.licenses.bsd3; }) {}; "string-class" = callPackage - ({ mkDerivation, base, bytestring, stdenv, tagged, text }: + ({ mkDerivation, base, bytestring, lib, tagged, text }: mkDerivation { pname = "string-class"; version = "0.1.7.0"; @@ -31976,10 +38487,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/string-class/string-class"; description = "String class library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "string-combinators" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "string-combinators"; version = "0.6.0.5"; @@ -31989,10 +38500,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/basvandijk/string-combinators"; description = "Polymorphic functions to build and combine stringlike values"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "string-conv" = callPackage - ({ mkDerivation, base, bytestring, stdenv, text }: + ({ mkDerivation, base, bytestring, lib, text }: mkDerivation { pname = "string-conv"; version = "0.1.2"; @@ -32002,10 +38513,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/Soostone/string-conv"; description = "Standardized conversion between string types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "string-conversions" = callPackage - ({ mkDerivation, base, bytestring, stdenv, text, utf8-string }: + ({ mkDerivation, base, bytestring, lib, text, utf8-string }: mkDerivation { pname = "string-conversions"; version = "0.4.0.1"; @@ -32015,39 +38526,74 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/soenkehahn/string-conversions#readme"; description = "Simplifies dealing with different types for strings"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "string-interpolate" = callPackage + ({ mkDerivation, base, bytestring, haskell-src-exts + , haskell-src-meta, lib, split, template-haskell, text + , text-conversions, utf8-string + }: + mkDerivation { + pname = "string-interpolate"; + version = "0.3.1.1"; + sha256 = "c96c1506397ae95fc6a15f6bb6c983bb20d73d2da562ac79d7d8eb9a74de1f42"; + libraryHaskellDepends = [ + base bytestring haskell-src-exts haskell-src-meta split + template-haskell text text-conversions utf8-string + ]; + doHaddock = false; + doCheck = false; + homepage = "https://gitlab.com/williamyaoh/string-interpolate/blob/master/README.md"; + description = "Haskell string/text/bytestring interpolation that just works"; + license = lib.licenses.bsd3; }) {}; "string-qq" = callPackage - ({ mkDerivation, base, Cabal, process, stdenv, template-haskell }: + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { pname = "string-qq"; - version = "0.0.2"; - sha256 = "9757cad387856a313729caffe0639215a10be7d72b09c44bcab9e55ee2a8c218"; - revision = "1"; - editedCabalFile = "1flc6mr1nnv8mx69cy1ilwk5gxsidcns82vjdg8dcs8z5axg95kp"; - enableSeparateDataOutput = true; - setupHaskellDepends = [ base Cabal process ]; + version = "0.0.4"; + sha256 = "c85b9c1e27596ea8e765e4b630b7be53c331c51b680ad46cc2d248d3099fdd71"; libraryHaskellDepends = [ base template-haskell ]; doHaddock = false; doCheck = false; description = "QuasiQuoter for non-interpolated strings, texts and bytestrings"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; + }) {}; + "string-random" = callPackage + ({ mkDerivation, attoparsec, base, containers, lib + , optparse-applicative, random, text, transformers + }: + mkDerivation { + pname = "string-random"; + version = "0.1.4.1"; + sha256 = "cd8e032971e953f91943f36cab42bf4686477c6a522043d41b907dff2b22ffbd"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + attoparsec base containers random text transformers + ]; + executableHaskellDepends = [ base optparse-applicative text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/hiratara/hs-string-random#readme"; + description = "A library for generating random string from a regular experession"; + license = lib.licenses.bsd3; }) {}; "string-transform" = callPackage - ({ mkDerivation, base, bytestring, stdenv, text, utf8-string }: + ({ mkDerivation, base, bytestring, lib, text, utf8-string }: mkDerivation { pname = "string-transform"; - version = "1.1.0"; - sha256 = "4d7daffe1d58671af5111c7179905653d692884cac21f09061768a5a6354e6b8"; + version = "1.1.1"; + sha256 = "1caeff34b02cd860ae1740629ae97f7df8458bb7ab6a83e3b15c124b513e5e21"; libraryHaskellDepends = [ base bytestring text utf8-string ]; doHaddock = false; doCheck = false; homepage = "https://github.com/ncaq/string-transform#readme"; description = "simple and easy haskell string transform wrapper"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "stringbuilder" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "stringbuilder"; version = "0.5.1"; @@ -32056,10 +38602,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A writer monad for multi-line string literals"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "stringsearch" = callPackage - ({ mkDerivation, array, base, bytestring, containers, stdenv }: + ({ mkDerivation, array, base, bytestring, containers, lib }: mkDerivation { pname = "stringsearch"; version = "0.3.6.6"; @@ -32071,74 +38617,167 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://bitbucket.org/dafis/stringsearch"; description = "Fast searching, splitting and replacing of ByteStrings"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "stripe-concepts" = callPackage + ({ mkDerivation, base, bytestring, lib, text }: + mkDerivation { + pname = "stripe-concepts"; + version = "1.0.3"; + sha256 = "028d6ca7c96845e3a9866b57928351aa1408b1ad93fbf1298e1483475d7ad3f3"; + libraryHaskellDepends = [ base bytestring text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/typeclasses/stripe"; + description = "Types for the Stripe API"; + license = lib.licenses.mit; + }) {}; + "stripe-core" = callPackage + ({ mkDerivation, aeson, base, bytestring, lib, mtl, text, time + , transformers, unordered-containers + }: + mkDerivation { + pname = "stripe-core"; + version = "2.6.2"; + sha256 = "2bf22d7cadb968b5c9d35358feaa33d964e7124177d48d4256c17245c3c97201"; + libraryHaskellDepends = [ + aeson base bytestring mtl text time transformers + unordered-containers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/dmjio/stripe-haskell"; + description = "Stripe API for Haskell - Pure Core"; + license = lib.licenses.mit; + }) {}; + "stripe-haskell" = callPackage + ({ mkDerivation, base, lib, stripe-core, stripe-http-client }: + mkDerivation { + pname = "stripe-haskell"; + version = "2.6.2"; + sha256 = "7407ac8daf83e7afa09601b27a06acb7eed33dd8c905b72165228b616272cd0b"; + libraryHaskellDepends = [ base stripe-core stripe-http-client ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/dmjio/stripe"; + description = "Stripe API for Haskell"; + license = lib.licenses.mit; + }) {}; + "stripe-http-client" = callPackage + ({ mkDerivation, aeson, base, bytestring, http-client + , http-client-tls, http-types, lib, stripe-core, text + }: + mkDerivation { + pname = "stripe-http-client"; + version = "2.6.2"; + sha256 = "e33949c04066ef8334e1c1ebe3d4b59107c8b480c4965b0763ba1658056be877"; + libraryHaskellDepends = [ + aeson base bytestring http-client http-client-tls http-types + stripe-core text + ]; + doHaddock = false; + doCheck = false; + description = "Stripe API for Haskell - http-client backend"; + license = lib.licenses.mit; }) {}; "strive" = callPackage ({ mkDerivation, aeson, base, bytestring, data-default, gpolyline - , http-client, http-client-tls, http-types, stdenv - , template-haskell, text, time, transformers + , http-client, http-client-tls, http-types, lib, template-haskell + , text, time, transformers }: mkDerivation { pname = "strive"; - version = "5.0.7"; - sha256 = "6f16cd578bff7cafc0cf923477effc880fe5eb49344a88da329a3297ed2fbe43"; + version = "5.0.14"; + sha256 = "34f656549dee7faf0c38dc14a4047e80d15eb5a84861f2439c22717e68b63029"; libraryHaskellDepends = [ aeson base bytestring data-default gpolyline http-client http-client-tls http-types template-haskell text time transformers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/tfausak/strive#readme"; description = "A client for the Strava V3 API"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "structs" = callPackage - ({ mkDerivation, base, Cabal, cabal-doctest, deepseq, ghc-prim - , primitive, stdenv, template-haskell + ({ mkDerivation, base, deepseq, ghc-prim, lib, primitive + , template-haskell, th-abstraction }: mkDerivation { pname = "structs"; - version = "0.1.1"; - sha256 = "df60ac419775ad96959338c7f14e93a3d47b82728234df206b0145d33694aa41"; - revision = "2"; - editedCabalFile = "1v9gmnj17cm4p491rizvw9xdj255lk1y24gz6s8bqcz56sdb4d4s"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "0.1.6"; + sha256 = "f381d7740f37824e75d74241d56ea761bea8f70da13608b455ca901eb786eb73"; libraryHaskellDepends = [ - base deepseq ghc-prim primitive template-haskell + base deepseq ghc-prim primitive template-haskell th-abstraction ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/structs/"; description = "Strict GC'd imperative object-oriented programming with cheap pointers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "stylish-haskell" = callPackage - ({ mkDerivation, aeson, base, bytestring, containers, directory - , file-embed, filepath, haskell-src-exts, mtl, optparse-applicative - , semigroups, stdenv, strict, syb, yaml + "structured" = callPackage + ({ mkDerivation, aeson, array, base, base16-bytestring, binary + , bytestring, containers, hashable, lib, scientific, tagged, text + , time-compat, transformers, unordered-containers, uuid-types + , vector + }: + mkDerivation { + pname = "structured"; + version = "0.1.0.1"; + sha256 = "aeb4303cee6d040432be90ae9a1ef40c215d178f4fd7c87f00c983fe273027aa"; + libraryHaskellDepends = [ + aeson array base base16-bytestring binary bytestring containers + hashable scientific tagged text time-compat transformers + unordered-containers uuid-types vector + ]; + doHaddock = false; + doCheck = false; + description = "Structure (hash) of your data types"; + license = lib.licenses.bsd3; + }) {}; + "structured-cli" = callPackage + ({ mkDerivation, base, data-default, exceptions, haskeline, lib + , mtl, split, transformers }: mkDerivation { - pname = "stylish-haskell"; - version = "0.9.2.1"; - sha256 = "fc5c8633289d53ec1e4c847eb54ae4fd7f41c26ff14eef5177db6ad39b0b41d3"; + pname = "structured-cli"; + version = "2.7.0.1"; + sha256 = "0f99287c5b8dc3574bf28b2fee0a6a946291ca3891565621cf553624869784a2"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - aeson base bytestring containers directory file-embed filepath - haskell-src-exts mtl semigroups syb yaml + base data-default exceptions haskeline mtl split transformers ]; - executableHaskellDepends = [ - aeson base bytestring containers directory file-embed filepath - haskell-src-exts mtl optparse-applicative strict syb yaml + executableHaskellDepends = [ base data-default mtl split ]; + doHaddock = false; + doCheck = false; + homepage = "https://gitlab.com/codemonkeylabs/structured-cli#readme"; + description = "Application library for building interactive console CLIs"; + license = lib.licenses.bsd3; + }) {}; + "subcategories" = callPackage + ({ mkDerivation, base, containers, data-default, foldl, hashable + , lib, mono-traversable, pointed, primitive, reflection, semialign + , template-haskell, text, these, unordered-containers, vector + , vector-algorithms, vector-builder + }: + mkDerivation { + pname = "subcategories"; + version = "0.1.1.0"; + sha256 = "e98835bfd322e49aff91cea1a2a3af88ec3df53050b22e87232fb22e8d103127"; + libraryHaskellDepends = [ + base containers data-default foldl hashable mono-traversable + pointed primitive reflection semialign template-haskell text these + unordered-containers vector vector-algorithms vector-builder ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/jaspervdj/stylish-haskell"; - description = "Haskell code prettifier"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/konn/subcategories#readme"; + description = "Subcategories induced by class constraints"; + license = lib.licenses.bsd3; }) {}; "sum-type-boilerplate" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { pname = "sum-type-boilerplate"; version = "0.1.1"; @@ -32148,34 +38787,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/jdreaver/sum-type-boilerplate#readme"; description = "Library for reducing the boilerplate involved with sum types"; - license = stdenv.lib.licenses.mit; - }) {}; - "summoner" = callPackage - ({ mkDerivation, aeson, ansi-terminal, base, base-noprelude - , bytestring, directory, filepath, generic-deriving, gitrev - , neat-interpolation, optparse-applicative, process, relude, stdenv - , text, time, tomland - }: - mkDerivation { - pname = "summoner"; - version = "1.2.0"; - sha256 = "6464b44ce9d7c29cb8ef7df376a536ddd948f301a8e64afd0fe811220d895013"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - aeson ansi-terminal base-noprelude bytestring directory filepath - generic-deriving gitrev neat-interpolation optparse-applicative - process relude text time tomland - ]; - executableHaskellDepends = [ base ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/kowainik/summoner"; - description = "Tool for scaffolding completely configured production Haskell projects"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mit; }) {}; "sundown" = callPackage - ({ mkDerivation, base, bytestring, stdenv, text }: + ({ mkDerivation, base, bytestring, lib, text }: mkDerivation { pname = "sundown"; version = "0.6"; @@ -32185,10 +38800,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/bitonic/sundown"; description = "Bindings to the sundown markdown library"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "superbuffer" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "superbuffer"; version = "0.3.1.1"; @@ -32198,78 +38813,19 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/agrafix/superbuffer#readme"; description = "Efficiently build a bytestring from smaller chunks"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "sv-cassava" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, cassava, stdenv - , sv-core, utf8-string, validation, vector - }: - mkDerivation { - pname = "sv-cassava"; - version = "0.3"; - sha256 = "2b1c5725aa13dfed861b975ca359bd0a8186928b098ee35dc94f97792e539cb0"; - revision = "1"; - editedCabalFile = "01xfdl296jcdh7c4yirzf6z0787z941h6p58dn5xhnsr965sncg1"; - libraryHaskellDepends = [ - attoparsec base bytestring cassava sv-core utf8-string validation - vector - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/qfpl/sv"; - description = "Integration to use sv with cassava's parser"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "sv-core" = callPackage - ({ mkDerivation, attoparsec, base, bifunctors, bytestring - , containers, contravariant, deepseq, lens, mtl, parsec - , profunctors, readable, semigroupoids, semigroups, stdenv, text - , transformers, trifecta, utf8-string, validation, vector, void - }: - mkDerivation { - pname = "sv-core"; - version = "0.3.1"; - sha256 = "d028d9aaf0ebabb1c29841f34c5c40f7f4483d0307b51756de92007c6cc44822"; - libraryHaskellDepends = [ - attoparsec base bifunctors bytestring containers contravariant - deepseq lens mtl parsec profunctors readable semigroupoids - semigroups text transformers trifecta utf8-string validation vector - void - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/qfpl/sv"; - description = "Encode and decode separated values (CSV, PSV, ...)"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "svg-builder" = callPackage - ({ mkDerivation, base, blaze-builder, bytestring, hashable, stdenv - , text, unordered-containers - }: - mkDerivation { - pname = "svg-builder"; - version = "0.1.1"; - sha256 = "4fd0e3f2cbc5601fc69e7eab41588cbfa1150dc508d9d86bf5f3d393880382cc"; - revision = "1"; - editedCabalFile = "1bhp9gvid2iis411k1vvyj5krzc4ahxcqcd9cwx9h37jxg180xw1"; - libraryHaskellDepends = [ - base blaze-builder bytestring hashable text unordered-containers - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/diagrams/svg-builder.git"; - description = "DSL for building SVG"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "svg-tree" = callPackage ({ mkDerivation, attoparsec, base, bytestring, containers - , JuicyPixels, lens, linear, mtl, scientific, stdenv, text + , JuicyPixels, lens, lib, linear, mtl, scientific, text , transformers, vector, xml }: mkDerivation { pname = "svg-tree"; - version = "0.6.2.3"; - sha256 = "29e5154e3992413ef13a4c50407b9753df2e60f9fddaae03b5475e77a8d8db6a"; + version = "0.6.2.4"; + sha256 = "4ce471e3c3378587360c2e3de055267991b88d846e858bcc3135b4ea0c171ac2"; + revision = "1"; + editedCabalFile = "12askkxmrzjkssnfa8m6xmdwdxk6v3z26jc63jcgb3q8snxb0hg1"; libraryHaskellDepends = [ attoparsec base bytestring containers JuicyPixels lens linear mtl scientific text transformers vector xml @@ -32277,10 +38833,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "SVG file loader and serializer"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "swagger" = callPackage - ({ mkDerivation, aeson, base, bytestring, stdenv, text, time + ({ mkDerivation, aeson, base, bytestring, lib, text, time , transformers }: mkDerivation { @@ -32294,43 +38850,64 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; description = "Implementation of swagger data model"; license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; + hydraPlatforms = lib.platforms.none; }) {}; "swagger2" = callPackage - ({ mkDerivation, aeson, base, base-compat-batteries, bytestring - , Cabal, cabal-doctest, containers, cookie, generics-sop, hashable - , http-media, insert-ordered-containers, lens, mtl, network - , QuickCheck, scientific, stdenv, template-haskell, text, time - , transformers, transformers-compat, unordered-containers - , uuid-types, vector + ({ mkDerivation, aeson, aeson-pretty, base, base-compat-batteries + , bytestring, Cabal, cabal-doctest, containers, cookie + , generics-sop, hashable, http-media, insert-ordered-containers + , lens, lib, mtl, network, optics-core, optics-th, QuickCheck + , scientific, template-haskell, text, time, transformers + , transformers-compat, unordered-containers, uuid-types, vector }: mkDerivation { pname = "swagger2"; - version = "2.3.1"; - sha256 = "c61fa150dfd4e6f8c17ef66044b7fd1c15f404fc7a91e4dae25e9fb41789271c"; + version = "2.6"; + sha256 = "682afe3b43d6b7c394cab330bb48692b8045dff8db3e8913bbfabee0fa8c706e"; + revision = "2"; + editedCabalFile = "1gdq1kiccn6qv05fnkb2dzsnsds2v3gri29gd8l1x9vx74mpbh0j"; setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ - aeson base base-compat-batteries bytestring containers cookie - generics-sop hashable http-media insert-ordered-containers lens mtl - network QuickCheck scientific template-haskell text time - transformers transformers-compat unordered-containers uuid-types - vector + aeson aeson-pretty base base-compat-batteries bytestring containers + cookie generics-sop hashable http-media insert-ordered-containers + lens mtl network optics-core optics-th QuickCheck scientific + template-haskell text time transformers transformers-compat + unordered-containers uuid-types vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/GetShopTV/swagger2"; description = "Swagger 2.0 data model"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "sweet-egison" = callPackage + ({ mkDerivation, backtracking, base, egison-pattern-src + , egison-pattern-src-th-mode, haskell-src-exts, haskell-src-meta + , lib, logict, template-haskell, transformers + }: + mkDerivation { + pname = "sweet-egison"; + version = "0.1.1.3"; + sha256 = "073a2add3d2502123e3a3315315862e1dc78001d2a96981fbd20d0239fdb592c"; + libraryHaskellDepends = [ + backtracking base egison-pattern-src egison-pattern-src-th-mode + haskell-src-exts haskell-src-meta logict template-haskell + transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/egison/sweet-egison#readme"; + description = "Shallow embedding implementation of non-linear pattern matching"; + license = lib.licenses.bsd3; }) {}; "swish" = callPackage ({ mkDerivation, base, containers, directory, filepath, hashable - , intern, mtl, network-uri, old-locale, polyparse, stdenv, text - , time + , intern, lib, mtl, network-uri, old-locale, polyparse, text, time }: mkDerivation { pname = "swish"; - version = "0.10.0.1"; - sha256 = "f3a9abefb1a15c4d7dcc391e3f466632be1d20f63399a405dfe9e4a4b2c778c6"; + version = "0.10.0.5"; + sha256 = "58e0cb603ace182fe23be2be0fd4b74a56745d4dbe3b5e95a2161654d452c331"; isLibrary = true; isExecutable = true; enableSeparateDataOutput = true; @@ -32341,25 +38918,151 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; executableHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://bitbucket.org/doug_burke/swish/wiki/Home"; + homepage = "https://gitlab.com/dburke/swish"; description = "A semantic web toolkit"; - license = stdenv.lib.licenses.lgpl21; + license = lib.licenses.lgpl21Only; }) {}; "syb" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "syb"; - version = "0.7"; - sha256 = "b8757dce5ab4045c49a0ae90407d575b87ee5523a7dd5dfa5c9d54fcceff42b5"; + version = "0.7.2.1"; + sha256 = "1807c66f77e66786739387f0ae9f16d150d1cfa9d626afcb729f0e9b442a8d96"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "http://www.cs.uu.nl/wiki/GenericProgramming/SYB"; description = "Scrap Your Boilerplate"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "sydtest" = callPackage + ({ mkDerivation, async, base, bytestring, containers, Diff, dlist + , envparse, filepath, lib, MonadRandom, mtl, optparse-applicative + , path, path-io, pretty-show, QuickCheck, quickcheck-io + , random-shuffle, safe, safe-coloured-text + , safe-coloured-text-terminfo, split, text, yaml + , yamlparse-applicative + }: + mkDerivation { + pname = "sydtest"; + version = "0.2.0.0"; + sha256 = "55f85e164f47fa55860741f23ccfa69f59d20f3f02b57739d36fffe8b6bd12cc"; + libraryHaskellDepends = [ + async base bytestring containers Diff dlist envparse filepath + MonadRandom mtl optparse-applicative path path-io pretty-show + QuickCheck quickcheck-io random-shuffle safe safe-coloured-text + safe-coloured-text-terminfo split text yaml yamlparse-applicative + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/sydtest#readme"; + description = "A modern testing framework for Haskell with good defaults and advanced testing features"; + license = "unknown"; + hydraPlatforms = lib.platforms.none; + }) {}; + "sydtest-discover" = callPackage + ({ mkDerivation, base, filepath, lib, optparse-applicative, path + , path-io + }: + mkDerivation { + pname = "sydtest-discover"; + version = "0.0.0.0"; + sha256 = "5d7f55738519e188c539f4018df0527bcf76d15258b40222045da99be266d2cf"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base filepath optparse-applicative path path-io + ]; + executableHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/sydtest#readme"; + description = "Automatic test suite discovery for sydtest"; + license = "unknown"; + hydraPlatforms = lib.platforms.none; + }) {}; + "sydtest-persistent-sqlite" = callPackage + ({ mkDerivation, base, lib, monad-logger, mtl, persistent + , persistent-sqlite, persistent-template, sydtest + }: + mkDerivation { + pname = "sydtest-persistent-sqlite"; + version = "0.1.0.0"; + sha256 = "9e823e8cb111c8ada84df62146497d472f4ae79dc5cfaf933950e454bd0688aa"; + libraryHaskellDepends = [ + base monad-logger mtl persistent persistent-sqlite + persistent-template sydtest + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/sydtest#readme"; + description = "A persistent-sqlite companion library for sydtest"; + license = "unknown"; + hydraPlatforms = lib.platforms.none; + }) {}; + "sydtest-servant" = callPackage + ({ mkDerivation, base, http-client, lib, servant, servant-client + , servant-server, sydtest, sydtest-wai + }: + mkDerivation { + pname = "sydtest-servant"; + version = "0.1.0.0"; + sha256 = "b3d960fc6d53c07ae3e5a445bab87f6c303e4394976696ed5553e100b477c756"; + libraryHaskellDepends = [ + base http-client servant servant-client servant-server sydtest + sydtest-wai + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/sydtest#readme"; + description = "A servant companion library for sydtest"; + license = "unknown"; + hydraPlatforms = lib.platforms.none; + }) {}; + "sydtest-wai" = callPackage + ({ mkDerivation, base, bytestring, case-insensitive, http-client + , http-types, lib, mtl, network, pretty-show, sydtest, text, time + , wai, warp + }: + mkDerivation { + pname = "sydtest-wai"; + version = "0.1.0.0"; + sha256 = "342322150d58033387d96c4ef0783b9e9db9cf50f592bbca5811c102c459613a"; + libraryHaskellDepends = [ + base bytestring case-insensitive http-client http-types mtl network + pretty-show sydtest text time wai warp + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/sydtest#readme"; + description = "A wai companion library for sydtest"; + license = "unknown"; + hydraPlatforms = lib.platforms.none; + }) {}; + "sydtest-yesod" = callPackage + ({ mkDerivation, base, blaze-builder, bytestring, case-insensitive + , containers, cookie, exceptions, http-client, http-types, lib, mtl + , network, pretty-show, sydtest, sydtest-wai, text, time, wai + , xml-conduit, yesod-core, yesod-test + }: + mkDerivation { + pname = "sydtest-yesod"; + version = "0.1.0.0"; + sha256 = "93889712d5d99d66f8fda1b2a47fc921071143402c36bf48183dbdeda0a5be4d"; + libraryHaskellDepends = [ + base blaze-builder bytestring case-insensitive containers cookie + exceptions http-client http-types mtl network pretty-show sydtest + sydtest-wai text time wai xml-conduit yesod-core yesod-test + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/sydtest#readme"; + description = "A yesod companion library for sydtest"; + license = "unknown"; + hydraPlatforms = lib.platforms.none; }) {}; "symbol" = callPackage - ({ mkDerivation, base, containers, deepseq, stdenv }: + ({ mkDerivation, base, containers, deepseq, lib }: mkDerivation { pname = "symbol"; version = "0.2.4"; @@ -32371,10 +39074,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.cs.drexel.edu/~mainland/"; description = "A 'Symbol' type for fast symbol comparison"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "symengine" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "symengine"; version = "0.1.2.0"; @@ -32384,10 +39087,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/symengine/symengine.hs#readme"; description = "SymEngine symbolic mathematics engine for Haskell"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "symmetry-operations-symbols" = callPackage + ({ mkDerivation, base, lib, matrix, matrix-as-xyz, parsec }: + mkDerivation { + pname = "symmetry-operations-symbols"; + version = "0.0.2.1"; + sha256 = "b07a7738bbf590094ba67f51e30d389a1c3dee31f752f0628514c129ce0f3579"; + libraryHaskellDepends = [ base matrix matrix-as-xyz parsec ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/narumij/symmetry-operations-symbols#readme"; + description = "Derivation of symbols and coordinate triplets Library"; + license = lib.licenses.bsd3; }) {}; "sysinfo" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "sysinfo"; version = "0.1.1"; @@ -32397,10 +39113,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/psibi/sysinfo#readme"; description = "Haskell Interface for getting overall system statistics"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "system-argv0" = callPackage - ({ mkDerivation, base, bytestring, stdenv, system-filepath, text }: + ({ mkDerivation, base, bytestring, lib, system-filepath, text }: mkDerivation { pname = "system-argv0"; version = "0.1.1"; @@ -32410,11 +39126,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://john-millikin.com/software/haskell-filesystem/"; description = "Get argv[0] as a FilePath"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "system-fileio" = callPackage - ({ mkDerivation, base, bytestring, stdenv, system-filepath, text - , time, unix + ({ mkDerivation, base, bytestring, lib, system-filepath, text, time + , unix }: mkDerivation { pname = "system-fileio"; @@ -32427,10 +39143,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/fpco/haskell-filesystem"; description = "Consistent filesystem interaction across GHC versions (deprecated)"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "system-filepath" = callPackage - ({ mkDerivation, base, bytestring, Cabal, deepseq, stdenv, text }: + ({ mkDerivation, base, bytestring, Cabal, deepseq, lib, text }: mkDerivation { pname = "system-filepath"; version = "0.4.14"; @@ -32443,16 +39159,28 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/fpco/haskell-filesystem"; description = "High-level, byte-based file and directory path manipulations (deprecated)"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "system-info" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "system-info"; + version = "0.5.2"; + sha256 = "e43c66f64d903ea321d4f5e02510d18925615618b46f7ddaf03c0ed81560354c"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ChaosGroup/system-info#readme"; + description = "Get the name of the operating system"; + license = lib.licenses.mit; }) {}; "systemd" = callPackage - ({ mkDerivation, base, bytestring, network, stdenv, transformers - , unix + ({ mkDerivation, base, bytestring, lib, network, transformers, unix }: mkDerivation { pname = "systemd"; - version = "1.1.2"; - sha256 = "59461920b66b4b63b055b08af464a6fd9ff529f64527dfb573f9396dadd39287"; + version = "2.3.0"; + sha256 = "26b880c3b7f34d3fc035a974a6756bc2e926f4ff72c039106ed96a93922c46b9"; libraryHaskellDepends = [ base bytestring network transformers unix ]; @@ -32460,24 +39188,24 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/erebe/systemd"; description = "Systemd facilities (Socket activation, Notify)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tabular" = callPackage - ({ mkDerivation, base, csv, html, mtl, stdenv }: + ({ mkDerivation, base, csv, html, lib, mtl }: mkDerivation { pname = "tabular"; - version = "0.2.2.7"; - sha256 = "13f8da12108dafcf3194eb6bf25febf0081c7e4734f66d2d4aeee899f3c14ffb"; + version = "0.2.2.8"; + sha256 = "cb7d06eaec7945cd77db2380ed4a9b7a048c5f6abcfba766c328228be033237d"; libraryHaskellDepends = [ base csv html mtl ]; doHaddock = false; doCheck = false; - homepage = "http://hub.darcs.net/kowey/tabular"; + homepage = "https://github.com/bgamari/tabular"; description = "Two-dimensional data tables with rendering functions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tagchup" = callPackage ({ mkDerivation, base, bytestring, containers, data-accessor - , explicit-exception, non-empty, stdenv, transformers, utility-ht + , explicit-exception, lib, non-empty, transformers, utility-ht , xml-basic }: mkDerivation { @@ -32498,13 +39226,14 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; license = "GPL"; }) {}; "tagged" = callPackage - ({ mkDerivation, base, deepseq, stdenv, template-haskell - , transformers + ({ mkDerivation, base, deepseq, lib, template-haskell, transformers }: mkDerivation { pname = "tagged"; - version = "0.8.6"; - sha256 = "ad16def0884cf6f05ae1ae8e90192cf9d8d9673fa264b249499bd9e4fac791dd"; + version = "0.8.6.1"; + sha256 = "f5e0fcf95f0bb4aa63f428f2c01955a41ea1a42cfcf39145ed631f59a9616c02"; + revision = "1"; + editedCabalFile = "1rzqfw2pafxbnfpl1lizf9zldpxyy28g92x4jzq49miw9hr1xpsx"; libraryHaskellDepends = [ base deepseq template-haskell transformers ]; @@ -32512,11 +39241,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/tagged"; description = "Haskell 98 phantom types to avoid unsafely passing dummy arguments"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tagged-binary" = callPackage - ({ mkDerivation, base, base-compat, binary, bytestring, pureMD5 - , stdenv + ({ mkDerivation, base, base-compat, binary, bytestring, lib + , pureMD5 }: mkDerivation { pname = "tagged-binary"; @@ -32528,24 +39257,24 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Provides tools for serializing data tagged with type information"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "tagged-identity" = callPackage - ({ mkDerivation, base, mtl, stdenv, transformers }: + ({ mkDerivation, base, lib, mtl, transformers }: mkDerivation { pname = "tagged-identity"; - version = "0.1.2"; - sha256 = "916dd7fdd15452f3d760c345e023ce99496806b813ab01b03ff1b240bbd50210"; + version = "0.1.3"; + sha256 = "2cec62a7aac67cae90003e811eda26bfcf3c297b9987e548c0d54cc6b653b2d8"; libraryHaskellDepends = [ base mtl transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mrkkrp/tagged-identity"; description = "Trivial monad transformer that allows identical monad stacks have different types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tagged-transformer" = callPackage ({ mkDerivation, base, comonad, contravariant, distributive - , exceptions, mtl, reflection, semigroupoids, stdenv, tagged + , exceptions, lib, mtl, reflection, semigroupoids, tagged }: mkDerivation { pname = "tagged-transformer"; @@ -32559,10 +39288,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/tagged-transformer"; description = "Monad transformer carrying an extra phantom type tag"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tagshare" = callPackage - ({ mkDerivation, base, containers, mtl, stdenv }: + ({ mkDerivation, base, containers, lib, mtl }: mkDerivation { pname = "tagshare"; version = "0.0"; @@ -32571,42 +39300,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "TagShare - explicit sharing with tags"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tagsoup" = callPackage - ({ mkDerivation, base, bytestring, containers, stdenv, text }: + ({ mkDerivation, base, bytestring, containers, lib, text }: mkDerivation { pname = "tagsoup"; - version = "0.14.7"; - sha256 = "9980f28169dd0ee8d9e0a65d553044d9bb24c6f2c7e5f6cf0a53dbd25cf1ec25"; + version = "0.14.8"; + sha256 = "ba7e5500d853d29f0675b90655b7fdd032a4a7eee82a56e7ee3ef9949fe93ad5"; libraryHaskellDepends = [ base bytestring containers text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/ndmitchell/tagsoup#readme"; description = "Parsing and extracting information from (possibly malformed) HTML/XML documents"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "tagstream-conduit" = callPackage - ({ mkDerivation, attoparsec, base, blaze-builder, bytestring - , case-insensitive, conduit, conduit-extra, data-default, resourcet - , stdenv, text, transformers, xml-conduit - }: - mkDerivation { - pname = "tagstream-conduit"; - version = "0.5.5.3"; - sha256 = "b296e8f0ba18ae951b5bb3fc2d9d964954666df61ea9363d667f251af17134ab"; - libraryHaskellDepends = [ - attoparsec base blaze-builder bytestring case-insensitive conduit - conduit-extra data-default resourcet text transformers xml-conduit - ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/yihuang/tagstream-conduit"; - description = "streamlined html tag parser"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tao" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "tao"; version = "1.0.0"; @@ -32616,10 +39326,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/jship/tao#readme"; description = "Type-level assertion operators"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "tao-example" = callPackage - ({ mkDerivation, base, stdenv, tao }: + ({ mkDerivation, base, lib, tao }: mkDerivation { pname = "tao-example"; version = "1.0.0"; @@ -32629,18 +39339,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/jship/tao#readme"; description = "Example usage of the tao package"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "tar" = callPackage ({ mkDerivation, array, base, bytestring, containers, deepseq - , directory, filepath, stdenv, time + , directory, filepath, lib, time }: mkDerivation { pname = "tar"; - version = "0.5.1.0"; - sha256 = "c89d697b6472b739db50e61201251fcaf8a8f5b595b1d9a488d395d7d5ce4b68"; - revision = "1"; - editedCabalFile = "1lydbwsmccf2av0g61j07bx7r5mzbcfgwvmh0qwg3a91857x264x"; + version = "0.5.1.1"; + sha256 = "b384449f62b2b0aa3e6d2cb1004b8060b01f21ec93e7b63e7af6d8fad8a9f1de"; + revision = "3"; + editedCabalFile = "0qjhii1lhvqav3pnm6z5ly40d9gwp7p3y4g7k26bhxgy31bx1pll"; configureFlags = [ "-f-old-time" ]; libraryHaskellDepends = [ array base bytestring containers deepseq directory filepath time @@ -32648,16 +39358,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Reading, writing and manipulating \".tar\" archive files."; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tar-conduit" = callPackage ({ mkDerivation, base, bytestring, conduit, conduit-combinators - , directory, filepath, safe-exceptions, stdenv, text, unix + , directory, filepath, lib, safe-exceptions, text, unix }: mkDerivation { pname = "tar-conduit"; - version = "0.3.1"; - sha256 = "15aa9da39ca74a744d15ca590891cb4333295103aabc36f40852747384c68197"; + version = "0.3.2"; + sha256 = "004578db7088e7ad53e23f8a293d739314698f0ec421ffad7be101e13c1cf62d"; libraryHaskellDepends = [ base bytestring conduit conduit-combinators directory filepath safe-exceptions text unix @@ -32666,51 +39376,49 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/snoyberg/tar-conduit#readme"; description = "Extract and create tar files using conduit for streaming"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "tardis" = callPackage - ({ mkDerivation, base, mmorph, mtl, stdenv }: + ({ mkDerivation, base, lib, mmorph, mtl }: mkDerivation { pname = "tardis"; - version = "0.4.1.0"; - sha256 = "e672abadd75055c2372d722c98058f7f3403fcca18258565d1cdd8e0dc25a5d9"; - revision = "1"; - editedCabalFile = "1wp6vp90g19hv8r2l83ava7qxf0933gb7ni2zgyfa66vlvxvhibv"; + version = "0.4.3.0"; + sha256 = "5cf1331e6495d4c4ff48cc59348f26388bbf34d318df39601e3ae46a77bbd5b9"; libraryHaskellDepends = [ base mmorph mtl ]; doHaddock = false; doCheck = false; homepage = "https://github.com/DanBurton/tardis"; description = "Bidirectional state monad transformer"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tasty" = callPackage - ({ mkDerivation, ansi-terminal, async, base, clock, containers, mtl - , optparse-applicative, stdenv, stm, tagged, unbounded-delays, unix + ({ mkDerivation, ansi-terminal, base, clock, containers, lib, mtl + , optparse-applicative, stm, tagged, unbounded-delays, unix , wcwidth }: mkDerivation { pname = "tasty"; - version = "1.2"; - sha256 = "d6185e079ac9c12068582cc6f5b50d37a3d2d3ed1a05a4db454340350b5d8317"; + version = "1.4.1"; + sha256 = "2728f04ea61d45c665188577f0748a54ca6960200b33e4a3b10ae8dba4d4ae47"; libraryHaskellDepends = [ - ansi-terminal async base clock containers mtl optparse-applicative - stm tagged unbounded-delays unix wcwidth + ansi-terminal base clock containers mtl optparse-applicative stm + tagged unbounded-delays unix wcwidth ]; doHaddock = false; doCheck = false; homepage = "https://github.com/feuerbach/tasty"; description = "Modern and extensible testing framework"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "tasty-ant-xml" = callPackage ({ mkDerivation, base, containers, directory, filepath - , generic-deriving, ghc-prim, mtl, stdenv, stm, tagged, tasty + , generic-deriving, ghc-prim, lib, mtl, stm, tagged, tasty , transformers, xml }: mkDerivation { pname = "tasty-ant-xml"; - version = "1.1.5"; - sha256 = "62ccee94bc5c3d7c6ed99037788262d8d971eeac487fe43b06760f969430a5df"; + version = "1.1.8"; + sha256 = "a8efd431d14036e668ba15a376e1f9c7db55797e48c24e86cda0b1c421a53541"; libraryHaskellDepends = [ base containers directory filepath generic-deriving ghc-prim mtl stm tagged tasty transformers xml @@ -32719,29 +39427,43 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ocharles/tasty-ant-xml"; description = "Render tasty output to XML for Jenkins"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "tasty-bench" = callPackage + ({ mkDerivation, base, containers, deepseq, lib, tasty }: + mkDerivation { + pname = "tasty-bench"; + version = "0.2.5"; + sha256 = "edc5a39eacf267948ad34c6382a29c45c68171aa287a7c6684088074e70ed190"; + revision = "1"; + editedCabalFile = "0rcsdiwri52wng5dj30k3c5qrn8qfr14qs53cs1y99mbqfpzs02g"; + libraryHaskellDepends = [ base containers deepseq tasty ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/Bodigrim/tasty-bench"; + description = "Featherlight benchmark framework"; + license = lib.licenses.mit; }) {}; "tasty-dejafu" = callPackage - ({ mkDerivation, base, dejafu, random, stdenv, tagged, tasty }: + ({ mkDerivation, base, dejafu, lib, random, tagged, tasty }: mkDerivation { pname = "tasty-dejafu"; - version = "1.2.0.8"; - sha256 = "24b7cfb2c9d59b878b785ab3c261faa533801059effbfadc1feade2d781a296d"; + version = "2.0.0.7"; + sha256 = "b48863486a339c7ff7ab858272cbf3b7f4f378b6cbbc20c7f03beb7754c6ea4b"; libraryHaskellDepends = [ base dejafu random tagged tasty ]; doHaddock = false; doCheck = false; homepage = "https://github.com/barrucadu/dejafu"; description = "Deja Fu support for the Tasty test framework"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "tasty-discover" = callPackage - ({ mkDerivation, base, containers, directory, filepath, Glob - , stdenv + ({ mkDerivation, base, containers, directory, filepath, Glob, lib }: mkDerivation { pname = "tasty-discover"; - version = "4.2.1"; - sha256 = "be6c5b384614a592fb056e2e4f7806416aa37f114db77d0f8986938ba7cc1d3e"; + version = "4.2.2"; + sha256 = "64bcfd452735405f1ee18e092db37f8e20c5643c2182cd6d77ecd03aa8b425c9"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -32752,54 +39474,81 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; ]; doHaddock = false; doCheck = false; - homepage = "http://git.coop/lwm/tasty-discover"; + homepage = "https://github.com/haskell-works/tasty-discover"; description = "Test discovery for the tasty framework"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "tasty-expected-failure" = callPackage - ({ mkDerivation, base, stdenv, tagged, tasty }: + ({ mkDerivation, base, lib, tagged, tasty, unbounded-delays }: mkDerivation { pname = "tasty-expected-failure"; - version = "0.11.1.1"; - sha256 = "519a5c0d2ef9dd60355479f11ca47423133364f20ad3151f3c8b105313405ac4"; - revision = "1"; - editedCabalFile = "1b3fn7d3zwhhwm3gp8cmmsdcrvn9dhshd665xrx1mk6cmy4m8k16"; - libraryHaskellDepends = [ base tagged tasty ]; + version = "0.12.3"; + sha256 = "cb07cc5ca62a6fd673ef54ae70b4bc5f9c12662fe835bea1f38b944684ee8f7e"; + libraryHaskellDepends = [ base tagged tasty unbounded-delays ]; doHaddock = false; doCheck = false; homepage = "http://github.com/nomeata/tasty-expected-failure"; description = "Mark tasty tests as failure expected"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "tasty-focus" = callPackage + ({ mkDerivation, base, lib, tagged, tasty }: + mkDerivation { + pname = "tasty-focus"; + version = "1.0.1"; + sha256 = "a2ca4b2ebf71f692215a4798cdf3386bee9ee4e89638a0bd70b9865543f3da44"; + libraryHaskellDepends = [ base tagged tasty ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jonascarpay/tasty-focus#readme"; + description = "Simple focus mechanism for tasty"; + license = lib.licenses.bsd3; }) {}; "tasty-golden" = callPackage ({ mkDerivation, async, base, bytestring, containers, deepseq - , directory, filepath, mtl, optparse-applicative, process, stdenv - , tagged, tasty, temporary + , directory, filepath, lib, mtl, optparse-applicative, process + , tagged, tasty, temporary, text, unix-compat }: mkDerivation { pname = "tasty-golden"; - version = "2.3.2"; - sha256 = "04103d2a2fd6acc8f66b67d943060e88a2ea36b799502bf3e76c2726a15c714c"; + version = "2.3.4"; + sha256 = "f6f2bd6cd8ef1ca5b47ed08fb4a9cda4484e7fac0c30830f67a177f7f05653db"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ async base bytestring containers deepseq directory filepath mtl - optparse-applicative process tagged tasty temporary + optparse-applicative process tagged tasty temporary text + unix-compat ]; doHaddock = false; doCheck = false; homepage = "https://github.com/feuerbach/tasty-golden"; description = "Golden tests support for tasty"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "tasty-hedgehog" = callPackage + ({ mkDerivation, base, hedgehog, lib, tagged, tasty }: + mkDerivation { + pname = "tasty-hedgehog"; + version = "1.1.0.0"; + sha256 = "cbf90f2690aed7f0be5055b645533336b858bcdb0211a1b2809d8860d14fc433"; + libraryHaskellDepends = [ base hedgehog tagged tasty ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/qfpl/tasty-hedgehog"; + description = "Integration for tasty and hedgehog"; + license = lib.licenses.bsd3; }) {}; "tasty-hspec" = callPackage - ({ mkDerivation, base, hspec, hspec-core, QuickCheck, stdenv, tasty + ({ mkDerivation, base, hspec, hspec-core, lib, QuickCheck, tasty , tasty-quickcheck, tasty-smallcheck }: mkDerivation { pname = "tasty-hspec"; - version = "1.1.5.1"; - sha256 = "fe889ec0f7b3991c46a07d9ff9cf09608a73a18f434a7480d2a09c79e56f3345"; + version = "1.1.6"; + sha256 = "74cbd9f288f08a0d76ffea04a33aaf7915cff6a8a72eac3b7e3666a16514480b"; revision = "1"; - editedCabalFile = "18k4p273qnvfmk5cbm89rjqr0v03v0q22q7bbl7z3bxpwnnkmhqf"; + editedCabalFile = "0za15rg0szacxq9yfxxjzddr77ai7ng5827a20pj9dr5anjlnajj"; libraryHaskellDepends = [ base hspec hspec-core QuickCheck tasty tasty-quickcheck tasty-smallcheck @@ -32808,23 +39557,53 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mitchellwrosen/tasty-hspec"; description = "Hspec support for the Tasty test framework"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tasty-hunit" = callPackage - ({ mkDerivation, base, call-stack, stdenv, tasty }: + ({ mkDerivation, base, call-stack, lib, tasty }: mkDerivation { pname = "tasty-hunit"; - version = "0.10.0.1"; - sha256 = "8f903bef276ef503e4ef8b66a1e201c224588e426bc76f7581480f66d47b7048"; + version = "0.10.0.3"; + sha256 = "b7ef1912ece25b9396d2c69c31e63f82facc95edac8fc1abbf84e8c3c7ffe63f"; libraryHaskellDepends = [ base call-stack tasty ]; doHaddock = false; doCheck = false; homepage = "https://github.com/feuerbach/tasty"; description = "HUnit support for the Tasty test framework"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "tasty-hunit-compat" = callPackage + ({ mkDerivation, base, HUnit, lib, tasty, tasty-hunit }: + mkDerivation { + pname = "tasty-hunit-compat"; + version = "0.2.0.1"; + sha256 = "5548c833026be448f233e1d64cdbc7277aee0b81ba0df90070c7c720937add4d"; + libraryHaskellDepends = [ base HUnit tasty tasty-hunit ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/serokell/tasty-hunit-compat#readme"; + description = "Integration of `HUnit` with `tasty`"; + license = lib.licenses.mpl20; + }) {}; + "tasty-inspection-testing" = callPackage + ({ mkDerivation, base, ghc, inspection-testing, lib, tasty + , template-haskell + }: + mkDerivation { + pname = "tasty-inspection-testing"; + version = "0.1"; + sha256 = "1cfad60f4bb25d9889886e88a62a465f5dcedd6f96bc87b8a3e875cab2535ca1"; + libraryHaskellDepends = [ + base ghc inspection-testing tasty template-haskell + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/Bodigrim/tasty-inspection-testing"; + description = "Inspection testing support for tasty"; + license = lib.licenses.mit; }) {}; "tasty-kat" = callPackage - ({ mkDerivation, base, bytestring, stdenv, tasty }: + ({ mkDerivation, base, bytestring, lib, tasty }: mkDerivation { pname = "tasty-kat"; version = "0.0.3"; @@ -32834,24 +39613,41 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/vincenthz/tasty-kat"; description = "Known Answer Tests (KAT) framework for tasty"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "tasty-leancheck" = callPackage - ({ mkDerivation, base, leancheck, stdenv, tasty }: + ({ mkDerivation, base, leancheck, lib, tasty }: mkDerivation { pname = "tasty-leancheck"; - version = "0.0.1"; - sha256 = "2791628bf9698aee88c9e1b07ff2f910510664cdc44e2a30c805c2026888d31a"; + version = "0.0.2"; + sha256 = "bf5dab47f87d35554416f4c43d927844a9b81679a7ed099b8d8eef7d87ee0381"; libraryHaskellDepends = [ base leancheck tasty ]; doHaddock = false; doCheck = false; homepage = "https://github.com/rudymatela/tasty-leancheck#readme"; description = "LeanCheck support for the Tasty test framework"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "tasty-lua" = callPackage + ({ mkDerivation, base, bytestring, file-embed, hslua, lib, tasty + , text + }: + mkDerivation { + pname = "tasty-lua"; + version = "0.2.3.2"; + sha256 = "a360163c6d9b2db8698787c37422a603247d7ae3fcb7fb2828b13339611c4771"; + libraryHaskellDepends = [ + base bytestring file-embed hslua tasty text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/hslua/tasty-lua"; + description = "Write tests in Lua, integrate into tasty"; + license = lib.licenses.mit; }) {}; "tasty-program" = callPackage - ({ mkDerivation, base, deepseq, directory, filepath, process - , stdenv, tasty + ({ mkDerivation, base, deepseq, directory, filepath, lib, process + , tasty }: mkDerivation { pname = "tasty-program"; @@ -32864,18 +39660,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/jstolarek/tasty-program"; description = "Use tasty framework to test whether a program executes correctly"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tasty-quickcheck" = callPackage - ({ mkDerivation, base, optparse-applicative, QuickCheck, random - , stdenv, tagged, tasty + ({ mkDerivation, base, lib, optparse-applicative, QuickCheck + , random, tagged, tasty }: mkDerivation { pname = "tasty-quickcheck"; - version = "0.10"; - sha256 = "10fd30cef4a0c2cefb70afecef5adcee1f32f0fd287f108321458fbfd6d7266f"; - revision = "1"; - editedCabalFile = "1ndkkywcqgb2wj339vgckjv5915da5kd4ixlkaww9fsba3qsrnwx"; + version = "0.10.1.2"; + sha256 = "89601c0a670ff11dbef6294fd12842630a5bb2a7b126a22fffd8fe830a3a3144"; libraryHaskellDepends = [ base optparse-applicative QuickCheck random tagged tasty ]; @@ -32883,44 +39677,89 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/feuerbach/tasty"; description = "QuickCheck support for the Tasty test framework"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "tasty-rerun" = callPackage + ({ mkDerivation, base, containers, lib, mtl, optparse-applicative + , split, stm, tagged, tasty, transformers + }: + mkDerivation { + pname = "tasty-rerun"; + version = "1.1.18"; + sha256 = "fa74ac10bc23fd3e443362427236a9c543f92b6aaf2e1bc8e959ecd47fb98c69"; + revision = "1"; + editedCabalFile = "17w6kxdd9zw87lh1bmh24c7dp59df8dshygx88j2i5nhbn7lfn50"; + libraryHaskellDepends = [ + base containers mtl optparse-applicative split stm tagged tasty + transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/ocharles/tasty-rerun"; + description = "Rerun only tests which failed in a previous test run"; + license = lib.licenses.bsd3; }) {}; "tasty-silver" = callPackage ({ mkDerivation, ansi-terminal, async, base, bytestring, containers - , deepseq, directory, filepath, mtl, optparse-applicative, process - , process-extras, regex-tdfa, semigroups, stdenv, stm, tagged - , tasty, temporary, text + , deepseq, directory, filepath, lib, mtl, optparse-applicative + , process, process-extras, regex-tdfa, stm, tagged, tasty + , temporary, text }: mkDerivation { pname = "tasty-silver"; - version = "3.1.12"; - sha256 = "9eba31a2b0ca4857ed7cea15f6da7a6a9224419f1499e5f11b0cd68e3ef8cc68"; + version = "3.2.2"; + sha256 = "23fc68ae365280ea1197a8061bf8872644d23f13d0c3ee71092247a4ac35547f"; libraryHaskellDepends = [ ansi-terminal async base bytestring containers deepseq directory filepath mtl optparse-applicative process process-extras regex-tdfa - semigroups stm tagged tasty temporary text + stm tagged tasty temporary text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/phile314/tasty-silver"; description = "A fancy test runner, including support for golden tests"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "tasty-smallcheck" = callPackage - ({ mkDerivation, async, base, smallcheck, stdenv, tagged, tasty }: + ({ mkDerivation, base, lib, optparse-applicative, smallcheck + , tagged, tasty + }: mkDerivation { pname = "tasty-smallcheck"; - version = "0.8.1"; - sha256 = "314ba7acdb7793730e7677f553a72dd6a4a8f9a45ff3e931cd7d384affb3c6d8"; - libraryHaskellDepends = [ async base smallcheck tagged tasty ]; + version = "0.8.2"; + sha256 = "d5cbd7a2a7100e4afd3aaac01a8fa1b7814fb074d93aeff1b51240b687e54f33"; + revision = "1"; + editedCabalFile = "0033ha2w9rzc1rxpzh1dkfdrn256i5lvb41pqbdh2i6kli0v5vmh"; + libraryHaskellDepends = [ + base optparse-applicative smallcheck tagged tasty + ]; doHaddock = false; doCheck = false; - homepage = "http://documentup.com/feuerbach/tasty"; + homepage = "https://github.com/feuerbach/tasty"; description = "SmallCheck support for the Tasty test framework"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "tasty-test-reporter" = callPackage + ({ mkDerivation, ansi-terminal, base, concurrent-output, containers + , directory, filepath, junit-xml, lib, mtl, safe-exceptions, stm + , tagged, tasty, text + }: + mkDerivation { + pname = "tasty-test-reporter"; + version = "0.1.1.4"; + sha256 = "36ca893e8c53574d60b36906f7cb7d7d1bf24f7316acc5a2273e468b4ca25129"; + libraryHaskellDepends = [ + ansi-terminal base concurrent-output containers directory filepath + junit-xml mtl safe-exceptions stm tagged tasty text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/stoeffel/tasty-test-reporter#readme"; + description = "Producing JUnit-style XML test reports"; + license = lib.licenses.bsd3; }) {}; "tasty-th" = callPackage - ({ mkDerivation, base, haskell-src-exts, stdenv, tasty + ({ mkDerivation, base, haskell-src-exts, lib, tasty , template-haskell }: mkDerivation { @@ -32934,10 +39773,28 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/bennofs/tasty-th"; description = "Automatic tasty test case discovery using TH"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "tasty-wai" = callPackage + ({ mkDerivation, base, bytestring, http-types, HUnit, lib, tasty + , wai, wai-extra + }: + mkDerivation { + pname = "tasty-wai"; + version = "0.1.1.1"; + sha256 = "fec4c2f50233a1b9fcb4b40663dff1cdfe1b120eb88d8175b27a86fd5615d8ae"; + revision = "2"; + editedCabalFile = "13f0rmdyfd8wx9w9d6vj40akskq763gjj89p7dzy6zyaiyllgk64"; + libraryHaskellDepends = [ + base bytestring http-types HUnit tasty wai wai-extra + ]; + doHaddock = false; + doCheck = false; + description = "Test 'wai' endpoints via Test.Tasty"; + license = lib.licenses.bsd3; }) {}; "tce-conf" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "tce-conf"; version = "1.3"; @@ -32950,124 +39807,42 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://hub.darcs.net/dino/tce-conf"; description = "Very simple config file reading"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "tcp-streams" = callPackage - ({ mkDerivation, base, bytestring, data-default-class, io-streams - , network, pem, stdenv, tls, x509, x509-store, x509-system - }: - mkDerivation { - pname = "tcp-streams"; - version = "1.0.1.0"; - sha256 = "77d812e5db567875ca26c2682ceddf4bcf825d90dd10dcb171279bd7e96e4861"; - enableSeparateDataOutput = true; - libraryHaskellDepends = [ - base bytestring data-default-class io-streams network pem tls x509 - x509-store x509-system - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/didi-FP/tcp-streams"; - description = "One stop solution for tcp client and server with tls support"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "tcp-streams-openssl" = callPackage - ({ mkDerivation, base, bytestring, HsOpenSSL, HsOpenSSL-x509-system - , io-streams, network, stdenv, tcp-streams - }: - mkDerivation { - pname = "tcp-streams-openssl"; - version = "1.0.1.0"; - sha256 = "c3e7588ba7348fac87a9dcc531909f90bb3b4a1c01da9eb871a918d02b146afe"; - libraryHaskellDepends = [ - base bytestring HsOpenSSL HsOpenSSL-x509-system io-streams network - tcp-streams - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/didi-FP/tcp-streams"; - description = "Tcp streams using openssl for tls support"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tdigest" = callPackage - ({ mkDerivation, base, base-compat, binary, Cabal, cabal-doctest - , deepseq, reducers, semigroupoids, stdenv, transformers, vector - , vector-algorithms + ({ mkDerivation, base, base-compat, binary, deepseq, lib, reducers + , semigroupoids, transformers, vector, vector-algorithms }: mkDerivation { pname = "tdigest"; - version = "0.2.1"; - sha256 = "d46e38067c4d064f3c9c77219f570ba4e9dbbd7273a5edc4860610cde4afb84e"; - revision = "1"; - editedCabalFile = "1jrq22j9jbvx31pspwjvyb539gix7vfb8cinqkkb2abmr0jrhibn"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "0.2.1.1"; + sha256 = "a3998575ff5d180e6383d5bd5fc7c8e5fcfdb0c03e16f5f9089935a4d97173b7"; libraryHaskellDepends = [ base base-compat binary deepseq reducers semigroupoids transformers vector vector-algorithms ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/futurice/haskell-tdigest#readme"; + homepage = "https://github.com/phadej/haskell-tdigest#readme"; description = "On-line accumulation of rank-based statistics"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "telegram-bot-simple" = callPackage - ({ mkDerivation, aeson, aeson-pretty, base, bytestring, cron - , hashable, http-api-data, http-client, http-client-tls - , monad-control, mtl, pretty-show, profunctors, servant - , servant-client, split, stdenv, stm, template-haskell, text, time - , transformers, unordered-containers - }: - mkDerivation { - pname = "telegram-bot-simple"; - version = "0.2.0"; - sha256 = "8a8cc572880a792d1ed722bd0ac961892d79113c9fa1b2fbdf3019f98f904ea9"; - revision = "1"; - editedCabalFile = "1li6b3m9glhfg8agr9h0mrbxpr8zr46l57mzjfdqndm248ddbklv"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - aeson aeson-pretty base bytestring cron hashable http-api-data - http-client http-client-tls monad-control mtl pretty-show - profunctors servant servant-client split stm template-haskell text - time transformers unordered-containers - ]; - executableHaskellDepends = [ - aeson aeson-pretty base bytestring cron hashable http-api-data - http-client http-client-tls monad-control mtl pretty-show - profunctors servant servant-client split stm template-haskell text - time transformers unordered-containers - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/fizruk/telegram-bot-simple#readme"; - description = "Easy to use library for building Telegram bots"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "template-toolkit" = callPackage - ({ mkDerivation, aeson, base, binary, bytestring, containers - , directory, hashtables, mtl, parsec, pcre-utils - , regex-pcre-builtin, scientific, stdenv, text, time - , unordered-containers, uri-encode - }: + "template-haskell-compat-v0208" = callPackage + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { - pname = "template-toolkit"; - version = "0.1.1.0"; - sha256 = "e112d6896958d9d6eb7a4fc63b0b77a9a185d5452d0d4318c6a62121b17b1a5b"; - libraryHaskellDepends = [ - aeson base binary bytestring containers directory hashtables mtl - parsec pcre-utils regex-pcre-builtin scientific text time - unordered-containers uri-encode - ]; + pname = "template-haskell-compat-v0208"; + version = "0.1.6"; + sha256 = "88cf6ce110c6ae4940cb1a6960ca541d3b3b3c19e739de42263665e10d524be8"; + libraryHaskellDepends = [ base template-haskell ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/kobargh/template-toolkit#readme"; - description = "Template Toolkit implementation for Haskell"; - license = stdenv.lib.licenses.gpl3; + homepage = "https://github.com/nikita-volkov/template-haskell-compat-v0208"; + description = "A backwards compatibility layer for Template Haskell newer than 2.8"; + license = lib.licenses.mit; }) {}; "temporary" = callPackage - ({ mkDerivation, base, directory, exceptions, filepath, random - , stdenv, transformers, unix + ({ mkDerivation, base, directory, exceptions, filepath, lib, random + , transformers, unix }: mkDerivation { pname = "temporary"; @@ -33080,10 +39855,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/feuerbach/temporary"; description = "Portable temporary file and directory support"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "temporary-rc" = callPackage - ({ mkDerivation, base, directory, exceptions, filepath, stdenv + ({ mkDerivation, base, directory, exceptions, filepath, lib , transformers, unix }: mkDerivation { @@ -33097,11 +39872,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.github.com/feuerbach/temporary"; description = "Portable temporary file and directory support for Windows and Unix, based on code from Cabal"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "temporary-resourcet" = callPackage - ({ mkDerivation, base, directory, exceptions, filepath, resourcet - , stdenv, transformers, unix + ({ mkDerivation, base, directory, exceptions, filepath, lib + , resourcet, transformers, unix }: mkDerivation { pname = "temporary-resourcet"; @@ -33114,10 +39889,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.github.com/ttuegel/temporary-resourcet"; description = "Portable temporary files and directories with automatic deletion"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tensorflow-test" = callPackage - ({ mkDerivation, base, HUnit, stdenv, vector }: + ({ mkDerivation, base, HUnit, lib, vector }: mkDerivation { pname = "tensorflow-test"; version = "0.1.0.0"; @@ -33127,42 +39902,51 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/tensorflow/haskell#readme"; description = "Some common functions for test suites"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; }) {}; "tensors" = callPackage - ({ mkDerivation, base, reflection, singletons, stdenv, vector }: + ({ mkDerivation, base, deepseq, lib, vector }: mkDerivation { pname = "tensors"; - version = "0.1.2"; - sha256 = "67981055c33d5365eabc90b7b0058731da3a90b54f03cd96ac726db4ae9421a7"; - libraryHaskellDepends = [ base reflection singletons vector ]; + version = "0.1.5"; + sha256 = "54f132b7f2c2ee714654f038fc20dc21724e857011addfd3ce6a8fcb9d8b32a0"; + libraryHaskellDepends = [ base deepseq vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/leptonyu/tensors#readme"; description = "Tensor in Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "termbox" = callPackage - ({ mkDerivation, array, base, c2hs, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "termbox"; - version = "0.1.0"; - sha256 = "4aafbf6d583fd5641da9dcc06754953c6a86ac36a9c0fa73e3b9188f02bad4f3"; - revision = "1"; - editedCabalFile = "0qwab9ayd9b8gmcnvy6pbbp16vwnqdzji9qi71jmgvviayqdlly5"; + version = "0.3.0"; + sha256 = "504d2e54c6e48dc2e8f2350fa38d5bf481c3124e6cdb0b2dee866d4ebdd622ee"; isLibrary = true; isExecutable = true; - libraryHaskellDepends = [ array base ]; - libraryToolDepends = [ c2hs ]; - executableHaskellDepends = [ base ]; + libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mitchellwrosen/termbox"; description = "termbox bindings"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "terminal-progress-bar" = callPackage + ({ mkDerivation, base, deepseq, lib, terminal-size, text, time }: + mkDerivation { + pname = "terminal-progress-bar"; + version = "0.4.1"; + sha256 = "a61ca10c92cacc712dbbe28881dc23f41cc139760b7b2eef66bd0faa60ea5e24"; + libraryHaskellDepends = [ base deepseq terminal-size text time ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/roelvandijk/terminal-progress-bar"; + description = "A progress bar in the terminal"; + license = lib.licenses.bsd3; }) {}; "terminal-size" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "terminal-size"; version = "0.3.2.1"; @@ -33171,18 +39955,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Get terminal window height and width"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "test-framework" = callPackage ({ mkDerivation, ansi-terminal, ansi-wl-pprint, base, containers - , hostname, old-locale, random, regex-posix, stdenv, time, xml + , hostname, lib, old-locale, random, regex-posix, time, xml }: mkDerivation { pname = "test-framework"; version = "0.8.2.0"; sha256 = "f5aec7a15dbcb39e951bcf6502606fd99d751197b5510f41706899aa7e660ac2"; - revision = "1"; - editedCabalFile = "1af61pnf2vrkvs3hcqla5ddsrd0hd2pylv6l545yn3dcvl665rcc"; + revision = "6"; + editedCabalFile = "0wbq9wiaag69nsqxwijzhs5y1hb9kbpkp1x65dvx158cxp8i9w9r"; libraryHaskellDepends = [ ansi-terminal ansi-wl-pprint base containers hostname old-locale random regex-posix time xml @@ -33191,10 +39975,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://haskell.github.io/test-framework/"; description = "Framework for running and organising tests, with HUnit and QuickCheck support"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "test-framework-hunit" = callPackage - ({ mkDerivation, base, extensible-exceptions, HUnit, stdenv + ({ mkDerivation, base, extensible-exceptions, HUnit, lib , test-framework }: mkDerivation { @@ -33210,29 +39994,31 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://batterseapower.github.io/test-framework/"; description = "HUnit support for the test-framework package"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "test-framework-leancheck" = callPackage - ({ mkDerivation, base, leancheck, stdenv, test-framework }: + ({ mkDerivation, base, leancheck, lib, test-framework }: mkDerivation { pname = "test-framework-leancheck"; - version = "0.0.1"; - sha256 = "236c4c2e6b647c5eb84aeda94a949d50341999825d1a9372f195218137609f2f"; + version = "0.0.4"; + sha256 = "fbbf9f79f1bb8b1975abb23d05b9fd07a93105e837d8f9e94d45ca94520e4229"; libraryHaskellDepends = [ base leancheck test-framework ]; doHaddock = false; doCheck = false; homepage = "https://github.com/rudymatela/test-framework-leancheck#readme"; description = "LeanCheck support for test-framework"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "test-framework-quickcheck2" = callPackage - ({ mkDerivation, base, extensible-exceptions, QuickCheck, random - , stdenv, test-framework + ({ mkDerivation, base, extensible-exceptions, lib, QuickCheck + , random, test-framework }: mkDerivation { pname = "test-framework-quickcheck2"; version = "0.3.0.5"; sha256 = "c9f678d4ec30599172eb887031f0bce2012b532daeb713836bd912bff64eee59"; + revision = "3"; + editedCabalFile = "0mglqfimla4vvv80mg08aj76zf4993wmngqlirh05h8i9nmgv6lh"; libraryHaskellDepends = [ base extensible-exceptions QuickCheck random test-framework ]; @@ -33240,10 +40026,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://haskell.github.io/test-framework/"; description = "QuickCheck-2 support for the test-framework package"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "test-framework-smallcheck" = callPackage - ({ mkDerivation, base, smallcheck, stdenv, test-framework + ({ mkDerivation, base, lib, smallcheck, test-framework , transformers }: mkDerivation { @@ -33257,45 +40043,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/feuerbach/smallcheck"; description = "Support for SmallCheck tests in test-framework"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "test-framework-th" = callPackage - ({ mkDerivation, base, haskell-src-exts, language-haskell-extract - , regex-posix, stdenv, template-haskell, test-framework - }: - mkDerivation { - pname = "test-framework-th"; - version = "0.2.4"; - sha256 = "8b780d9e3edd8d91e24f72d9fa1f80420e52959428ad7c22d0694901a43f9c8a"; - libraryHaskellDepends = [ - base haskell-src-exts language-haskell-extract regex-posix - template-haskell test-framework - ]; - doHaddock = false; - doCheck = false; - homepage = "http://github.com/finnsson/test-generator"; - description = "Automagically generate the HUnit- and Quickcheck-bulk-code using Template Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "testing-feat" = callPackage - ({ mkDerivation, base, QuickCheck, size-based, stdenv - , testing-type-modifiers - }: + "test-fun" = callPackage + ({ mkDerivation, base, lib }: mkDerivation { - pname = "testing-feat"; - version = "1.1.0.0"; - sha256 = "1904d31ddce611474e8c836582efbca1ae7d1c7dc76083cf4300e8e0eeff58ec"; - libraryHaskellDepends = [ - base QuickCheck size-based testing-type-modifiers - ]; + pname = "test-fun"; + version = "0.1.0.0"; + sha256 = "cbe7af3bf11339247d2a48a4f057e1d0326a2e8ba4e7d05c4d162a12854ae1ea"; + libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/JonasDuregard/testing-feat"; - description = "Functional Enumeration of Algebraic Types"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/Lysxia/test-fun#readme"; + description = "Testable functions"; + license = lib.licenses.mit; }) {}; "testing-type-modifiers" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "testing-type-modifiers"; version = "0.1.0.1"; @@ -33304,47 +40068,44 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Data type modifiers for property based testing"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "texmath" = callPackage - ({ mkDerivation, base, containers, mtl, pandoc-types, parsec - , stdenv, syb, xml + ({ mkDerivation, base, containers, lib, mtl, pandoc-types, parsec + , split, syb, text, xml }: mkDerivation { pname = "texmath"; - version = "0.11.1.2"; - sha256 = "373f1281832c0f397976eec8f94117d2e298443ae2591f64a92e734631224cf1"; + version = "0.12.3"; + sha256 = "1d215c20f8b0be2779752f36ee5837ef1b5b37042716713335456bc8b57d0b52"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - base containers mtl pandoc-types parsec syb xml + base containers mtl pandoc-types parsec split syb text xml ]; doHaddock = false; doCheck = false; homepage = "http://github.com/jgm/texmath"; description = "Conversion between formats used to represent mathematics"; - license = stdenv.lib.licenses.gpl2; + license = lib.licenses.gpl2Only; }) {}; - "text" = callPackage - ({ mkDerivation, array, base, binary, bytestring, deepseq, ghc-prim - , integer-gmp, stdenv - }: + "text-ansi" = callPackage + ({ mkDerivation, base, lib, text }: mkDerivation { - pname = "text"; - version = "1.2.3.1"; - sha256 = "8360624d5d01f278da320eebd16fd5d6f366b7f876d0ad424041d58e5e1147a6"; - configureFlags = [ "-f-integer-simple" ]; - libraryHaskellDepends = [ - array base binary bytestring deepseq ghc-prim integer-gmp - ]; + pname = "text-ansi"; + version = "0.1.1"; + sha256 = "c69536dd2ec13525a96cb28f26e31faf19b680a86ba67603b4df58b4cfd399ed"; + revision = "1"; + editedCabalFile = "09s363h3lw4p8f73m7vw0d1cqnwmap9ndrfxd4qbzbra5xf58q38"; + libraryHaskellDepends = [ base text ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/haskell/text"; - description = "An efficient packed Unicode text type"; - license = stdenv.lib.licenses.bsd2; + homepage = "https://github.com/mitchellwrosen/text-ansi"; + description = "Text styling for ANSI terminals"; + license = lib.licenses.bsd3; }) {}; "text-binary" = callPackage - ({ mkDerivation, base, binary, stdenv, text }: + ({ mkDerivation, base, binary, lib, text }: mkDerivation { pname = "text-binary"; version = "0.2.1.1"; @@ -33354,34 +40115,33 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/kawu/text-binary"; description = "Binary instances for text types"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; }) {}; "text-builder" = callPackage - ({ mkDerivation, base, base-prelude, bytestring, deferred-folds - , semigroups, stdenv, text, transformers + ({ mkDerivation, base, bytestring, deferred-folds, lib, text + , transformers }: mkDerivation { pname = "text-builder"; - version = "0.6.4"; - sha256 = "ef3151775bf3061938a6bc94b79144a37a476aebe37f5a9f5a77b47433bc7968"; + version = "0.6.6.2"; + sha256 = "bc0194d38235b87341b3a270f8c1a749632ba9e4d173277979a0fec48f9846b2"; libraryHaskellDepends = [ - base base-prelude bytestring deferred-folds semigroups text - transformers + base bytestring deferred-folds text transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nikita-volkov/text-builder"; description = "An efficient strict text builder"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "text-conversions" = callPackage ({ mkDerivation, base, base16-bytestring, base64-bytestring - , bytestring, errors, stdenv, text + , bytestring, errors, lib, text }: mkDerivation { pname = "text-conversions"; - version = "0.3.0"; - sha256 = "1756be2f6b515fea9e00b383c00d1ee851f8b25ddbc2901dd6be27d9b6292c21"; + version = "0.3.1"; + sha256 = "b137843d3074248f28c5856a749bfd8e71d932b3afa040dbd3497684838d7d4d"; libraryHaskellDepends = [ base base16-bytestring base64-bytestring bytestring errors text ]; @@ -33389,18 +40149,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/cjdev/text-conversions#readme"; description = "Safe conversions between textual types"; - license = stdenv.lib.licenses.isc; + license = lib.licenses.isc; }) {}; "text-format" = callPackage ({ mkDerivation, array, base, double-conversion, ghc-prim - , integer-gmp, old-locale, stdenv, text, time, transformers + , integer-gmp, lib, old-locale, text, time, transformers }: mkDerivation { pname = "text-format"; version = "0.3.2"; sha256 = "326637b8ad8420a51c0531cb444e45e0029d68c5980a53d5ffdfa2297d47bae3"; - revision = "1"; - editedCabalFile = "155bddqabsxdfzdr7wl67qw9w777c2qkwxgjpx625875cvyhqkpa"; + revision = "2"; + editedCabalFile = "05findgw709h930wshaq514maxarjyjhsam6pkyzq83iz1yc2gra"; libraryHaskellDepends = [ array base double-conversion ghc-prim integer-gmp old-locale text time transformers @@ -33409,25 +40169,25 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/bos/text-format"; description = "Text formatting"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "text-icu" = callPackage - ({ mkDerivation, base, bytestring, deepseq, icu, stdenv, text }: + ({ mkDerivation, base, bytestring, deepseq, icu, lib, text }: mkDerivation { pname = "text-icu"; - version = "0.7.0.1"; - sha256 = "e2764c2749033706eed5b9fb3cda11177ad15cdf11912028f551eca39a2c7f78"; + version = "0.7.1.0"; + sha256 = "328e8453174f2c0194034642c26e14a4b8bb3698fe47d8bc4813664653632f69"; libraryHaskellDepends = [ base bytestring deepseq text ]; librarySystemDepends = [ icu ]; doHaddock = false; doCheck = false; homepage = "https://github.com/bos/text-icu"; description = "Bindings to the ICU library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) icu;}; "text-latin1" = callPackage ({ mkDerivation, base, bytestring, case-insensitive, data-checked - , hashable, semigroups, stdenv, text + , hashable, lib, semigroups, text }: mkDerivation { pname = "text-latin1"; @@ -33441,11 +40201,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mvv/text-latin1"; description = "Latin-1 (including ASCII) utility functions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "text-ldap" = callPackage ({ mkDerivation, attoparsec, base, bytestring, containers, dlist - , memory, stdenv, transformers + , lib, memory, transformers }: mkDerivation { pname = "text-ldap"; @@ -33460,24 +40220,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Parser and Printer for LDAP text data stream"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "text-manipulate" = callPackage - ({ mkDerivation, base, stdenv, text }: + ({ mkDerivation, base, lib, text }: mkDerivation { pname = "text-manipulate"; - version = "0.2.0.1"; - sha256 = "e0e9c71d9b1cfb7d3bca3d0a500d939b3efc6684515c0d7bd685503aa4f49d2f"; + version = "0.3.0.0"; + sha256 = "0a8484b903cff637a81ca527d0a2a27b3fdae9c53cac93f43513e451d1b8bf5e"; libraryHaskellDepends = [ base text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/brendanhay/text-manipulate"; description = "Case conversion, word boundary manipulation, and textual subjugation"; - license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; + license = lib.licenses.mpl20; }) {}; "text-metrics" = callPackage - ({ mkDerivation, base, containers, stdenv, text, vector }: + ({ mkDerivation, base, containers, lib, text, vector }: mkDerivation { pname = "text-metrics"; version = "0.3.0"; @@ -33489,10 +40248,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mrkkrp/text-metrics"; description = "Calculate various string metrics efficiently"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "text-postgresql" = callPackage - ({ mkDerivation, base, dlist, stdenv, transformers + ({ mkDerivation, base, dlist, lib, transformers , transformers-compat }: mkDerivation { @@ -33506,16 +40265,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://khibino.github.io/haskell-relational-record/"; description = "Parser and Printer of PostgreSQL extended types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "text-printer" = callPackage - ({ mkDerivation, base, bytestring, pretty, semigroups, stdenv, text + ({ mkDerivation, base, bytestring, lib, pretty, semigroups, text , text-latin1 }: mkDerivation { pname = "text-printer"; - version = "0.5"; - sha256 = "8f0c01a6a15b4314c2d47ab5f0772d176ec38f1c1fe190b9fa7db5149a6c4a0b"; + version = "0.5.0.1"; + sha256 = "58a7680fc75a058ef8a03a6d519d5266f204bae2eb30021663de135a1c31b518"; libraryHaskellDepends = [ base bytestring pretty semigroups text text-latin1 ]; @@ -33523,11 +40282,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mvv/text-printer"; description = "Abstract interface for text builders/printers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "text-regex-replace" = callPackage + ({ mkDerivation, attoparsec, base, lib, text, text-icu }: + mkDerivation { + pname = "text-regex-replace"; + version = "0.1.1.4"; + sha256 = "4b3f09638a2e9cfbc090c9b822a505d1de6452cf1c530e5d44aa919a2dffc7a6"; + libraryHaskellDepends = [ attoparsec base text text-icu ]; + doHaddock = false; + doCheck = false; + description = "Easy replacement when using text-icu regexes"; + license = lib.licenses.asl20; }) {}; "text-region" = callPackage ({ mkDerivation, aeson, base, base-unicode-symbols, bytestring - , groups, lens, stdenv, text + , groups, lens, lib, text }: mkDerivation { pname = "text-region"; @@ -33542,55 +40313,94 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mvoidex/text-region"; description = "Marking text regions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "text-short" = callPackage ({ mkDerivation, base, binary, bytestring, deepseq, ghc-prim - , hashable, stdenv, text + , hashable, lib, text }: mkDerivation { pname = "text-short"; - version = "0.1.2"; - sha256 = "b3f2b867d14c7c2586ea580028606b6662293ad080726d5241def937e5e31167"; - revision = "1"; - editedCabalFile = "00w77idkh44m88vivkqsys0y1bbxrflh06yq66liq0wgjhhzdppj"; + version = "0.1.3"; + sha256 = "bf5b9fedb7d0301e8fdf33e3223d10ca940e9e72c18bac135be80b6016edd977"; + revision = "3"; + editedCabalFile = "1wjy98ihhipzr34b310sgjjq3cc12aydhckbrgr21kxkzwglm4nv"; libraryHaskellDepends = [ base binary bytestring deepseq ghc-prim hashable text ]; doHaddock = false; doCheck = false; description = "Memory-efficient representation of Unicode text strings"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "text-show" = callPackage ({ mkDerivation, array, base, base-compat-batteries, bifunctors - , bytestring, bytestring-builder, containers, contravariant - , generic-deriving, ghc-boot-th, ghc-prim, integer-gmp, nats - , semigroups, stdenv, tagged, template-haskell, text - , th-abstraction, th-lift, transformers, transformers-compat, void + , bytestring, bytestring-builder, containers, generic-deriving + , ghc-boot-th, ghc-prim, integer-gmp, lib, template-haskell, text + , th-abstraction, th-lift, transformers, transformers-compat }: mkDerivation { pname = "text-show"; - version = "3.7.5"; - sha256 = "39381f23edd5388477ad61f1bdb21962c1abc5e206342ae581d263c3464cc8af"; + version = "3.9"; + sha256 = "20b99af09d0b8fa14f7ded8cf960cd7f2f4029747c7c195ef32cc147cfe146b2"; revision = "1"; - editedCabalFile = "1v8czpi9mn54850k0pilqh1f3yfr5n5vykmg5k57wmrdpx25vkws"; + editedCabalFile = "1jwsp8g7c7wywxvhb7ns7xw0h7mbr33c3kyhba8ybw0rn43ynjki"; libraryHaskellDepends = [ array base base-compat-batteries bifunctors bytestring - bytestring-builder containers contravariant generic-deriving - ghc-boot-th ghc-prim integer-gmp nats semigroups tagged - template-haskell text th-abstraction th-lift transformers - transformers-compat void + bytestring-builder containers generic-deriving ghc-boot-th ghc-prim + integer-gmp template-haskell text th-abstraction th-lift + transformers transformers-compat ]; doHaddock = false; doCheck = false; homepage = "https://github.com/RyanGlScott/text-show"; description = "Efficient conversion of values into Text"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "text-show-instances" = callPackage + ({ mkDerivation, base, base-compat-batteries, bifunctors, binary + , containers, directory, ghc-boot-th, haskeline, hpc, lib + , old-locale, old-time, pretty, random, semigroups, tagged + , template-haskell, terminfo, text, text-short, text-show, time + , transformers, transformers-compat, unix, unordered-containers + , vector, xhtml + }: + mkDerivation { + pname = "text-show-instances"; + version = "3.8.4"; + sha256 = "5848dcda0f1ea25a84b10cf91dd224938164e1987e7f9b752ae7132c377159ef"; + revision = "2"; + editedCabalFile = "1k5q21j0276jafyy4icgncz45r5gab2mj8964xayhh548rzj5cm6"; + libraryHaskellDepends = [ + base base-compat-batteries bifunctors binary containers directory + ghc-boot-th haskeline hpc old-locale old-time pretty random + semigroups tagged template-haskell terminfo text text-short + text-show time transformers transformers-compat unix + unordered-containers vector xhtml + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/RyanGlScott/text-show-instances"; + description = "Additional instances for text-show"; + license = lib.licenses.bsd3; + }) {}; + "text-zipper" = callPackage + ({ mkDerivation, base, deepseq, lib, text, vector }: + mkDerivation { + pname = "text-zipper"; + version = "0.11"; + sha256 = "da93821a05663315e9f4f613abb14e15769544882d401e2c2b69bf91babf811e"; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ base deepseq text vector ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jtdaugherty/text-zipper/"; + description = "A text editor zipper library"; + license = lib.licenses.bsd3; }) {}; "textlocal" = callPackage ({ mkDerivation, aeson, base, bytestring, http-client - , http-client-tls, http-conduit, stdenv, text, unix-time + , http-client-tls, http-conduit, lib, text, unix-time }: mkDerivation { pname = "textlocal"; @@ -33604,10 +40414,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/just-chow/textlocal"; description = "Haskell wrapper for textlocal SMS gateway"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tf-random" = callPackage - ({ mkDerivation, base, primitive, random, stdenv, time }: + ({ mkDerivation, base, lib, primitive, random, time }: mkDerivation { pname = "tf-random"; version = "0.5"; @@ -33616,29 +40426,30 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "High-quality splittable pseudorandom number generator"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tfp" = callPackage - ({ mkDerivation, base, stdenv, utility-ht }: + ({ mkDerivation, base, lib, utility-ht }: mkDerivation { pname = "tfp"; - version = "1.0.1.1"; - sha256 = "71b494920377cfd1c58f220e5d8862c1f2c0d2b1ce529352f2fde20428a96ce2"; + version = "1.0.2"; + sha256 = "8ede80c2df6a33c338f01a3a9fcc54cfc740410143d16b96028748a69901350b"; libraryHaskellDepends = [ base utility-ht ]; doHaddock = false; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Type_arithmetic"; description = "Type-level integers, booleans, lists using type families"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "th-abstraction" = callPackage - ({ mkDerivation, base, containers, ghc-prim, stdenv - , template-haskell + ({ mkDerivation, base, containers, ghc-prim, lib, template-haskell }: mkDerivation { pname = "th-abstraction"; - version = "0.2.10.0"; - sha256 = "c9dbffcaa4ed04f257427e61da135797190b572d4e37662f7821844cbd2114af"; + version = "0.4.2.0"; + sha256 = "ea06b2cda25fc4b52dac48cc23e5a756f997df8985ecaee5a554202508a11c40"; + revision = "1"; + editedCabalFile = "1yc17r29vkwi4qzbrxy1d3gra87hk3ghy1jzfmrl2q8zjc0v59vb"; libraryHaskellDepends = [ base containers ghc-prim template-haskell ]; @@ -33646,55 +40457,109 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/glguy/th-abstraction"; description = "Nicer interface for reified information about data types"; - license = stdenv.lib.licenses.isc; + license = lib.licenses.isc; + }) {}; + "th-bang-compat" = callPackage + ({ mkDerivation, base, lib, template-haskell }: + mkDerivation { + pname = "th-bang-compat"; + version = "0.0.1.0"; + sha256 = "3fd877c05cea39db7a1427ecfb440aa06b91da9da30a332c5181043471bcbf5c"; + libraryHaskellDepends = [ base template-haskell ]; + doHaddock = false; + doCheck = false; + description = "Compatibility for bang-type template"; + license = lib.licenses.bsd3; + }) {}; + "th-compat" = callPackage + ({ mkDerivation, base, lib, template-haskell }: + mkDerivation { + pname = "th-compat"; + version = "0.1.2"; + sha256 = "2bc45d0199de3dc65ebc9b71251799f5238869dbc6a66bdf0c06c7e23d603801"; + libraryHaskellDepends = [ base template-haskell ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskell-compat/th-compat"; + description = "Backward- (and forward-)compatible Quote and Code types"; + license = lib.licenses.bsd3; + }) {}; + "th-constraint-compat" = callPackage + ({ mkDerivation, base, containers, lib, template-haskell }: + mkDerivation { + pname = "th-constraint-compat"; + version = "0.0.1.0"; + sha256 = "ec8f6d1fec59aad0fc1d023316ddc60269fe4219b8a90720a0cae747842ba3f3"; + libraryHaskellDepends = [ base containers template-haskell ]; + doHaddock = false; + doCheck = false; + description = "Compatibility for type constraint template"; + license = lib.licenses.bsd3; }) {}; "th-data-compat" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { pname = "th-data-compat"; - version = "0.0.2.7"; - sha256 = "13aaff2410e39e518f6de74a5bdd20de0e0139fc4af2c344e7c282cf63fa4e7a"; + version = "0.1.0.0"; + sha256 = "5d5213f9950e035b49541f6e4d37449ad2f6dfc127d8deb507c6badf576ba50d"; libraryHaskellDepends = [ base template-haskell ]; doHaddock = false; doCheck = false; description = "Compatibility for data definition template of TH"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "th-desugar" = callPackage - ({ mkDerivation, base, containers, mtl, stdenv, syb - , template-haskell, th-expand-syns, th-lift, th-orphans + ({ mkDerivation, base, containers, fail, ghc-prim, lib, mtl + , ordered-containers, semigroups, syb, template-haskell + , th-abstraction, th-lift, th-orphans, transformers-compat }: mkDerivation { pname = "th-desugar"; - version = "1.9"; - sha256 = "f14a7a854df55abb3bbca5ef0ec202ed4d7e1631a5fb51767d360dc1b604afef"; + version = "1.11"; + sha256 = "14e29e035b96d7c35bb1503426736e610465f75939bd89df1386f2a0c26ce82a"; libraryHaskellDepends = [ - base containers mtl syb template-haskell th-expand-syns th-lift - th-orphans + base containers fail ghc-prim mtl ordered-containers semigroups syb + template-haskell th-abstraction th-lift th-orphans + transformers-compat ]; doHaddock = false; doCheck = false; homepage = "https://github.com/goldfirere/th-desugar"; description = "Functions to desugar Template Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "th-env" = callPackage + ({ mkDerivation, base, lib, template-haskell }: + mkDerivation { + pname = "th-env"; + version = "0.1.0.2"; + sha256 = "c0d29be2104dd0964f534637841b8ceb665d594b02318062aa4a245ccb353a8f"; + libraryHaskellDepends = [ base template-haskell ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/dzhus/th-env#readme"; + description = "Template Haskell splice that expands to an environment variable"; + license = lib.licenses.bsd3; }) {}; "th-expand-syns" = callPackage - ({ mkDerivation, base, containers, stdenv, syb, template-haskell }: + ({ mkDerivation, base, containers, lib, syb, template-haskell + , th-abstraction + }: mkDerivation { pname = "th-expand-syns"; - version = "0.4.4.0"; - sha256 = "cc0f52d1364ace9ba56f51afd9106a5fe01ed3f5ae45c958c1b0f83be0a6f906"; - revision = "1"; - editedCabalFile = "1zbdg3hrqv7rzlsrw4a2vjr3g4nzny32wvjcpxamlvx77b1jvsw9"; - libraryHaskellDepends = [ base containers syb template-haskell ]; + version = "0.4.8.0"; + sha256 = "5113610c59a17a4e554ce0ffd3a43feaa761afd1e4b3ec72049bc5ba5cf780d7"; + libraryHaskellDepends = [ + base containers syb template-haskell th-abstraction + ]; doHaddock = false; doCheck = false; homepage = "https://github.com/DanielSchuessler/th-expand-syns"; description = "Expands type synonyms in Template Haskell ASTs"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "th-extras" = callPackage - ({ mkDerivation, base, stdenv, syb, template-haskell }: + ({ mkDerivation, base, lib, syb, template-haskell }: mkDerivation { pname = "th-extras"; version = "0.0.0.4"; @@ -33704,79 +40569,96 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mokus0/th-extras"; description = "A grab bag of functions for use with Template Haskell"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; "th-lift" = callPackage - ({ mkDerivation, base, ghc-prim, stdenv, template-haskell + ({ mkDerivation, base, ghc-prim, lib, template-haskell , th-abstraction }: mkDerivation { pname = "th-lift"; - version = "0.7.11"; - sha256 = "d53cd1479d3cf35c513095f3954eee539e73c55266cec5f1fa0a82d53f30238c"; + version = "0.8.2"; + sha256 = "3a5927037a10ae63e605c02228c4027c32b7bab1985ae7b5379e6363b3cd5ce4"; + revision = "1"; + editedCabalFile = "1l8fsxbxfsgcy6qxlgn6qxwhiqwwmmaj2vb1gbrjyb905gb3lpwm"; libraryHaskellDepends = [ base ghc-prim template-haskell th-abstraction ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/mboes/th-lift"; + homepage = "http://github.com/RyanGlScott/th-lift"; description = "Derive Template Haskell's Lift class for datatypes"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "th-lift-instances" = callPackage - ({ mkDerivation, base, bytestring, containers, stdenv - , template-haskell, text, th-lift, vector + ({ mkDerivation, base, bytestring, containers, lib + , template-haskell, text, th-lift, transformers, vector }: mkDerivation { pname = "th-lift-instances"; - version = "0.1.11"; - sha256 = "1da46afabdc73c86f279a0557d5a8f9af1296f9f6043264ba354b1c9cc65a6b8"; + version = "0.1.18"; + sha256 = "bee57c7522e0fefdf8719d4492312883d1a168c6ec4b17befb666fe7f40fdb26"; libraryHaskellDepends = [ - base bytestring containers template-haskell text th-lift vector + base bytestring containers template-haskell text th-lift + transformers vector ]; doHaddock = false; doCheck = false; homepage = "http://github.com/bennofs/th-lift-instances/"; description = "Lift instances for template-haskell for common data types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "th-nowq" = callPackage + ({ mkDerivation, base, lib, template-haskell, time }: + mkDerivation { + pname = "th-nowq"; + version = "0.1.0.5"; + sha256 = "91f127417ed263a13c25df442fc24041d366dbc607e2d83fca57caddaa231124"; + libraryHaskellDepends = [ base template-haskell time ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/dzhus/th-nowq#readme"; + description = "Template Haskell splice that expands to current time"; + license = lib.licenses.bsd3; }) {}; "th-orphans" = callPackage - ({ mkDerivation, base, mtl, stdenv, template-haskell, th-lift - , th-lift-instances, th-reify-many + ({ mkDerivation, base, lib, mtl, template-haskell, th-compat + , th-lift, th-lift-instances, th-reify-many }: mkDerivation { pname = "th-orphans"; - version = "0.13.6"; - sha256 = "7745e6b93a73cbc0a6aa0da0a7b7377f0be4fffb4fd311e5502de199ec1dd469"; + version = "0.13.11"; + sha256 = "6e4a5b6e24a615cb6eb0849382ff04204757be36b82fdc0431ccd506a5f6f5d4"; libraryHaskellDepends = [ - base mtl template-haskell th-lift th-lift-instances th-reify-many + base mtl template-haskell th-compat th-lift th-lift-instances + th-reify-many ]; doHaddock = false; doCheck = false; description = "Orphan instances for TH datatypes"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "th-printf" = callPackage - ({ mkDerivation, base, charset, containers, microlens-platform, mtl - , parsec, semigroups, stdenv, template-haskell, th-lift - , transformers + ({ mkDerivation, base, charset, containers, dlist + , integer-logarithms, lib, microlens-platform, mtl, parsec + , semigroups, template-haskell, text, th-lift, transformers }: mkDerivation { pname = "th-printf"; - version = "0.6.0"; - sha256 = "c258ed7852cbafa6c4b7142343d6294513081a7b7ddeeb89c089b082fa5f0ed7"; + version = "0.7"; + sha256 = "ea2bc2ab17961188fcf69221cbfab0b420dbe1fddcef072bb47789ca34e034b9"; libraryHaskellDepends = [ - base charset containers microlens-platform mtl parsec semigroups - template-haskell th-lift transformers + base charset containers dlist integer-logarithms microlens-platform + mtl parsec semigroups template-haskell text th-lift transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/pikajude/th-printf#readme"; description = "Quasiquoters for printf"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "th-reify-compat" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { pname = "th-reify-compat"; version = "0.0.1.5"; @@ -33786,16 +40668,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/khibino/haskell-th-reify-compat/"; description = "Compatibility for the result type of TH reify"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "th-reify-many" = callPackage - ({ mkDerivation, base, containers, mtl, safe, stdenv - , template-haskell, th-expand-syns + ({ mkDerivation, base, containers, lib, mtl, safe, template-haskell + , th-expand-syns }: mkDerivation { pname = "th-reify-many"; - version = "0.1.8"; - sha256 = "cecaae187df911de515d08929e1394d6d6f7ce129795be8189a6b10d3734fe43"; + version = "0.1.9"; + sha256 = "f889dd029d5ab191ace99fe595f363c60314d536e61c8c58f6167f1a9d29ae43"; libraryHaskellDepends = [ base containers mtl safe template-haskell th-expand-syns ]; @@ -33803,10 +40685,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/mgsloan/th-reify-many"; description = "Recurseively reify template haskell datatype info"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "th-strict-compat" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { pname = "th-strict-compat"; version = "0.1.0.1"; @@ -33816,63 +40698,117 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://gitlab.com/igrep/th-strict-compat"; description = "Compatibility shim for Bang and Strict in Template Haskell"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; + }) {}; + "th-test-utils" = callPackage + ({ mkDerivation, base, lib, template-haskell, th-orphans + , transformers + }: + mkDerivation { + pname = "th-test-utils"; + version = "1.1.0"; + sha256 = "937f1e325742bdff1da8f2597551005029d6d57812e93b94538050c7d3f54889"; + revision = "2"; + editedCabalFile = "1jwx31jqglfcy6ylj4520kqfp918lnv6m13flx2qvhfwbd88xwcv"; + libraryHaskellDepends = [ + base template-haskell th-orphans transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/LeapYear/th-test-utils#readme"; + description = "Utility functions for testing Template Haskell code"; + license = lib.licenses.bsd3; }) {}; "th-utilities" = callPackage ({ mkDerivation, base, bytestring, containers, directory, filepath - , primitive, stdenv, syb, template-haskell, text, th-orphans + , lib, primitive, syb, template-haskell, text, th-abstraction + , th-orphans }: mkDerivation { pname = "th-utilities"; - version = "0.2.1.0"; - sha256 = "cb597eb207cdae81c24abcae106b43e6479038b6bc5e76c8861c9134c8fe83cd"; + version = "0.2.4.3"; + sha256 = "89c5aa07e8cc046519dc26f67d8eb1242125e85baf3e86b9b92cfe73fbb03bcf"; libraryHaskellDepends = [ base bytestring containers directory filepath primitive syb - template-haskell text th-orphans + template-haskell text th-abstraction th-orphans ]; doHaddock = false; doCheck = false; homepage = "https://github.com/fpco/th-utilities#readme"; description = "Collection of useful functions for use with Template Haskell"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "these" = callPackage - ({ mkDerivation, aeson, base, bifunctors, binary, containers - , data-default-class, deepseq, hashable, keys, mtl, profunctors - , QuickCheck, semigroupoids, stdenv, transformers - , transformers-compat, unordered-containers, vector - , vector-instances - }: + ({ mkDerivation, assoc, base, binary, deepseq, hashable, lib }: mkDerivation { pname = "these"; - version = "0.7.5"; - sha256 = "dbac2412ad609d2ccd180722ac73a3f0fb2df300460a78d687660135efec35fb"; - libraryHaskellDepends = [ - aeson base bifunctors binary containers data-default-class deepseq - hashable keys mtl profunctors QuickCheck semigroupoids transformers - transformers-compat unordered-containers vector vector-instances - ]; + version = "1.1.1.1"; + sha256 = "d798c9f56e17def441e8f51e54cc11afdb3e76c6a9d1e9ee154e9a78da0bf508"; + revision = "1"; + editedCabalFile = "1bzi28jvaxil9rc6z1hkf87pfjsa3r5gfc9n0ixffnnv519cd0g9"; + libraryHaskellDepends = [ assoc base binary deepseq hashable ]; doHaddock = false; doCheck = false; homepage = "https://github.com/isomorphism/these"; - description = "An either-or-both data type & a generalized 'zip with padding' typeclass"; - license = stdenv.lib.licenses.bsd3; + description = "An either-or-both data type"; + license = lib.licenses.bsd3; + }) {}; + "these-lens" = callPackage + ({ mkDerivation, base, lens, lib, these }: + mkDerivation { + pname = "these-lens"; + version = "1.0.1.2"; + sha256 = "e606d192fb8dafe1e4117a2c9d4a1b4217a95fd198d3b55a5ddccf45e49173ec"; + libraryHaskellDepends = [ base lens these ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskellari/these"; + description = "Lenses for These"; + license = lib.licenses.bsd3; + }) {}; + "these-optics" = callPackage + ({ mkDerivation, base, lib, optics-core, these }: + mkDerivation { + pname = "these-optics"; + version = "1.0.1.2"; + sha256 = "ed936a7dbc7ebf7c836feb56f638fcb389bfc50130632de527c92105c4d85d1a"; + libraryHaskellDepends = [ base optics-core these ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/haskellari/these"; + description = "Optics for These"; + license = lib.licenses.bsd3; + }) {}; + "these-skinny" = callPackage + ({ mkDerivation, base, deepseq, lib }: + mkDerivation { + pname = "these-skinny"; + version = "0.7.4"; + sha256 = "79dae5785ca26768925e31f020ef2259ad7df46608df54bf073ea51c49729d42"; + revision = "2"; + editedCabalFile = "0q1izcz4kxrnl7sh0sxamxxq02mkxww88vr6v04pwj8alyhkd4z2"; + libraryHaskellDepends = [ base deepseq ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/chessai/these-skinny"; + description = "A fork of the 'these' package without the dependency bloat"; + license = lib.licenses.bsd3; }) {}; "thread-hierarchy" = callPackage - ({ mkDerivation, base, containers, stdenv, stm }: + ({ mkDerivation, base, containers, lib, stm }: mkDerivation { pname = "thread-hierarchy"; - version = "0.3.0.1"; - sha256 = "8181448452c759b660f6d7c8775fd99479ccc382cd291460903b15574e5d5c34"; + version = "0.3.0.2"; + sha256 = "f0f6347d2d403a9037a9bfe61c5f60ee0dcc0ae52eae25315a8f38de8f0e1dae"; libraryHaskellDepends = [ base containers stm ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nshimaza/thread-hierarchy#readme"; - description = "Simple Haskel thread management in hierarchical manner"; - license = stdenv.lib.licenses.mit; + description = "Simple Haskell thread management in hierarchical manner"; + license = lib.licenses.mit; }) {}; "thread-local-storage" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "thread-local-storage"; version = "0.2"; @@ -33882,10 +40818,27 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/rrnewton/thread-local-storage"; description = "Several options for thread-local-storage (TLS) in Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "thread-supervisor" = callPackage + ({ mkDerivation, base, clock, containers, data-default, lib + , unliftio + }: + mkDerivation { + pname = "thread-supervisor"; + version = "0.2.0.0"; + sha256 = "db5e015dfd88c227b8a3b905af0e17385c59327c523bf6083cba0328989982cc"; + libraryHaskellDepends = [ + base clock containers data-default unliftio + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/nshimaza/thread-supervisor#readme"; + description = "A simplified implementation of Erlang/OTP like supervisor over thread"; + license = lib.licenses.mit; }) {}; "threads" = callPackage - ({ mkDerivation, base, Cabal, stdenv, stm }: + ({ mkDerivation, base, Cabal, lib, stm }: mkDerivation { pname = "threads"; version = "0.5.1.6"; @@ -33896,19 +40849,19 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/basvandijk/threads"; description = "Fork threads and wait for their result"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "threepenny-gui" = callPackage ({ mkDerivation, aeson, async, base, bytestring, containers , data-default, deepseq, exceptions, file-embed, filepath, hashable - , safe, snap-core, snap-server, stdenv, stm, template-haskell, text + , lib, safe, snap-core, snap-server, stm, template-haskell, text , transformers, unordered-containers, vault, vector, websockets , websockets-snap }: mkDerivation { pname = "threepenny-gui"; - version = "0.8.3.0"; - sha256 = "c661b206987d6c85821e6b5206c563e3182138dfddda62cda454b8cd34536a9c"; + version = "0.9.1.0"; + sha256 = "a25f47ebc9902955eccf26a1b471f1a15a83215a1e19de1ce6d63a9c949b5203"; isLibrary = true; isExecutable = true; enableSeparateDataOutput = true; @@ -33922,10 +40875,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://wiki.haskell.org/Threepenny-gui"; description = "GUI framework that uses the web browser as a display"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "throttle-io-stream" = callPackage - ({ mkDerivation, async, base, clock, stdenv, stm, stm-chans }: + ({ mkDerivation, async, base, clock, lib, stm, stm-chans }: mkDerivation { pname = "throttle-io-stream"; version = "0.2.0.1"; @@ -33935,10 +40888,25 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mtesseract/throttle-io-stream#readme"; description = "Throttler between arbitrary IO producer and consumer functions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "through-text" = callPackage + ({ mkDerivation, base, bytestring, case-insensitive, lib, text }: + mkDerivation { + pname = "through-text"; + version = "0.1.0.0"; + sha256 = "933225da128906e61865ccd1da73463781b890d742cbb38f52524d94ac19b4cd"; + revision = "6"; + editedCabalFile = "12mqlm77g0fymx3xwlkf6s9nqivcf78szhrzkvssi7lq1lqq9lbc"; + libraryHaskellDepends = [ base bytestring case-insensitive text ]; + doHaddock = false; + doCheck = false; + homepage = "https://www.github.com/bergmark/through-text"; + description = "Convert textual types through Text without needing O(n^2) instances"; + license = lib.licenses.bsd3; }) {}; "throwable-exceptions" = callPackage - ({ mkDerivation, base, safe-exceptions, stdenv, template-haskell }: + ({ mkDerivation, base, lib, safe-exceptions, template-haskell }: mkDerivation { pname = "throwable-exceptions"; version = "0.1.0.9"; @@ -33948,12 +40916,12 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/aiya000/hs-throwable-exceptions#README.md"; description = "throwable-exceptions gives the easy way to throw exceptions"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "thyme" = callPackage ({ mkDerivation, aeson, attoparsec, base, bytestring, containers - , cpphs, deepseq, mtl, old-locale, profunctors, QuickCheck, random - , stdenv, text, time, vector, vector-space, vector-th-unbox + , cpphs, deepseq, lib, mtl, old-locale, profunctors, QuickCheck + , random, text, time, vector, vector-space, vector-th-unbox }: mkDerivation { pname = "thyme"; @@ -33969,10 +40937,30 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/liyang/thyme"; description = "A faster time library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "tidal" = callPackage + ({ mkDerivation, base, bifunctors, bytestring, clock, colour + , containers, deepseq, hosc, lib, network, parsec, primitive + , random, text, transformers + }: + mkDerivation { + pname = "tidal"; + version = "1.7.7"; + sha256 = "4528119a05ebc94314b602430c4507f195b84ae715f780a0aabc8be60b8129a7"; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + base bifunctors bytestring clock colour containers deepseq hosc + network parsec primitive random text transformers + ]; + doHaddock = false; + doCheck = false; + homepage = "http://tidalcycles.org/"; + description = "Pattern language for improvised music"; + license = lib.licenses.gpl3Only; }) {}; "tile" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "tile"; version = "0.3.0.0"; @@ -33982,23 +40970,25 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/caneroj1/tile#readme"; description = "Slippy map tile functionality"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "time-compat" = callPackage - ({ mkDerivation, base, old-time, stdenv, time }: + ({ mkDerivation, base, base-orphans, deepseq, lib, time }: mkDerivation { pname = "time-compat"; - version = "0.1.0.3"; - sha256 = "590711214510c0d2d09780c7fe3b21748bc4802e9053f78ccd6658e951fe0f7f"; - libraryHaskellDepends = [ base old-time time ]; + version = "1.9.5"; + sha256 = "3126b267d19f31d52a3c36f13a8788be03242f829a5bddd8a3084e134d01e3a6"; + revision = "1"; + editedCabalFile = "1f6r8cyfgzpfg9nrsqbf99pi44fyds9wcmgwxb4s0zmlb5dbv1m5"; + libraryHaskellDepends = [ base base-orphans deepseq time ]; doHaddock = false; doCheck = false; - homepage = "http://hub.darcs.net/dag/time-compat"; - description = "Compatibility with old-time for the time package"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/haskellari/time-compat"; + description = "Compatibility package for time"; + license = lib.licenses.bsd3; }) {}; "time-lens" = callPackage - ({ mkDerivation, base, data-lens-light, stdenv, time }: + ({ mkDerivation, base, data-lens-light, lib, time }: mkDerivation { pname = "time-lens"; version = "0.4.0.2"; @@ -34008,10 +40998,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/feuerbach/time-lens"; description = "Lens-based interface to Data.Time data structures"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "time-locale-compat" = callPackage - ({ mkDerivation, base, stdenv, time }: + ({ mkDerivation, base, lib, time }: mkDerivation { pname = "time-locale-compat"; version = "0.1.1.5"; @@ -34022,10 +41012,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/khibino/haskell-time-locale-compat"; description = "Compatibile module for time-format locale"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "time-locale-vietnamese" = callPackage - ({ mkDerivation, base, stdenv, time }: + ({ mkDerivation, base, lib, time }: mkDerivation { pname = "time-locale-vietnamese"; version = "1.0.0.0"; @@ -34035,42 +41025,51 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/tungd/time-locale-vietnamese#readme"; description = "Vietnamese locale for date and time format"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; + }) {}; + "time-manager" = callPackage + ({ mkDerivation, auto-update, base, lib }: + mkDerivation { + pname = "time-manager"; + version = "0.0.0"; + sha256 = "90a616ed20b2119bb64f78f84230b6798cde22a35e87bc8d9ee08cdf1d90fcdb"; + libraryHaskellDepends = [ auto-update base ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/yesodweb/wai"; + description = "Scalable timer"; + license = lib.licenses.mit; }) {}; "time-parsers" = callPackage - ({ mkDerivation, base, parsers, stdenv, template-haskell, time }: + ({ mkDerivation, base, lib, parsers, template-haskell, time }: mkDerivation { pname = "time-parsers"; - version = "0.1.2.0"; - sha256 = "4e50d40f13f8e6c5175be22b91586f909607ecb631f8209ff45bce2031bb3c24"; + version = "0.1.2.1"; + sha256 = "bbf133bd986e79664560f42f2a36b7ad2e89c1095316029e7d6b228412355380"; revision = "3"; - editedCabalFile = "0im963wjcmwf6ii9a00mbi8lhmx5cy7cs6rmp0qi2j2jddba78j2"; + editedCabalFile = "1cv9fpn8bixicwcacyv0hx81q1xw06pig07zrpnf354bqzrsf3jw"; libraryHaskellDepends = [ base parsers template-haskell time ]; doHaddock = false; doCheck = false; homepage = "https://github.com/phadej/time-parsers#readme"; description = "Parsers for types in `time`"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "time-qq" = callPackage - ({ mkDerivation, base, stdenv, template-haskell, time - , time-locale-compat - }: + "time-units" = callPackage + ({ mkDerivation, base, lib }: mkDerivation { - pname = "time-qq"; - version = "0.0.1.0"; - sha256 = "ad6f0e5a6e5606ec2df3bb20006f92158100f20298a1b71fe6d79532c6814c87"; - libraryHaskellDepends = [ - base template-haskell time time-locale-compat - ]; + pname = "time-units"; + version = "1.0.0"; + sha256 = "e181997dd05321f09b21c5e0bf38524ccab51ecc588a6017253cc96db289e099"; + libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/christian-marie/time-qq"; - description = "Quasi-quoter for UTCTime times"; - license = stdenv.lib.licenses.bsd3; + homepage = "http://github.com/acw/time-units"; + description = "A basic library for defining units of time as types"; + license = lib.licenses.bsd3; }) {}; "timeit" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "timeit"; version = "2.0"; @@ -34082,10 +41081,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/merijn/timeit"; description = "Time monadic computations with an IO base"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "timelens" = callPackage - ({ mkDerivation, base, lens, stdenv, time }: + ({ mkDerivation, base, lens, lib, time }: mkDerivation { pname = "timelens"; version = "0.2.0.2"; @@ -34095,35 +41094,31 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.github.com/massysett/timelens"; description = "Lenses for the time package"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "timer-wheel" = callPackage - ({ mkDerivation, atomic-primops, base, ghc-prim, primitive - , psqueues, stdenv - }: + ({ mkDerivation, atomic-primops, base, lib, psqueues, vector }: mkDerivation { pname = "timer-wheel"; - version = "0.1.0"; - sha256 = "52e8679dc2daea5ce7bf49d2e100d6ba6db74084a05980ee7870b8ee8f395572"; + version = "0.3.0"; + sha256 = "fa805b893b3a6f44e84ca16a863972a30e7d1b28386649fa091048cdea30669b"; revision = "1"; - editedCabalFile = "0vk0p21x90wiazss30zkbzr5fnsc4gih9a6xaa9myyycw078600v"; - libraryHaskellDepends = [ - atomic-primops base ghc-prim primitive psqueues - ]; + editedCabalFile = "03wprm88wl6smfcq6dfr62l4igi8lfg6wkk65rsmyzxxkjzhc6f1"; + libraryHaskellDepends = [ atomic-primops base psqueues vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mitchellwrosen/timer-wheel"; description = "A timer wheel"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "timerep" = callPackage - ({ mkDerivation, attoparsec, base, monoid-subclasses, stdenv, text + ({ mkDerivation, attoparsec, base, lib, monoid-subclasses, text , time }: mkDerivation { pname = "timerep"; - version = "2.0.0.2"; - sha256 = "1d4e417f3ca08921941c16791680e13b66fb1844d94759068846ede78c965339"; + version = "2.0.1.0"; + sha256 = "2ef6a7266357fbfcb5859a6fff7b3cdfdcda3fbf69169fafea00372fdd7ac7d0"; libraryHaskellDepends = [ attoparsec base monoid-subclasses text time ]; @@ -34131,16 +41126,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/HugoDaniel/timerep"; description = "Parse and display time according to some RFCs (RFC3339, RFC2822, RFC822)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "timezone-olson" = callPackage ({ mkDerivation, base, binary, bytestring, extensible-exceptions - , stdenv, time, timezone-series + , lib, time, timezone-series }: mkDerivation { pname = "timezone-olson"; - version = "0.1.9"; - sha256 = "32230509029bcf9e1bd95b5ad7ee69b8b0250cffc4bb8f2df88a651b3af74b15"; + version = "0.2.0"; + sha256 = "8f57c369a72c4da5ba546d6e62370567e835cc2f6da406fd00e8dbb48e803b2d"; libraryHaskellDepends = [ base binary bytestring extensible-exceptions time timezone-series ]; @@ -34148,10 +41143,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://projects.haskell.org/time-ng/"; description = "A pure Haskell parser and renderer for binary Olson timezone files"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "timezone-series" = callPackage - ({ mkDerivation, base, deepseq, stdenv, time }: + ({ mkDerivation, base, deepseq, lib, time }: mkDerivation { pname = "timezone-series"; version = "0.1.9"; @@ -34161,16 +41156,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://projects.haskell.org/time-ng/"; description = "Enhanced timezone handling for Data.Time"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tinylog" = callPackage ({ mkDerivation, base, bytestring, containers, double-conversion - , fast-logger, stdenv, text, transformers, unix-time + , fast-logger, lib, text, transformers, unix-time }: mkDerivation { pname = "tinylog"; - version = "0.14.1"; - sha256 = "d13e96117dfcedc861185bee5d1d130a92bce7876cc1ffd041ace2426820df07"; + version = "0.15.0"; + sha256 = "cb71164ce47af991babc9837e3e86c4f9d4e0cac1440f56faa71f4497af58d5f"; libraryHaskellDepends = [ base bytestring containers double-conversion fast-logger text transformers unix-time @@ -34179,10 +41174,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://gitlab.com/twittner/tinylog/"; description = "Simplistic logging using fast-logger"; - license = stdenv.lib.licenses.mpl20; + license = lib.licenses.mpl20; }) {}; "titlecase" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "titlecase"; version = "1.0.1"; @@ -34195,87 +41190,113 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/peti/titlecase#readme"; description = "Convert English Words to Title Case"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tldr" = callPackage - ({ mkDerivation, ansi-terminal, base, bytestring, cmark, directory - , filepath, optparse-applicative, semigroups, stdenv, text - , typed-process + ({ mkDerivation, ansi-terminal, base, bytestring, cmark, containers + , directory, filepath, http-conduit, lib, optparse-applicative + , semigroups, text, time, zip-archive }: mkDerivation { pname = "tldr"; - version = "0.4.0.1"; - sha256 = "a35525699a5a16fa0e9d4a80c00336f3285ac561883c84286afc4b997c408559"; + version = "0.9.0"; + sha256 = "b0d42781f6ac77660a9cba6ae7e2e5c0e711835e5e2e9399d373a86922ea3d36"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - ansi-terminal base bytestring cmark text - ]; - executableHaskellDepends = [ - base directory filepath optparse-applicative semigroups - typed-process + ansi-terminal base bytestring cmark containers directory filepath + http-conduit optparse-applicative semigroups text time zip-archive ]; + executableHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/psibi/tldr-hs#readme"; description = "Haskell tldr client"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tls" = callPackage ({ mkDerivation, asn1-encoding, asn1-types, async, base, bytestring - , cereal, cryptonite, data-default-class, memory, mtl, network - , stdenv, transformers, x509, x509-store, x509-validation + , cereal, cryptonite, data-default-class, hourglass, lib, memory + , mtl, network, transformers, x509, x509-store, x509-validation }: mkDerivation { pname = "tls"; - version = "1.4.1"; - sha256 = "bbead1afc0b808bd5cff7bddaeae84ade37f18bbe72bd78d45a2fa4ac41908f8"; + version = "1.5.5"; + sha256 = "8a48b5ced43fac15c99158f0eedec458d77a6605c1a4302d41457f5a70ef3948"; libraryHaskellDepends = [ asn1-encoding asn1-types async base bytestring cereal cryptonite - data-default-class memory mtl network transformers x509 x509-store - x509-validation + data-default-class hourglass memory mtl network transformers x509 + x509-store x509-validation ]; doHaddock = false; doCheck = false; homepage = "http://github.com/vincenthz/hs-tls"; description = "TLS/SSL protocol native implementation (Server and Client)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tls-debug" = callPackage ({ mkDerivation, base, bytestring, cryptonite, data-default-class - , network, pem, stdenv, time, tls, x509, x509-store, x509-system - , x509-validation + , lib, network, pem, tls, tls-session-manager, x509, x509-store + , x509-system, x509-validation }: mkDerivation { pname = "tls-debug"; - version = "0.4.5"; - sha256 = "a345c4863bf923829d73abb8e2b706dab8058b12cdf73859d3860eaf7223eb9b"; + version = "0.4.8"; + sha256 = "74633188747b117762b9c6e7b6df9ac0e536a1adf93de3836733cb50c194def4"; isLibrary = false; isExecutable = true; executableHaskellDepends = [ - base bytestring cryptonite data-default-class network pem time tls - x509 x509-store x509-system x509-validation + base bytestring cryptonite data-default-class network pem tls + tls-session-manager x509 x509-store x509-system x509-validation ]; doHaddock = false; doCheck = false; homepage = "http://github.com/vincenthz/hs-tls"; description = "Set of programs for TLS testing and debugging"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tls-session-manager" = callPackage - ({ mkDerivation, auto-update, base, clock, psqueues, stdenv, tls }: + ({ mkDerivation, auto-update, base, basement, bytestring, clock + , lib, memory, psqueues, tls + }: mkDerivation { pname = "tls-session-manager"; - version = "0.0.0.2"; - sha256 = "c586ccfd8da578ed2174352bea1952f55fe38023e476f851d7f0ed428aa57567"; - libraryHaskellDepends = [ auto-update base clock psqueues tls ]; + version = "0.0.4"; + sha256 = "ba207f79b4536a65625063106c621e8bafc0dc7928bd9273270e19f36d59938c"; + libraryHaskellDepends = [ + auto-update base basement bytestring clock memory psqueues tls + ]; doHaddock = false; doCheck = false; description = "In-memory TLS session manager"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "tlynx" = callPackage + ({ mkDerivation, aeson, attoparsec, base, bytestring, comonad + , containers, elynx-tools, elynx-tree, gnuplot, lib, lifted-async + , monad-logger, mwc-random, optparse-applicative, parallel + , statistics, text, transformers, vector + }: + mkDerivation { + pname = "tlynx"; + version = "0.5.1.1"; + sha256 = "dd6f5727b98d34b23f600d3d1ba252c82aa0a39ffb2430e08954c4197d91e2c2"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson attoparsec base bytestring comonad containers elynx-tools + elynx-tree gnuplot lifted-async monad-logger mwc-random + optparse-applicative parallel statistics text transformers vector + ]; + executableHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/dschrempf/elynx#readme"; + description = "Handle phylogenetic trees"; + license = lib.licenses.gpl3Plus; }) {}; "tmapchan" = callPackage - ({ mkDerivation, base, containers, hashable, stdenv, stm + ({ mkDerivation, base, containers, hashable, lib, stm , unordered-containers }: mkDerivation { @@ -34289,10 +41310,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/athanclark/tmapchan#readme"; description = "An insert-ordered multimap (indexed FIFO) which consumes values as you lookup"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tmapmvar" = callPackage - ({ mkDerivation, base, containers, hashable, stdenv, stm + ({ mkDerivation, base, containers, hashable, lib, stm , unordered-containers }: mkDerivation { @@ -34305,66 +41326,109 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A single-entity stateful Map in STM, similar to tmapchan"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tmp-postgres" = callPackage - ({ mkDerivation, base, bytestring, directory, network - , postgresql-simple, process, stdenv, temporary, unix + ({ mkDerivation, ansi-wl-pprint, async, base, base64-bytestring + , bytestring, containers, cryptohash-sha1, deepseq, directory + , generic-monoid, lib, port-utils, postgres-options + , postgresql-simple, process, stm, temporary, transformers, unix }: mkDerivation { pname = "tmp-postgres"; - version = "0.1.1.1"; - sha256 = "2c5d557c53f60179d5e5e8c7fb6e393ff703e45b55c126359b308ab7a82be863"; + version = "1.34.1.0"; + sha256 = "98514428edaf527cc464cb9a30df89c6168c858e039ab1baf8293471196c3ba2"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - base bytestring directory network postgresql-simple process - temporary unix + ansi-wl-pprint async base base64-bytestring bytestring containers + cryptohash-sha1 deepseq directory generic-monoid port-utils + postgres-options postgresql-simple process stm temporary + transformers unix + ]; + executableHaskellDepends = [ + async base directory postgres-options postgresql-simple process + temporary ]; doHaddock = false; doCheck = false; homepage = "https://github.com/jfischoff/tmp-postgres#readme"; - description = "Start and stop a temporary postgres for testing"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "token-bucket" = callPackage - ({ mkDerivation, base, stdenv }: - mkDerivation { - pname = "token-bucket"; - version = "0.1.0.1"; - sha256 = "312609c0037271b1091f23c2edf467e9449edca5bbed0cfb45c2c93c1bee6ad0"; - revision = "4"; - editedCabalFile = "19kxi77aqyra00m02751sdfm6qy6mx4mlh7bhqv4wyaggwga707g"; - libraryHaskellDepends = [ base ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/hvr/token-bucket"; - description = "Rate limiter using lazy bucket algorithm"; - license = stdenv.lib.licenses.gpl3; + description = "Start and stop a temporary postgres"; + license = lib.licenses.bsd3; }) {}; "tomland" = callPackage ({ mkDerivation, base, bytestring, containers, deepseq, hashable - , megaparsec, mtl, parser-combinators, stdenv, text, time - , transformers, unordered-containers + , lib, markdown-unlit, megaparsec, mtl, parser-combinators, text + , time, transformers, unordered-containers, validation-selective }: mkDerivation { pname = "tomland"; - version = "0.5.0"; - sha256 = "eeedfcdd08b0d4839ff1417d39e437bdb12ba7429f174c6a1b6f4520fde02f00"; + version = "1.3.2.0"; + sha256 = "cc4e959be89b368f7e1619bf53c73bc56cfa32f543a3113396638f4f604d437a"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base bytestring containers deepseq hashable megaparsec mtl parser-combinators text time transformers unordered-containers + validation-selective + ]; + executableHaskellDepends = [ + base bytestring containers hashable text time unordered-containers ]; - executableHaskellDepends = [ base text time unordered-containers ]; + executableToolDepends = [ markdown-unlit ]; doHaddock = false; doCheck = false; homepage = "https://github.com/kowainik/tomland"; - description = "Bidirectional TOML parser"; - license = stdenv.lib.licenses.mpl20; + description = "Bidirectional TOML serialization"; + license = lib.licenses.mpl20; }) {}; - "tostring" = callPackage - ({ mkDerivation, base, case-insensitive, stdenv, text, utf8-string + "tonalude" = callPackage + ({ mkDerivation, base, bytestring, lib, rio, unliftio }: + mkDerivation { + pname = "tonalude"; + version = "0.1.1.1"; + sha256 = "10c0e278f4b8703204e0adc04084cf7f65761ac52085301ce4de8e6f0105f4a6"; + libraryHaskellDepends = [ base bytestring rio unliftio ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/tonatona-project/tonatona#readme"; + description = "A standard library for Tonatona framework"; + license = lib.licenses.mit; + }) {}; + "topograph" = callPackage + ({ mkDerivation, base, base-compat, base-orphans, containers, lib + , vector }: + mkDerivation { + pname = "topograph"; + version = "1.0.0.1"; + sha256 = "9b11c14dd579b952e64faaa762a5faddebc64949bc7f732865fcb599a37fa2e9"; + revision = "1"; + editedCabalFile = "1cbpm16jk8x8xy0r3v8zdmwrdgxlp6zww03rmzbz0031hddpywrk"; + libraryHaskellDepends = [ + base base-compat base-orphans containers vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/phadej/topograph"; + description = "Directed acyclic graphs"; + license = lib.licenses.bsd3; + }) {}; + "torsor" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "torsor"; + version = "0.1"; + sha256 = "75a3f53a08b9333613a16c5e98f12a069a1c1a360dc3c2abf7b47522acb06d9c"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/andrewthad/torsor#readme"; + description = "Torsor Typeclass"; + license = lib.licenses.bsd3; + }) {}; + "tostring" = callPackage + ({ mkDerivation, base, case-insensitive, lib, text, utf8-string }: mkDerivation { pname = "tostring"; version = "0.2.1.1"; @@ -34373,10 +41437,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "The ToString class"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "transaction" = callPackage - ({ mkDerivation, base, mono-traversable, stdenv }: + ({ mkDerivation, base, lib, mono-traversable }: mkDerivation { pname = "transaction"; version = "0.1.1.3"; @@ -34386,10 +41450,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/arowM/haskell-transaction#readme"; description = "Monadic representation of transactions"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "transformers-base" = callPackage - ({ mkDerivation, base, base-orphans, stdenv, stm, transformers + ({ mkDerivation, base, base-orphans, lib, stm, transformers , transformers-compat }: mkDerivation { @@ -34403,37 +41467,39 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mvv/transformers-base"; description = "Lift computations from the bottom of a transformer stack"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "transformers-bifunctors" = callPackage - ({ mkDerivation, base, mmorph, stdenv, transformers }: + ({ mkDerivation, base, lib, mmorph, transformers }: mkDerivation { pname = "transformers-bifunctors"; version = "0.1"; sha256 = "3c25d3d76361f62b4c7c37d4bc4b7497af691d000fcd8e5fe9cbb3544d284807"; + revision = "1"; + editedCabalFile = "1vjyk2ldwfi2pkvk79p37ii5xgg1399kxqhkq3l4wvag4j5p4afs"; libraryHaskellDepends = [ base mmorph transformers ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/jystic/transformers-bifunctors"; + homepage = "https://github.com/jacobstanley/transformers-bifunctors"; description = "Bifunctors over monad transformers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "transformers-compat" = callPackage - ({ mkDerivation, base, ghc-prim, stdenv, transformers }: + ({ mkDerivation, base, ghc-prim, lib, transformers }: mkDerivation { pname = "transformers-compat"; - version = "0.6.2"; - sha256 = "dc06228b7b8a546f9d257b4fe2b369fc2cb279240bbe4312aa8f47bb2752e4be"; + version = "0.6.6"; + sha256 = "7e2e0251e5e6d28142615a4b950a3fabac9c0b7804b1ec4a4ae985f19519a9f9"; configureFlags = [ "-ffive-three" ]; libraryHaskellDepends = [ base ghc-prim transformers ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/transformers-compat/"; description = "A small compatibility shim for the transformers library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "transformers-fix" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "transformers-fix"; version = "1.0"; @@ -34445,62 +41511,45 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/thumphries/transformers-fix"; description = "Monad transformer for evaluating to a fixpoint"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "transformers-lift" = callPackage - ({ mkDerivation, base, stdenv, transformers - , writer-cps-transformers - }: - mkDerivation { - pname = "transformers-lift"; - version = "0.2.0.1"; - sha256 = "0bd8bf23fb29874daf9ff990bf25035e21208cfa292f9f18e8cfdb0b4b1ee09d"; - revision = "2"; - editedCabalFile = "16gpca2wfa7w2b5kzfvqsjjyd61pkv0wyi2mk5b34367p4chnsc5"; - libraryHaskellDepends = [ - base transformers writer-cps-transformers - ]; - doHaddock = false; - doCheck = false; - description = "Ad-hoc type classes for lifting"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "traverse-with-class" = callPackage - ({ mkDerivation, base, stdenv, template-haskell, transformers }: + ({ mkDerivation, base, lib, template-haskell, transformers }: mkDerivation { pname = "traverse-with-class"; - version = "1.0.0.0"; - sha256 = "65a220f1652b68269dfe8cc283a6e9292941eb12bdbd79344e073ba766191fbb"; + version = "1.0.1.1"; + sha256 = "a698c9dd8316fc05339f818927b457e0f9a5ca1c1f4abc69a5f68d0c05481030"; libraryHaskellDepends = [ base template-haskell transformers ]; doHaddock = false; doCheck = false; description = "Generic applicative traversals"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "tree-diff" = callPackage ({ mkDerivation, aeson, ansi-terminal, ansi-wl-pprint, base - , base-compat, bytestring, containers, generics-sop, hashable - , MemoTrie, parsec, parsers, pretty, QuickCheck, scientific, stdenv - , tagged, text, time, unordered-containers, uuid-types, vector + , base-compat, bytestring, bytestring-builder, containers, deepseq + , hashable, lib, parsec, parsers, pretty, primitive, QuickCheck + , scientific, semialign, strict, tagged, text, these, time + , unordered-containers, uuid-types, vector }: mkDerivation { pname = "tree-diff"; - version = "0.0.2"; - sha256 = "f8690bd14977f66292759f432a9f0d1b15f00b37001e7c4ea1a04c3fa38a9b7e"; + version = "0.2"; + sha256 = "1d38d8b84068222f21f08409de1042cafbd89fa876c1987031cb336441acc7db"; libraryHaskellDepends = [ aeson ansi-terminal ansi-wl-pprint base base-compat bytestring - containers generics-sop hashable MemoTrie parsec parsers pretty - QuickCheck scientific tagged text time unordered-containers - uuid-types vector + bytestring-builder containers deepseq hashable parsec parsers + pretty primitive QuickCheck scientific semialign strict tagged text + these time unordered-containers uuid-types vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/phadej/tree-diff"; description = "Diffing of (expression) trees"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.gpl2Plus; }) {}; "tree-fun" = callPackage - ({ mkDerivation, base, containers, mtl, stdenv }: + ({ mkDerivation, base, containers, lib, mtl }: mkDerivation { pname = "tree-fun"; version = "0.8.1.0"; @@ -34509,41 +41558,52 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Library for functions pertaining to tree exploration and manipulation"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; + }) {}; + "tree-view" = callPackage + ({ mkDerivation, base, containers, lib, mtl }: + mkDerivation { + pname = "tree-view"; + version = "0.5.1"; + sha256 = "4f58284da25f6347f971ff7f4fbcfdc51acb8ffc6b3bf73939f60e1471a843f9"; + libraryHaskellDepends = [ base containers mtl ]; + doHaddock = false; + doCheck = false; + description = "Render trees as foldable HTML and Unicode art"; + license = lib.licenses.bsd3; }) {}; "trifecta" = callPackage - ({ mkDerivation, ansi-terminal, ansi-wl-pprint, array, base - , blaze-builder, blaze-html, blaze-markup, bytestring, Cabal - , cabal-doctest, charset, comonad, containers, deepseq, fingertree - , ghc-prim, hashable, lens, mtl, parsers, profunctors, reducers - , semigroups, stdenv, transformers, unordered-containers - , utf8-string + ({ mkDerivation, ansi-terminal, array, base, blaze-builder + , blaze-html, blaze-markup, bytestring, charset, comonad + , containers, deepseq, fingertree, ghc-prim, hashable + , indexed-traversable, lens, lib, mtl, parsers, prettyprinter + , prettyprinter-ansi-terminal, profunctors, reducers, transformers + , unordered-containers, utf8-string }: mkDerivation { pname = "trifecta"; - version = "2"; - sha256 = "53972fe9d206eab6ae1a654fe8c57274f01b373b0c8b3882ef01e962226af643"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "2.1.1"; + sha256 = "de5cfeb21951f21ede04d46a0885297ae6ea78416e383fbc7c9bc6dd3b881fd2"; libraryHaskellDepends = [ - ansi-terminal ansi-wl-pprint array base blaze-builder blaze-html - blaze-markup bytestring charset comonad containers deepseq - fingertree ghc-prim hashable lens mtl parsers profunctors reducers - semigroups transformers unordered-containers utf8-string + ansi-terminal array base blaze-builder blaze-html blaze-markup + bytestring charset comonad containers deepseq fingertree ghc-prim + hashable indexed-traversable lens mtl parsers prettyprinter + prettyprinter-ansi-terminal profunctors reducers transformers + unordered-containers utf8-string ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/trifecta/"; description = "A modern parser combinator library with convenient diagnostics"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "triplesec" = callPackage - ({ mkDerivation, base, cryptonite, memory, mtl, stdenv - , transformers + ({ mkDerivation, base, cryptonite, lib, memory, mtl, transformers }: mkDerivation { pname = "triplesec"; - version = "0.2.2.0"; - sha256 = "077e32dc11a2d80b74baa37d3fb0fab46a1e0165e56c912d0d6a64090bd1b3bf"; + version = "0.2.2.1"; + sha256 = "3ab7ff8bc630fbdd3d479e993d67853dacfc2967a2ca46b8bb7ee9387158d971"; libraryHaskellDepends = [ base cryptonite memory mtl transformers ]; @@ -34551,10 +41611,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/SamProtas/hs-triplesec"; description = "TripleSec is a simple, triple-paranoid, symmetric encryption library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "trivial-constraint" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "trivial-constraint"; + version = "0.7.0.0"; + sha256 = "4742c2dd42ac6301370692a646add818232d502d6639a256ae9438e9b08bd24f"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/leftaroundabout/trivial-constraint"; + description = "Constraints that any type, resp. no type fulfills"; + license = lib.licenses.gpl3Only; }) {}; "tsv2csv" = callPackage - ({ mkDerivation, base, HUnit, split, stdenv }: + ({ mkDerivation, base, HUnit, lib, split }: mkDerivation { pname = "tsv2csv"; version = "0.1.0.2"; @@ -34566,10 +41639,42 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Convert tsv to csv"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "ttc" = callPackage + ({ mkDerivation, base, bytestring, lib, template-haskell, text }: + mkDerivation { + pname = "ttc"; + version = "1.1.0.1"; + sha256 = "c1121514142c32fc6ad72fb6fde79d06de04dc1d16037c4a263feed2aab9cf6e"; + libraryHaskellDepends = [ base bytestring template-haskell text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ExtremaIS/ttc-haskell#readme"; + description = "Textual Type Classes"; + license = lib.licenses.mit; + }) {}; + "ttl-hashtables" = callPackage + ({ mkDerivation, base, clock, containers, data-default, failable + , hashable, hashtables, lib, mtl, transformers + }: + mkDerivation { + pname = "ttl-hashtables"; + version = "1.4.1.0"; + sha256 = "d20d7aefb98a617fefaf9178c0a3d23620625800598054f2d7be36e8cafa7cf8"; + revision = "1"; + editedCabalFile = "0ghzp5kqk5a6831kxfizsnjjcaflinqb26l4d5vjwk7763jad195"; + libraryHaskellDepends = [ + base clock containers data-default failable hashable hashtables mtl + transformers + ]; + doHaddock = false; + doCheck = false; + description = "Extends hashtables so that entries added can be expired after a TTL"; + license = lib.licenses.bsd3; }) {}; "ttrie" = callPackage - ({ mkDerivation, atomic-primops, base, hashable, primitive, stdenv + ({ mkDerivation, atomic-primops, base, hashable, lib, primitive , stm }: mkDerivation { @@ -34583,10 +41688,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/mcschroeder/ttrie"; description = "Contention-free STM hash map"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "tuple" = callPackage - ({ mkDerivation, base, OneTuple, stdenv }: + ({ mkDerivation, base, lib, OneTuple }: mkDerivation { pname = "tuple"; version = "0.3.0.2"; @@ -34595,10 +41700,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Various functions on tuples"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tuple-sop" = callPackage - ({ mkDerivation, base, generics-sop, stdenv }: + ({ mkDerivation, base, generics-sop, lib }: mkDerivation { pname = "tuple-sop"; version = "0.3.1.0"; @@ -34608,10 +41713,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/Ferdinand-vW/tuple-sop#readme"; description = "functions on n-ary tuples using generics-sop"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; }) {}; "tuple-th" = callPackage - ({ mkDerivation, base, containers, stdenv, template-haskell }: + ({ mkDerivation, base, containers, lib, template-haskell }: mkDerivation { pname = "tuple-th"; version = "0.2.5"; @@ -34620,10 +41725,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Generate (non-recursive) utility functions for tuples of statically known size"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "tuples-homogenous-h98" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "tuples-homogenous-h98"; version = "0.1.1.0"; @@ -34633,45 +41738,81 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/ppetr/tuples-homogenous-h98"; description = "Wrappers for n-ary tuples with Traversable and Applicative/Monad instances"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "turtle" = callPackage ({ mkDerivation, ansi-wl-pprint, async, base, bytestring, clock - , containers, directory, exceptions, foldl, hostname, managed - , optional-args, optparse-applicative, process, semigroups, stdenv - , stm, system-fileio, system-filepath, temporary, text, time - , transformers, unix, unix-compat + , containers, directory, exceptions, foldl, hostname, lib, managed + , optional-args, optparse-applicative, process, stm + , streaming-commons, system-fileio, system-filepath, temporary + , text, time, transformers, unix, unix-compat }: mkDerivation { pname = "turtle"; - version = "1.5.13"; - sha256 = "0f06763f7a50b19862bd048e9387ddc441f085c5e1aa3a392322210a38f44484"; + version = "1.5.22"; + sha256 = "9ac4bbbd8063e376b1b05c174333d161915ac259f305afd33591f55cd6208e92"; libraryHaskellDepends = [ ansi-wl-pprint async base bytestring clock containers directory exceptions foldl hostname managed optional-args - optparse-applicative process semigroups stm system-fileio + optparse-applicative process stm streaming-commons system-fileio system-filepath temporary text time transformers unix unix-compat ]; doHaddock = false; doCheck = false; description = "Shell programming, Haskell-style"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "type-fun" = callPackage - ({ mkDerivation, base, stdenv }: + "type-equality" = callPackage + ({ mkDerivation, base, lib }: mkDerivation { - pname = "type-fun"; - version = "0.1.1"; - sha256 = "df5ec7428a101235df46c0b819a9ab3562d1d27991cc3b04303643952c555da1"; + pname = "type-equality"; + version = "1"; + sha256 = "4728b502a211454ef682a10d7a3e817c22d06ba509df114bb267ef9d43a08ce8"; + revision = "2"; + editedCabalFile = "1a3irpv5kyg3rywhmcp5fwg5irrdbdr0hrlw7asdk113nakrba7j"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/hesselink/type-equality"; + description = "Data.Type.Equality compat package"; + license = lib.licenses.bsd3; + }) {}; + "type-errors" = callPackage + ({ mkDerivation, base, first-class-families, lib, syb + , template-haskell, th-abstraction + }: + mkDerivation { + pname = "type-errors"; + version = "0.2.0.0"; + sha256 = "174d509c30ec806117a244add923fee578ba5f3505b0156f4e03a32023892eb4"; + revision = "2"; + editedCabalFile = "1rlhswrkyvhaqhgk2yr9xk49yp196p5fy37hmyni9g7rx1d07qyj"; + libraryHaskellDepends = [ + base first-class-families syb template-haskell th-abstraction + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/isovector/type-errors#readme"; + description = "Tools for writing better type errors"; + license = lib.licenses.bsd3; + }) {}; + "type-errors-pretty" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "type-errors-pretty"; + version = "0.0.1.1"; + sha256 = "c05129843ad37820fec27f1a9e150ca239efc9d5b00fce26a3765b3ca0c2d9fc"; + revision = "1"; + editedCabalFile = "1qfm0018ids9s7kdwf6d3r1cwnb5aqn55in4vdwklas3ydi8mmrx"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/s9gf4ult/type-fun"; - description = "Collection of widely reimplemented type families"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/chshersh/type-errors-pretty"; + description = "Combinators for writing pretty type errors easily"; + license = lib.licenses.mpl20; }) {}; "type-hint" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "type-hint"; version = "0.1"; @@ -34681,10 +41822,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mvv/type-hint"; description = "Guide type inference with proxy values"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "type-level-integers" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "type-level-integers"; version = "0.0.1"; @@ -34694,10 +41835,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mtesseract/type-level-integers"; description = "Provides integers lifted to the type level"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "type-level-kv-list" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "type-level-kv-list"; version = "1.1.0"; @@ -34707,10 +41848,22 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/arowM/type-level-kv-list#readme"; description = "A module for hash map like object with type level keys"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "type-level-natural-number" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "type-level-natural-number"; + version = "2.0"; + sha256 = "d36754ece101d23e2666a3fb7d8dbf88b05153fc6bfccf7a9fc1fca07da9ef9f"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + description = "Simple type level natural numbers"; + license = lib.licenses.bsd3; }) {}; "type-level-numbers" = callPackage - ({ mkDerivation, base, stdenv, template-haskell }: + ({ mkDerivation, base, lib, template-haskell }: mkDerivation { pname = "type-level-numbers"; version = "0.1.1.1"; @@ -34719,16 +41872,50 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Type level numbers implemented using type families"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "type-map" = callPackage + ({ mkDerivation, base, containers, ghc-prim, lib, vector }: + mkDerivation { + pname = "type-map"; + version = "0.1.6.0"; + sha256 = "25d7ff6ceda7eb4f9aa95a1a4d8463fc71f88d019ca0d1410ecff2df56a1537d"; + libraryHaskellDepends = [ base containers ghc-prim vector ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/Lysxia/type-map"; + description = "Type-indexed maps"; + license = lib.licenses.mit; + }) {}; + "type-natural" = callPackage + ({ mkDerivation, base, constraints, equational-reasoning, ghc + , ghc-typelits-knownnat, ghc-typelits-natnormalise + , ghc-typelits-presburger, integer-logarithms, lib + , template-haskell + }: + mkDerivation { + pname = "type-natural"; + version = "1.1.0.0"; + sha256 = "55ae1e1a520eb4d02ed34f00afc938ce4b977c2f7d63513d91612423c8955e2b"; + libraryHaskellDepends = [ + base constraints equational-reasoning ghc ghc-typelits-knownnat + ghc-typelits-natnormalise ghc-typelits-presburger + integer-logarithms template-haskell + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/konn/type-natural"; + description = "Type-level natural and proofs of their properties"; + license = lib.licenses.bsd3; }) {}; "type-of-html" = callPackage ({ mkDerivation, base, bytestring, containers, double-conversion - , ghc-prim, stdenv, text + , ghc-prim, lib, text }: mkDerivation { pname = "type-of-html"; - version = "1.5.0.0"; - sha256 = "891aa1694017f96ebab4633cc240b2ce51352b42c4d033c8e8c73e0d2b2f402e"; + version = "1.6.2.0"; + sha256 = "72401addcb6243054719e1bcef87db225a6733386b78495a0003b6bae8d29ca1"; libraryHaskellDepends = [ base bytestring containers double-conversion ghc-prim text ]; @@ -34736,10 +41923,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/knupfer/type-of-html"; description = "High performance type driven html generation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "type-of-html-static" = callPackage - ({ mkDerivation, base, stdenv, template-haskell, type-of-html }: + ({ mkDerivation, base, lib, template-haskell, type-of-html }: mkDerivation { pname = "type-of-html-static"; version = "0.1.0.2"; @@ -34749,123 +41936,134 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/knupfer/type-of-html-static"; description = "Optimize static parts of type-of-html"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "type-operators" = callPackage - ({ mkDerivation, base, ghc-prim, stdenv }: + ({ mkDerivation, base, ghc-prim, lib }: mkDerivation { pname = "type-operators"; - version = "0.1.0.4"; - sha256 = "dbbcedf368c23c46abac04f157cb4f2c812099a4f75d606b24f1ac1116d40b74"; + version = "0.2.0.0"; + sha256 = "9250be034d38b1412f530b92814b5de9ad189e97b5f0120b42955f9995dba3b2"; libraryHaskellDepends = [ base ghc-prim ]; doHaddock = false; doCheck = false; homepage = "https://github.com/Shou/type-operators#readme"; description = "Various type-level operators"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "type-spec" = callPackage - ({ mkDerivation, base, pretty, stdenv }: + ({ mkDerivation, base, lib, pretty }: mkDerivation { pname = "type-spec"; - version = "0.3.0.1"; - sha256 = "aecd1a319efc13eb42b73b489cf374f94bf126f19fdc28b2f5cd6f73dda3a241"; + version = "0.4.0.0"; + sha256 = "b8eb5e12f4979dd3e2ea7c0edca60e31a7f4fbaab35d7dd44e9b5d5bf783247d"; libraryHaskellDepends = [ base pretty ]; doHaddock = false; doCheck = false; homepage = "https://github.com/sheyll/type-spec#readme"; description = "Type Level Specification by Example"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "typecheck-plugin-nat-simple" = callPackage + ({ mkDerivation, base, containers, ghc, lib }: + mkDerivation { + pname = "typecheck-plugin-nat-simple"; + version = "0.1.0.2"; + sha256 = "20ddc4d7de8a2f33b6d4a8ca4951f0aa0ff81fcedca664650e9996639115b7c1"; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ base containers ghc ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/YoshikuniJujo/typecheck-plugin-nat-simple#readme"; + description = "Simple type check plugin which calculate addition, subtraction and less-or-equal-than"; + license = lib.licenses.bsd3; }) {}; "typed-process" = callPackage - ({ mkDerivation, async, base, bytestring, process, stdenv, stm - , transformers + ({ mkDerivation, async, base, bytestring, lib, process, stm + , transformers, unliftio-core }: mkDerivation { pname = "typed-process"; - version = "0.2.3.0"; - sha256 = "c0dea5591a4730d151d5c146685d0fa3db1f390d2a63be70a981209e58de6648"; + version = "0.2.6.0"; + sha256 = "31a2a81f33463fedc33cc519ad5b9679787e648fe2ec7efcdebd7d54bdbbc2b1"; libraryHaskellDepends = [ - async base bytestring process stm transformers + async base bytestring process stm transformers unliftio-core ]; doHaddock = false; doCheck = false; homepage = "https://haskell-lang.org/library/typed-process"; description = "Run external processes, with strong typing of streams"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "typed-uuid" = callPackage + ({ mkDerivation, aeson, base, binary, bytestring, deepseq, hashable + , http-api-data, lib, random, text, uuid, validity, validity-uuid + , yamlparse-applicative + }: + mkDerivation { + pname = "typed-uuid"; + version = "0.1.0.0"; + sha256 = "b1fb195e15b1fa586c7696e2e0f7f5cdee85ddbbaa4d16e9f15bf361acccbcea"; + libraryHaskellDepends = [ + aeson base binary bytestring deepseq hashable http-api-data random + text uuid validity validity-uuid yamlparse-applicative + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/typed-uuid#readme"; + description = "Phantom-Typed version of UUID"; + license = lib.licenses.mit; }) {}; "typelits-witnesses" = callPackage - ({ mkDerivation, base, constraints, reflection, stdenv }: + ({ mkDerivation, base, dependent-sum, lib }: mkDerivation { pname = "typelits-witnesses"; - version = "0.3.0.3"; - sha256 = "4edd4aff3f49961a1eb87130c4d36c39f4cc81d411ff20100ef5f33fd74d191d"; - libraryHaskellDepends = [ base constraints reflection ]; + version = "0.4.0.0"; + sha256 = "e0505cdb323111d1a0dfb121b7e0dc7fd4b43cd931b7f3368187eaca942d1ece"; + libraryHaskellDepends = [ base dependent-sum ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mstksg/typelits-witnesses"; description = "Existential witnesses, singletons, and classes for operations on GHC TypeLits"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "typenums" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "typenums"; - version = "0.1.2.1"; - sha256 = "c6b4e083e664ecea40be2555f24c2e8b322b4f32a4a434e6514fecd6d6d6991b"; + version = "0.1.4"; + sha256 = "d47cd5c7410827c97212daa5cb18543849e8c11a892626147282138c34b16e99"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/adituv/typenums#readme"; description = "Type level numbers using existing Nat functionality"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "typerep-map" = callPackage - ({ mkDerivation, base, containers, ghc-prim, primitive, stdenv - , vector + ({ mkDerivation, base, containers, deepseq, ghc-prim, lib + , primitive, vector }: mkDerivation { pname = "typerep-map"; - version = "0.3.0"; - sha256 = "6e1d5bf975f9810f1fc3d235f370b57a338bb60a5f239c2ea5ca95b3dc17aa34"; - revision = "1"; - editedCabalFile = "102lwg5rl1628j3v331xj93cgvr9ppmphyjlqli4gm5vxgrkwsfv"; + version = "0.3.3.0"; + sha256 = "0456c29aaa75b2f2e245ace73d3441e65b31b63fef2f700381ba5d3bc13cee48"; libraryHaskellDepends = [ - base containers ghc-prim primitive vector + base containers deepseq ghc-prim primitive vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/kowainik/typerep-map"; description = "Efficient implementation of a dependent map with types as keys"; - license = stdenv.lib.licenses.mit; - }) {}; - "tz" = callPackage - ({ mkDerivation, base, binary, bytestring, containers, data-default - , deepseq, stdenv, template-haskell, time, tzdata, vector - }: - mkDerivation { - pname = "tz"; - version = "0.1.3.2"; - sha256 = "f0d066d0169f283b199193d8825aa56de6e3818cd85d8979791c0e7504bf654c"; - libraryHaskellDepends = [ - base binary bytestring containers data-default deepseq - template-haskell time tzdata vector - ]; - doHaddock = false; - doCheck = false; - preConfigure = "export TZDIR=${pkgs.tzdata}/share/zoneinfo"; - homepage = "https://github.com/nilcons/haskell-tz"; - description = "Efficient time zone handling"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.mpl20; }) {}; "tzdata" = callPackage - ({ mkDerivation, base, bytestring, containers, deepseq, stdenv - , vector + ({ mkDerivation, base, bytestring, containers, deepseq, lib, vector }: mkDerivation { pname = "tzdata"; - version = "0.1.20181026.0"; - sha256 = "ee99daf34ed04513ec69d4d97b719f0f8adbc1a1a2b12b3f217898c59a0fa32c"; + version = "0.2.20201021.0"; + sha256 = "a9f26ceb7b42ff7603a6fce9f3d3115882e9f19ae1b80f83b8d43584c13c6d2e"; enableSeparateDataOutput = true; libraryHaskellDepends = [ base bytestring containers deepseq vector @@ -34874,16 +42072,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/nilcons/haskell-tzdata"; description = "Time zone database (as files and as a module)"; - license = stdenv.lib.licenses.asl20; + license = lib.licenses.asl20; }) {}; "ua-parser" = callPackage ({ mkDerivation, aeson, base, bytestring, data-default, file-embed - , pcre-light, stdenv, text, yaml + , lib, pcre-light, text, yaml }: mkDerivation { pname = "ua-parser"; - version = "0.7.5.1"; - sha256 = "1fcc39a99b9ad7eb2ddb2194ea84def35860078c0344531e2715dc2b819e3424"; + version = "0.7.6.0"; + sha256 = "d44cdeeb6cf6b1a98323ec039e353af78db459910df3b91a504c5ce36add5369"; enableSeparateDataOutput = true; libraryHaskellDepends = [ aeson base bytestring data-default file-embed pcre-light text yaml @@ -34891,54 +42089,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A library for parsing User-Agent strings, official Haskell port of ua-parser"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "ucam-webauth" = callPackage - ({ mkDerivation, aeson, attoparsec, base, bytestring, containers - , cryptonite, errors, http-api-data, http-types, microlens - , microlens-mtl, mtl, parser-combinators, pem, stdenv, text, time - , ucam-webauth-types, x509 - }: - mkDerivation { - pname = "ucam-webauth"; - version = "0.1.0.0"; - sha256 = "335920d87a8d8fa24bcba34c4cba0a7adc84199c3161757ae00d7bad54428992"; - revision = "2"; - editedCabalFile = "1myl5nncwmld4hr0b9990dnqn9ydvza5ciqw5b8pjl747g9qky9f"; - libraryHaskellDepends = [ - aeson attoparsec base bytestring containers cryptonite errors - http-api-data http-types microlens microlens-mtl mtl - parser-combinators pem text time ucam-webauth-types x509 - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/dbaynard/UcamWebauth#readme"; - description = "The Ucam-Webauth protocol, used by Raven"; - license = "(BSD-3-Clause OR Apache-2.0)"; - }) {}; - "ucam-webauth-types" = callPackage - ({ mkDerivation, aeson, base, base64-bytestring, bytestring - , case-insensitive, containers, deepseq, http-types, microlens - , microlens-mtl, mtl, stdenv, text, time, timerep - }: - mkDerivation { - pname = "ucam-webauth-types"; - version = "0.1.0.0"; - sha256 = "d1ca7f834078ca63d398c1c2498e8f89e9edfae16b3150937973e5daaa32064b"; - revision = "2"; - editedCabalFile = "1pbl2sy17pkc15170h96ard4z155fm45g18jdxjcdx9hacl003rw"; - libraryHaskellDepends = [ - aeson base base64-bytestring bytestring case-insensitive containers - deepseq http-types microlens microlens-mtl mtl text time timerep - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/dbaynard/UcamWebauth#readme"; - description = "Types for the Ucam-Webauth protocol, as used by Raven"; - license = "(BSD-3-Clause OR Apache-2.0)"; + license = lib.licenses.bsd3; }) {}; "uglymemo" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "uglymemo"; version = "0.1.0.1"; @@ -34947,42 +42101,35 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A simple (but internally ugly) memoization function"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.publicDomain; }) {}; - "unbound-generics" = callPackage - ({ mkDerivation, ansi-wl-pprint, base, containers, contravariant - , deepseq, exceptions, mtl, profunctors, stdenv, template-haskell - , transformers, transformers-compat - }: + "unagi-chan" = callPackage + ({ mkDerivation, atomic-primops, base, ghc-prim, lib, primitive }: mkDerivation { - pname = "unbound-generics"; - version = "0.4.0"; - sha256 = "bd6aeda0921d540b3c4181805299ab34e0194389bd8617696d7fa9cc49d95511"; - libraryHaskellDepends = [ - ansi-wl-pprint base containers contravariant deepseq exceptions mtl - profunctors template-haskell transformers transformers-compat - ]; + pname = "unagi-chan"; + version = "0.4.1.3"; + sha256 = "e232e525881eb05f0c20b5a4e53150a3063351e5d94917c6f55934477a9ad695"; + libraryHaskellDepends = [ atomic-primops base ghc-prim primitive ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/lambdageek/unbound-generics"; - description = "Support for programming with names and binders using GHC Generics"; - license = stdenv.lib.licenses.bsd3; + description = "Fast concurrent queues with a Chan-like API, and more"; + license = lib.licenses.bsd3; }) {}; "unbounded-delays" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "unbounded-delays"; - version = "0.1.1.0"; - sha256 = "8aa7f7d10a8d0073518804db76c3ef4c313359994ef175122341b0bce07329c7"; + version = "0.1.1.1"; + sha256 = "59ad7e53bfe32ffbf0e703b31490d41d14c70e4745ed49e8adf592ed68dd6185"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/basvandijk/unbounded-delays"; description = "Unbounded thread delays and timeouts"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "unboxed-ref" = callPackage - ({ mkDerivation, base, ghc-prim, primitive, stdenv }: + ({ mkDerivation, base, ghc-prim, lib, primitive }: mkDerivation { pname = "unboxed-ref"; version = "0.4.0.0"; @@ -34992,11 +42139,44 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/winterland1989/unboxed-ref"; description = "Fast unboxed references for ST and IO monad"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "unboxing-vector" = callPackage + ({ mkDerivation, base, deepseq, lib, mono-traversable, primitive + , vector + }: + mkDerivation { + pname = "unboxing-vector"; + version = "0.2.0.0"; + sha256 = "21c91abdae9a2a690df72da57e86511daeeb90d98543ff54b469c1eaae3d5283"; + libraryHaskellDepends = [ + base deepseq mono-traversable primitive vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/minoki/unboxing-vector#readme"; + description = "A newtype-friendly variant of unboxed vectors"; + license = lib.licenses.bsd3; + }) {}; + "uncaught-exception" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "uncaught-exception"; + version = "0.1.0"; + sha256 = "b63f1749068b936d427ff9554dcecd53be1caf3b9e0ea08382bc27b99cb6dd9c"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base ]; + executableHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/serokell/uncaught-exception"; + description = "Customize uncaught exception handling"; + license = lib.licenses.mpl20; }) {}; "uncertain" = callPackage - ({ mkDerivation, ad, base, base-compat, containers, free - , mwc-random, primitive, stdenv, transformers + ({ mkDerivation, ad, base, base-compat, containers, free, lib + , mwc-random, primitive, transformers }: mkDerivation { pname = "uncertain"; @@ -35010,21 +42190,53 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/mstksg/uncertain"; description = "Manipulating numbers with inherent experimental/measurement uncertainty"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "unconstrained" = callPackage - ({ mkDerivation, stdenv }: + ({ mkDerivation, lib }: mkDerivation { pname = "unconstrained"; version = "0.1.0.2"; sha256 = "d2717a66a0232ce454740f45c74645af5ef052e23ba81195ce6c3a06a10e010d"; + revision = "1"; + editedCabalFile = "13fj2jlh44774www49fwp7h7z6gr23scfbvg745rpywys49c0559"; doHaddock = false; doCheck = false; description = "Null constraint"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "unexceptionalio" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "unexceptionalio"; + version = "0.5.1"; + sha256 = "b0ea7422bf197ca2620b4a16d7ee53314eb13e7c0c6f9f35fab7bfe69c15fe1e"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/singpolyma/unexceptionalio"; + description = "IO without any non-error, synchronous exceptions"; + license = "unknown"; + hydraPlatforms = lib.platforms.none; + }) {}; + "unexceptionalio-trans" = callPackage + ({ mkDerivation, base, lib, transformers, unexceptionalio }: + mkDerivation { + pname = "unexceptionalio-trans"; + version = "0.5.1"; + sha256 = "3f5a9c3d5c1feef2d0aa12b28ba067aa741be674179b13d419bf5175f3721a80"; + revision = "1"; + editedCabalFile = "0f15n8hqqczwjrcqxwjp2mrd9iycv53sylv407c95nb6d4hw93ci"; + libraryHaskellDepends = [ base transformers unexceptionalio ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/singpolyma/unexceptionalio-trans"; + description = "A wrapper around UnexceptionalIO using monad transformers"; + license = "unknown"; + hydraPlatforms = lib.platforms.none; }) {}; "unicode" = callPackage - ({ mkDerivation, base, containers, semigroups, stdenv }: + ({ mkDerivation, base, containers, lib, semigroups }: mkDerivation { pname = "unicode"; version = "0.0.1.1"; @@ -35036,69 +42248,86 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://hub.darcs.net/thielema/unicode/"; description = "Construct and transform unicode characters"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "unicode-collation" = callPackage + ({ mkDerivation, base, binary, bytestring, containers, lib, parsec + , template-haskell, text, th-lift-instances + }: + mkDerivation { + pname = "unicode-collation"; + version = "0.1.3"; + sha256 = "f11f09eb9f6cd7676e121b5ad2b6a8e9b3e99c566acdc8b6896dc724da9d7d59"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base binary bytestring containers parsec template-haskell text + th-lift-instances + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jgm/unicode-collation"; + description = "Haskell implementation of the Unicode Collation Algorithm"; + license = lib.licenses.bsd2; }) {}; "unicode-show" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "unicode-show"; - version = "0.1.0.3"; - sha256 = "3f2e33277ce6e2e3d8644fd68d945a799ff86d0cbefee05cf3441c29a1769c21"; - revision = "1"; - editedCabalFile = "0sw9kn147kbgp0x9823hwiqn1yiyfxqkrchk34lsjfx2lq3igrzv"; + version = "0.1.0.4"; + sha256 = "31d138f4c5634ce7357d3aa7e02ed28dad828ab64897ec46852ae8d3ccb61b95"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "http://github.com/haskell-jp/unicode-show#readme"; description = "print and show in unicode"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "unicode-transforms" = callPackage - ({ mkDerivation, base, bitarray, bytestring, stdenv, text }: + ({ mkDerivation, base, bytestring, ghc-prim, lib, text }: mkDerivation { pname = "unicode-transforms"; - version = "0.3.5"; - sha256 = "c9f7d138ab43ed2e11de5973b0bd771c8f5c14cc0d87d3fbd1c6980c176fa03e"; - libraryHaskellDepends = [ base bitarray bytestring text ]; + version = "0.3.7.1"; + sha256 = "8ef4dfa741ab9ebeb0fc71970ece1074554ff3387c488a7bc55f5612a1d22080"; + revision = "1"; + editedCabalFile = "01kf1hanqcwc7vpkwq2rw5v2mn4nxx58l3v5hpk166jalmwqijaz"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base bytestring ghc-prim text ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/harendra-kumar/unicode-transforms"; + homepage = "http://github.com/composewell/unicode-transforms"; description = "Unicode normalization"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "unification-fd" = callPackage - ({ mkDerivation, base, containers, logict, mtl, stdenv }: + ({ mkDerivation, base, containers, lib, logict, mtl }: mkDerivation { pname = "unification-fd"; - version = "0.10.0.1"; - sha256 = "5bf46760e6db104c57f915322b32744f7604323281f5c7dd20185f905fb51996"; + version = "0.11.1"; + sha256 = "05e84d090ccc38dde80e0f22c0b9f84a2edaa365a1196743ebb2430f541f6c77"; libraryHaskellDepends = [ base containers logict mtl ]; doHaddock = false; doCheck = false; - homepage = "http://code.haskell.org/~wren/"; + homepage = "https://wrengr.org/software/hackage.html"; description = "Simple generic unification algorithms"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "union" = callPackage - ({ mkDerivation, base, deepseq, hashable, profunctors, stdenv - , tagged, vinyl - }: + "union-angle" = callPackage + ({ mkDerivation, base, lib }: mkDerivation { - pname = "union"; - version = "0.1.2"; - sha256 = "63e9dc2901a7d857e278445ca2b03bb869ecb01264206a14319d073e39dd8ec4"; - revision = "2"; - editedCabalFile = "170dhg4z4jzi50nh4xx75r9k8zz5br7j2iqjjw2r1dx29ajqbcw9"; - libraryHaskellDepends = [ - base deepseq hashable profunctors tagged vinyl - ]; + pname = "union-angle"; + version = "0.1.0.1"; + sha256 = "94259e4ef9748b5eae3b81596229da6310ae1048c73393d6255ed0022cfd9b69"; + libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; - description = "Extensible type-safe unions"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/githubuser/union-angle#readme"; + description = "Union type that include radian angle and degree angle"; + license = lib.licenses.bsd3; }) {}; "union-find" = callPackage - ({ mkDerivation, base, containers, stdenv, transformers }: + ({ mkDerivation, base, containers, lib, transformers }: mkDerivation { pname = "union-find"; version = "0.2"; @@ -35110,72 +42339,121 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/nominolo/union-find"; description = "Efficient union and equivalence testing of sets"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "unipatterns" = callPackage + ({ mkDerivation, base, lib }: + mkDerivation { + pname = "unipatterns"; + version = "0.0.0.0"; + sha256 = "8214fc1103623026c009f8b2cee4dc366fcffbb88b3d8175bdeb119fac1a541e"; + libraryHaskellDepends = [ base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/ChrisPenner/unipatterns#readme"; + description = "Helpers which allow safe partial pattern matching in lambdas"; + license = lib.licenses.bsd3; }) {}; "uniplate" = callPackage - ({ mkDerivation, base, containers, hashable, stdenv, syb + ({ mkDerivation, base, containers, ghc-prim, hashable, lib, syb , unordered-containers }: mkDerivation { pname = "uniplate"; - version = "1.6.12"; - sha256 = "fcc60bc6b3f6e925f611646db90e6db9f05286a9363405f844df1dc15572a8b7"; + version = "1.6.13"; + sha256 = "e777c94628445556a71f135a42cf72d2cfbaccba5849cc42fbfec8b2182e3ad2"; + revision = "1"; + editedCabalFile = "1rvvzmi43gbrww0f17dzchm3g61zvm97arrfa5raljqb1mbibdy8"; libraryHaskellDepends = [ - base containers hashable syb unordered-containers + base containers ghc-prim hashable syb unordered-containers ]; doHaddock = false; doCheck = false; - homepage = "http://community.haskell.org/~ndm/uniplate/"; + homepage = "https://github.com/ndmitchell/uniplate#readme"; description = "Help writing simple, concise and fast generic operations"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "uniprot-kb" = callPackage - ({ mkDerivation, attoparsec, base, stdenv, text }: + ({ mkDerivation, attoparsec, base, lib, text }: mkDerivation { pname = "uniprot-kb"; version = "0.1.2.0"; sha256 = "d40c80522f9e70e6fe97234f362e503736ae9f520f1e10e9ab249a5cad750642"; - revision = "2"; - editedCabalFile = "1kyqbp32a9wys94rxbm5k022crpnm6fnz8w2d3anb7zch17l80qw"; + revision = "4"; + editedCabalFile = "1g4qds20lwsbn5hqrgbhb4yd5w5vx2gkw47mjvxr8z8nj20g2pii"; libraryHaskellDepends = [ attoparsec base text ]; doHaddock = false; doCheck = false; homepage = "https://github.com/biocad/uniprot-kb#readme"; description = "UniProt-KB format parser"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "uniq-deep" = callPackage - ({ mkDerivation, base, bytestring, containers, stdenv }: + ({ mkDerivation, base, bytestring, lib, unordered-containers }: mkDerivation { pname = "uniq-deep"; - version = "1.1.0.0"; - sha256 = "f8953f91cbf90c5073ca90d4e9235dbe0a399ff811709d051b037a8a7db0d38e"; + version = "1.2.1"; + sha256 = "2f8a60135f59438d7f6395ac9dcd56ff734b1e366ee77d0b0eb862b3a3f30109"; isLibrary = false; isExecutable = true; - executableHaskellDepends = [ base bytestring containers ]; + executableHaskellDepends = [ + base bytestring unordered-containers + ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/ncaq/uniq-deep"; + homepage = "https://github.com/ncaq/uniq-deep#readme"; description = "uniq-deep"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.mit; }) {}; "unique" = callPackage - ({ mkDerivation, base, ghc-prim, hashable, stdenv }: + ({ mkDerivation, base, hashable, lib }: mkDerivation { pname = "unique"; - version = "0"; - sha256 = "e3fb171b7b1787683863934df0fc082fb47c0da6972bb1839c2ee8ceb64a0a90"; - revision = "1"; - editedCabalFile = "0pq3a5y8ddgd37x21vafwxpyi079ir7k9g96y99pygmxwibkg4v8"; - libraryHaskellDepends = [ base ghc-prim hashable ]; + version = "0.0.1"; + sha256 = "6df23ca2199723332b444f6b7972ad3a3daaa5c5414e8d750caa12939bb0f4b5"; + libraryHaskellDepends = [ base hashable ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/unique/"; description = "Fully concurrent unique identifiers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "unique-logic" = callPackage + ({ mkDerivation, base, explicit-exception, lib, transformers + , utility-ht + }: + mkDerivation { + pname = "unique-logic"; + version = "0.4"; + sha256 = "1209ab415264c97030f5ddae5f6bc5171abf0f7dd93b7b807446c65dcf03ea53"; + libraryHaskellDepends = [ + base explicit-exception transformers utility-ht + ]; + doHaddock = false; + doCheck = false; + homepage = "http://hub.darcs.net/thielema/unique-logic/"; + description = "Solve simple simultaneous equations"; + license = lib.licenses.bsd3; + }) {}; + "unique-logic-tf" = callPackage + ({ mkDerivation, base, containers, data-ref, lib, semigroups + , transformers, utility-ht + }: + mkDerivation { + pname = "unique-logic-tf"; + version = "0.5.1"; + sha256 = "8b818cb19dea8ed6fbdd21795b76f3fa0dcc4416bcf5ceb4c7d6f179ea945028"; + libraryHaskellDepends = [ + base containers data-ref semigroups transformers utility-ht + ]; + doHaddock = false; + doCheck = false; + homepage = "http://hub.darcs.net/thielema/unique-logic-tf/"; + description = "Solve simple simultaneous equations"; + license = lib.licenses.bsd3; }) {}; "unit-constraint" = callPackage - ({ mkDerivation, base, constraints, stdenv }: + ({ mkDerivation, base, constraints, lib }: mkDerivation { pname = "unit-constraint"; version = "0.0.0"; @@ -35184,83 +42462,142 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Extremely simple typeclass"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "universe" = callPackage + ({ mkDerivation, lib, universe-base, universe-instances-extended + , universe-reverse-instances, universe-some + }: + mkDerivation { + pname = "universe"; + version = "1.2.1"; + sha256 = "111a3fce81558ac8076b9872397c380a9569d197da988e22384578ea667f34ed"; + libraryHaskellDepends = [ + universe-base universe-instances-extended + universe-reverse-instances universe-some + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/dmwit/universe"; + description = "A class for finite and recursively enumerable types"; + license = lib.licenses.bsd3; }) {}; "universe-base" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, containers, lib, tagged, transformers }: mkDerivation { pname = "universe-base"; - version = "1.0.2.1"; - sha256 = "07c48350afacdc0b5569f72e3d6a27a8ff3c208b7a6f22d00e149a201798bb51"; - libraryHaskellDepends = [ base ]; + version = "1.1.2"; + sha256 = "99e818321b59def4184c68fbe641b963fdf4f1654c41811260d736ecb00f4aca"; + libraryHaskellDepends = [ base containers tagged transformers ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/dmwit/universe"; + description = "A class for finite and recursively enumerable types"; + license = lib.licenses.bsd3; + }) {}; + "universe-dependent-sum" = callPackage + ({ mkDerivation, base, lib, universe-some }: + mkDerivation { + pname = "universe-dependent-sum"; + version = "1.3"; + sha256 = "65eabcaca941ce9af6fa65e0f347b77d83856bd4251c97b94b4027fd1de9983b"; + libraryHaskellDepends = [ base universe-some ]; doHaddock = false; doCheck = false; homepage = "https://github.com/dmwit/universe"; - description = "A class for finite and recursively enumerable types and some helper functions for enumerating them"; - license = stdenv.lib.licenses.bsd3; + description = "Universe instances for types from dependent-sum"; + license = lib.licenses.bsd3; }) {}; "universe-instances-base" = callPackage - ({ mkDerivation, base, containers, stdenv, universe-base }: + ({ mkDerivation, base, lib, universe-base }: mkDerivation { pname = "universe-instances-base"; - version = "1.0"; - sha256 = "a21150ee3bb71283522a573bf092c8d96b2e28a95336a95505aa4c2a067dd212"; + version = "1.1"; + sha256 = "8bb1190ef89af0ba09c354b0512fefd61f44c10a805c509550a975f68febe49d"; revision = "2"; - editedCabalFile = "0c9zxmifhy2qjvsikgm168n8k8ka8ia88ldy8qjqkz5pqknlr9sj"; - libraryHaskellDepends = [ base containers universe-base ]; + editedCabalFile = "03g5vpmmymfjx4p1l2v275vn2dknb7m91wmh01aw8f26224f7sjw"; + libraryHaskellDepends = [ base universe-base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/dmwit/universe"; description = "Universe instances for types from the base package"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "universe-instances-trans" = callPackage - ({ mkDerivation, base, mtl, stdenv, transformers, universe-base - , universe-instances-base + "universe-instances-extended" = callPackage + ({ mkDerivation, adjunctions, base, comonad, containers, lib + , universe-base }: mkDerivation { - pname = "universe-instances-trans"; - version = "1.0.0.1"; - sha256 = "0d047cf1eb4af9f2052f44f487e7d2d44c86f51b54a3cc1fc5243ad816e8310e"; + pname = "universe-instances-extended"; + version = "1.1.2"; + sha256 = "561f05c272374162f361d06a3ff1116771152a4baa63bb5106739a929962e3f9"; revision = "1"; - editedCabalFile = "0dcwgbgmbkjwzbxlncpl1b5hgjrmkl73djknjkhbnh02pysbwv69"; + editedCabalFile = "017adjf6wbw56a81l69vd0gzhlvi6n1wplh85smq7l9m98wsh4wy"; libraryHaskellDepends = [ - base mtl transformers universe-base universe-instances-base + adjunctions base comonad containers universe-base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/dmwit/universe"; + description = "Universe instances for types from selected extra packages"; + license = lib.licenses.bsd3; + }) {}; + "universe-instances-trans" = callPackage + ({ mkDerivation, base, lib, universe-base }: + mkDerivation { + pname = "universe-instances-trans"; + version = "1.1"; + sha256 = "c6aef59a7c5387c7b19efaa4f0af4d3543c9fa37f14d3789c4b5bc60563ee336"; + revision = "2"; + editedCabalFile = "0fyhcfkriq4zcvqrr33x5ywxxmpyjjy0bz78pq2x38vpgqagiz4p"; + libraryHaskellDepends = [ base universe-base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/dmwit/universe"; description = "Universe instances for types from the transformers and mtl packages"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "universe-reverse-instances" = callPackage - ({ mkDerivation, base, containers, stdenv, universe-instances-base - }: + ({ mkDerivation, base, containers, lib, universe-base }: mkDerivation { pname = "universe-reverse-instances"; - version = "1.0"; - sha256 = "e9d41cbf26eabd77587fddf69493d7ad23028303d1c1d1d2ee1de1bf3d3e8d49"; - revision = "2"; - editedCabalFile = "0cpnsip1iakwkgnwnd21gwrc8qbifzpff6agjwm34jgkq9j646k8"; + version = "1.1.1"; + sha256 = "c4127e12a6af8d8e05f87e546a57fdc0bd7b7f47eaf85d4a0f1826c998cdfb73"; + libraryHaskellDepends = [ base containers universe-base ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/dmwit/universe"; + description = "Instances of standard classes that are made possible by enumerations"; + license = lib.licenses.bsd3; + }) {}; + "universe-some" = callPackage + ({ mkDerivation, base, lib, some, template-haskell, th-abstraction + , transformers, universe-base + }: + mkDerivation { + pname = "universe-some"; + version = "1.2.1"; + sha256 = "771181fb9897b07e7662f8be271ac5671fdd5d606624a6d0e3a0a5117199bb5d"; libraryHaskellDepends = [ - base containers universe-instances-base + base some template-haskell th-abstraction transformers + universe-base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/dmwit/universe"; - description = "instances of standard classes that are made possible by enumerations"; - license = stdenv.lib.licenses.bsd3; + description = "Universe instances for Some from some"; + license = lib.licenses.bsd3; }) {}; "universum" = callPackage ({ mkDerivation, base, bytestring, containers, deepseq, ghc-prim - , hashable, microlens, microlens-mtl, mtl, safe-exceptions, stdenv + , hashable, lib, microlens, microlens-mtl, mtl, safe-exceptions , stm, text, transformers, unordered-containers, utf8-string , vector }: mkDerivation { pname = "universum"; - version = "1.5.0"; - sha256 = "53d29c4de630320c4364d37ea26a150c40e8df7faf81f69bb94372314f883f9f"; + version = "1.7.2"; + sha256 = "eb1d377c2f7bbca9dc5ed05212d6f90ab95b113177de5fcb476ef69477c147cd"; libraryHaskellDepends = [ base bytestring containers deepseq ghc-prim hashable microlens microlens-mtl mtl safe-exceptions stm text transformers @@ -35270,10 +42607,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/serokell/universum"; description = "Custom prelude used in Serokell"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "unix-bytestring" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "unix-bytestring"; version = "0.3.7.3"; @@ -35283,71 +42620,101 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://code.haskell.org/~wren/"; description = "Unix/Posix-specific functions for ByteStrings"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "unix-compat" = callPackage - ({ mkDerivation, base, stdenv, unix }: + ({ mkDerivation, base, lib, unix }: mkDerivation { pname = "unix-compat"; - version = "0.5.1"; - sha256 = "a39d0c79dd906763770b80ba5b6c5cb710e954f894350e9917de0d73f3a19c52"; + version = "0.5.3"; + sha256 = "0893b597ea0db406429d0d563506af6755728eface0e1981f9392122db88e5c8"; libraryHaskellDepends = [ base unix ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/jystic/unix-compat"; + homepage = "http://github.com/jacobstanley/unix-compat"; description = "Portable POSIX-compatibility layer"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "unix-time" = callPackage - ({ mkDerivation, base, binary, bytestring, Cabal, cabal-doctest - , old-time, stdenv - }: + ({ mkDerivation, base, binary, bytestring, lib, old-time }: mkDerivation { pname = "unix-time"; - version = "0.4.4"; - sha256 = "1d4636e664b45ec5ff3af7794c7c7a2f400017b832dad560328d69d6c53ef0c1"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "0.4.7"; + sha256 = "19233f8badf921d444c6165689253d877cfed58ce08f28cad312558a9280de09"; libraryHaskellDepends = [ base binary bytestring old-time ]; doHaddock = false; doCheck = false; description = "Unix time parser/formatter and utilities"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "unliftio" = callPackage - ({ mkDerivation, async, base, deepseq, directory, filepath, process - , stdenv, stm, time, transformers, unix, unliftio-core + ({ mkDerivation, async, base, bytestring, deepseq, directory + , filepath, lib, process, stm, time, transformers, unix + , unliftio-core }: mkDerivation { pname = "unliftio"; - version = "0.2.10"; - sha256 = "141d6e858f3c340c881d9853a38076ca09306e45a02fffc36885b9ee11cf1b5c"; + version = "0.2.18"; + sha256 = "3ef4ed7a6d4f78a0c4dc21daba310953ad56619c355091d0e1ed923bb6e8e579"; libraryHaskellDepends = [ - async base deepseq directory filepath process stm time transformers - unix unliftio-core + async base bytestring deepseq directory filepath process stm time + transformers unix unliftio-core ]; doHaddock = false; doCheck = false; homepage = "https://github.com/fpco/unliftio/tree/master/unliftio#readme"; description = "The MonadUnliftIO typeclass for unlifting monads to IO (batteries included)"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "unliftio-core" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "unliftio-core"; - version = "0.1.2.0"; - sha256 = "24c38b3d610ca2642ed496d1de3d7b6b398ce0410aa0a15f3c7ce636ba8f7a78"; + version = "0.2.0.1"; + sha256 = "919f0d1297ea2f5373118553c1df2a9405d8b9e31a8307e829da67d4953c299a"; revision = "1"; - editedCabalFile = "0s6xfg9d0i3sfil5gjbamlq017wdxa69csk73bcqjkficg43vm29"; + editedCabalFile = "16k5fxlm9xpbd0ca861nmhb1j2ahyid02m1vbg1vzb5ckbm48glv"; libraryHaskellDepends = [ base transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/fpco/unliftio/tree/master/unliftio-core#readme"; description = "The MonadUnliftIO typeclass for unlifting monads to IO"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "unliftio-pool" = callPackage + ({ mkDerivation, base, lib, resource-pool, time, transformers + , unliftio-core + }: + mkDerivation { + pname = "unliftio-pool"; + version = "0.2.1.1"; + sha256 = "bb23cd7415061792bf7b047ad7810bb9fb839430ee1db37129f993dbe8b3bd43"; + libraryHaskellDepends = [ + base resource-pool time transformers unliftio-core + ]; + doHaddock = false; + doCheck = false; + description = "Data.Pool generalized to MonadUnliftIO."; + license = lib.licenses.bsd3; + }) {}; + "unliftio-streams" = callPackage + ({ mkDerivation, base, bytestring, io-streams, lib, text + , unliftio-core + }: + mkDerivation { + pname = "unliftio-streams"; + version = "0.1.1.1"; + sha256 = "56e012fff3567b76704b2160c5a023bdf9725585b45ee1a780a4730bc2b13ee5"; + libraryHaskellDepends = [ + base bytestring io-streams text unliftio-core + ]; + doHaddock = false; + doCheck = false; + description = "Generalization of io-streams to MonadUnliftIO"; + license = lib.licenses.asl20; }) {}; "unlit" = callPackage - ({ mkDerivation, base, directory, stdenv, text }: + ({ mkDerivation, base, directory, lib, text }: mkDerivation { pname = "unlit"; version = "0.4.0.0"; @@ -35359,36 +42726,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Tool to convert literate code between styles or to code"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "unordered-containers" = callPackage - ({ mkDerivation, base, deepseq, hashable, stdenv }: + ({ mkDerivation, base, deepseq, hashable, lib }: mkDerivation { pname = "unordered-containers"; - version = "0.2.9.0"; - sha256 = "6730cb5c4a3e953e2c199d6425be08fd088ff0089a3e140d63226c052e318250"; + version = "0.2.14.0"; + sha256 = "a10f48a94cef1fab72d2a404c7d541a3cda54ab2f1321872658aca7e5e9d8867"; libraryHaskellDepends = [ base deepseq hashable ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/tibbe/unordered-containers"; + homepage = "https://github.com/haskell-unordered-containers/unordered-containers"; description = "Efficient hashing-based container types"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "unordered-intmap" = callPackage - ({ mkDerivation, base, deepseq, primitive, stdenv }: - mkDerivation { - pname = "unordered-intmap"; - version = "0.1.1"; - sha256 = "d8faaf0c23ed143942ba7948616c73134c78e02aa4cf252605c73fb2412876ef"; - libraryHaskellDepends = [ base deepseq primitive ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/ethercrow/unordered-intmap"; - description = "A specialization of `HashMap Int v`"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "unsafe" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "unsafe"; version = "0.0"; @@ -35399,16 +42753,29 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://code.haskell.org/~thielema/unsafe/"; description = "Unified interface to unsafe functions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "urbit-hob" = callPackage + ({ mkDerivation, base, bytestring, lib, murmur3, text, vector }: + mkDerivation { + pname = "urbit-hob"; + version = "0.3.3"; + sha256 = "20bb15bd845ab536cdca26c236263d5725b6fab0340b9fa58174041da55e68f0"; + libraryHaskellDepends = [ base bytestring murmur3 text vector ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/urbit/urbit-hob"; + description = "Hoon-style atom manipulation and printing functions"; + license = lib.licenses.mit; }) {}; "uri-bytestring" = callPackage ({ mkDerivation, attoparsec, base, blaze-builder, bytestring - , containers, stdenv, template-haskell, th-lift-instances + , containers, lib, template-haskell, th-lift-instances }: mkDerivation { pname = "uri-bytestring"; - version = "0.3.2.1"; - sha256 = "64bd16bed1eca66d844cbc9dfb90a7ffda5b24572066765cf61b3d8d28a1c1fc"; + version = "0.3.3.1"; + sha256 = "f3e7a0ac26111c426727fed11624efe9ce36ee2e74ca79570ec0985eb6111368"; libraryHaskellDepends = [ attoparsec base blaze-builder bytestring containers template-haskell th-lift-instances @@ -35417,16 +42784,15 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/Soostone/uri-bytestring"; description = "Haskell URI parsing as ByteStrings"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "uri-bytestring-aeson" = callPackage - ({ mkDerivation, aeson, base, bytestring, stdenv, text - , uri-bytestring + ({ mkDerivation, aeson, base, bytestring, lib, text, uri-bytestring }: mkDerivation { pname = "uri-bytestring-aeson"; - version = "0.1.0.7"; - sha256 = "7e90b5eb1c65a83461e127a27ce635f2f8279eb0d0cb14823831b6dfb503ef9b"; + version = "0.1.0.8"; + sha256 = "612accdae921dd7a5d00fedaa377d994be5ab585ae75b1f9f0dcaa10412e7509"; libraryHaskellDepends = [ aeson base bytestring text uri-bytestring ]; @@ -35434,16 +42800,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/reactormonk/uri-bytestring-aeson"; description = "Aeson instances for URI Bytestring"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "uri-encode" = callPackage - ({ mkDerivation, base, bytestring, network-uri, stdenv, text + ({ mkDerivation, base, bytestring, lib, network-uri, text , utf8-string }: mkDerivation { pname = "uri-encode"; - version = "1.5.0.5"; - sha256 = "e82b588aad63112d34f6bad6f1ef72489b9edebfe14f2f523dc1dabdcbe2b186"; + version = "1.5.0.7"; + sha256 = "c79c624257833841a22890e4d2b0ab07e4be88e0f99474d328223815c0814252"; + revision = "1"; + editedCabalFile = "172mgdd8dgy8wphgl9vbvp26lrzp01prr5jshbng4rlhpyd340p1"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -35452,32 +42820,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Unicode aware uri-encoding"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "uri-templater" = callPackage - ({ mkDerivation, ansi-wl-pprint, base, bytestring, charset - , containers, dlist, HTTP, mtl, parsers, stdenv, template-haskell - , text, time, trifecta, unordered-containers, uuid-types, vector - }: - mkDerivation { - pname = "uri-templater"; - version = "0.3.1.0"; - sha256 = "21e665ff2600b3de42b6ad01ef342b6165859dc6e66897f84a9075649f1c49c2"; - revision = "1"; - editedCabalFile = "0vl1nv40yzns9fnaz6h34x72vpfaaws8f0zm8qlr82333pxg2scw"; - libraryHaskellDepends = [ - ansi-wl-pprint base bytestring charset containers dlist HTTP mtl - parsers template-haskell text time trifecta unordered-containers - uuid-types vector - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/iand675/uri-templater"; - description = "Parsing & Quasiquoting for RFC 6570 URI Templates"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.bsd3; }) {}; "url" = callPackage - ({ mkDerivation, base, stdenv, utf8-string }: + ({ mkDerivation, base, lib, utf8-string }: mkDerivation { pname = "url"; version = "2.1.3"; @@ -35487,32 +42833,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.haskell.org/haskellwiki/Url"; description = "A library for working with URLs"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "urlpath" = callPackage - ({ mkDerivation, attoparsec-uri, base, exceptions, mmorph - , monad-control, monad-control-aligned, monad-logger, mtl, path - , path-extra, resourcet, split, stdenv, strict, text, transformers - , transformers-base, vector - }: - mkDerivation { - pname = "urlpath"; - version = "9.0.1"; - sha256 = "2fe703a9c65fcfb12ba86bcffed22dca4c4a76fc78e1271816ae46b0f6a58e29"; - libraryHaskellDepends = [ - attoparsec-uri base exceptions mmorph monad-control - monad-control-aligned monad-logger mtl path path-extra resourcet - split strict text transformers transformers-base vector - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/athanclark/urlpath#readme"; - description = "Painfully simple URL deployment"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "users" = callPackage - ({ mkDerivation, aeson, base, bcrypt, path-pieces, stdenv, text - , time + ({ mkDerivation, aeson, base, bcrypt, lib, path-pieces, text, time }: mkDerivation { pname = "users"; @@ -35527,40 +42851,27 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/agrafix/users"; description = "A library simplifying user management for web applications"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; - "users-postgresql-simple" = callPackage - ({ mkDerivation, base, bytestring, mtl, postgresql-simple, stdenv - , text, time, users, uuid + "utf8-conversions" = callPackage + ({ mkDerivation, base, bytestring, lib, text, text-short + , utf8-string }: mkDerivation { - pname = "users-postgresql-simple"; - version = "0.5.0.2"; - sha256 = "051b5d2c9c6cdeaacb6271a50ee4084cc1473de8d873825dc6d98023e96ec100"; + pname = "utf8-conversions"; + version = "0.1.0.4"; + sha256 = "9f93259090f04d8532bf262544a3adb2d68f14607a68ec132b5fda32e4d4b248"; libraryHaskellDepends = [ - base bytestring mtl postgresql-simple text time users uuid + base bytestring text text-short utf8-string ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/agrafix/users"; - description = "A PostgreSQL backend for the users package"; - license = stdenv.lib.licenses.mit; - }) {}; - "users-test" = callPackage - ({ mkDerivation, base, hspec, stdenv, text, users }: - mkDerivation { - pname = "users-test"; - version = "0.5.0.1"; - sha256 = "f68549fa0cc002b16dc55f23a73b1a423aa2e64ab584c4041252a3bb6a5cac3e"; - libraryHaskellDepends = [ base hspec text users ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/agrafix/users"; - description = "Library to test backends for the users library"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/chemirea/utf8-conversions#readme"; + description = "A string conversion library that assumes utf8"; + license = lib.licenses.bsd3; }) {}; "utf8-light" = callPackage - ({ mkDerivation, base, bytestring, ghc-prim, stdenv }: + ({ mkDerivation, base, bytestring, ghc-prim, lib }: mkDerivation { pname = "utf8-light"; version = "0.4.2"; @@ -35569,127 +42880,135 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Unicode"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "utf8-string" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "utf8-string"; - version = "1.0.1.1"; - sha256 = "fb0b9e3acbe0605bcd1c63e51f290a7bbbe6628dfa3294ff453e4235fbaef140"; - revision = "3"; - editedCabalFile = "02vhj5gykkqa2dyn7s6gn8is1b5fdn9xcqqvlls268g7cpv6rk38"; + version = "1.0.2"; + sha256 = "ee48deada7600370728c4156cb002441de770d0121ae33a68139a9ed9c19b09a"; libraryHaskellDepends = [ base bytestring ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/glguy/utf8-string/"; + homepage = "https://github.com/glguy/utf8-string/"; description = "Support for reading and writing UTF8 Strings"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "util" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "util"; - version = "0.1.11.0"; - sha256 = "8bc5a5f56cc94f17bf9460efb47e79f430c98adddaf646be22fe78980207119b"; - libraryHaskellDepends = [ base ]; + version = "0.1.17.1"; + sha256 = "471b83468c146037d82f17be3206c1ba92bc4aecc53135bd2ec25b7d44261de2"; + revision = "1"; + editedCabalFile = "16hbcmcq2674j37gl808n5i02kv0vn3nwq5l2a6v5lj0dn34nicb"; + libraryHaskellDepends = [ base transformers ]; doHaddock = false; doCheck = false; description = "Utilities"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "utility-ht" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "utility-ht"; - version = "0.0.14"; - sha256 = "69c2eee1330839cdff40fad4f68f8c7ce41ae3b46a9e1d575f589fcdcf7ceba8"; + version = "0.0.16"; + sha256 = "bce53223bb77643222331efec5d69a656c0fa2d11be6563e27bc4808a1abbb81"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; description = "Various small helper functions for Lists, Maybes, Tuples, Functions"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "uuid" = callPackage ({ mkDerivation, base, binary, bytestring, cryptohash-md5 - , cryptohash-sha1, entropy, network-info, random, stdenv, text - , time, uuid-types + , cryptohash-sha1, entropy, lib, network-info, random, text, time + , uuid-types }: mkDerivation { pname = "uuid"; - version = "1.3.13"; - sha256 = "dfac808a7026217d018b408eab18facc6a85c6183be308d4ac7877e80599b027"; - revision = "2"; - editedCabalFile = "0m185q62jkfb5jsv358nxbnrkv8y8hd0qqvgvh22wvc5g9ipz0r9"; + version = "1.3.15"; + sha256 = "f885958d8934930b7c0f9b91f980722f7f992c9383fc98f075cf9df64c800564"; libraryHaskellDepends = [ base binary bytestring cryptohash-md5 cryptohash-sha1 entropy network-info random text time uuid-types ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/hvr/uuid"; + homepage = "https://github.com/haskell-hvr/uuid"; description = "For creating, comparing, parsing and printing Universally Unique Identifiers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "uuid-types" = callPackage - ({ mkDerivation, base, binary, bytestring, deepseq, hashable - , random, stdenv, text + ({ mkDerivation, base, binary, bytestring, deepseq, hashable, lib + , random, template-haskell, text }: mkDerivation { pname = "uuid-types"; - version = "1.0.3"; - sha256 = "9276517ab24a9b06f39d6e3c33c6c2b4ace1fc2126dbc1cd9806866a6551b3fd"; - revision = "1"; - editedCabalFile = "0iwwj07gp28g357hv76k4h8pvlzamvchnw003cv3qk778pcpx201"; + version = "1.0.5"; + sha256 = "ad68b89b7a64c07dd5c250a11be2033ee929318ff51ec7b4e4b54e1b4deba7dd"; libraryHaskellDepends = [ - base binary bytestring deepseq hashable random text + base binary bytestring deepseq hashable random template-haskell + text ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/aslatter/uuid"; + homepage = "https://github.com/haskell-hvr/uuid"; description = "Type definitions for Universally Unique Identifiers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "validation" = callPackage - ({ mkDerivation, base, bifunctors, deepseq, lens, semigroupoids - , semigroups, stdenv + ({ mkDerivation, assoc, base, bifunctors, deepseq, lens, lib + , semigroupoids, semigroups }: mkDerivation { pname = "validation"; - version = "1"; - sha256 = "70455a22637983dbcf7a688ff80c05bb8bf2690d9e4523d6ca4ebcef77abb921"; - revision = "1"; - editedCabalFile = "1x1g4nannz81j1h64l1m3ancc96zc57d1bjhj1wk7bwn1xxbi5h3"; + version = "1.1.1"; + sha256 = "53615c06da0f8e0f1ff7a60aa9825d21180cc3f8d67ebb723c8e3549ef5767b7"; libraryHaskellDepends = [ - base bifunctors deepseq lens semigroupoids semigroups + assoc base bifunctors deepseq lens semigroupoids semigroups ]; doHaddock = false; doCheck = false; homepage = "https://github.com/qfpl/validation"; description = "A data-type like Either but with an accumulating Applicative"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "validation-selective" = callPackage + ({ mkDerivation, base, deepseq, lib, selective }: + mkDerivation { + pname = "validation-selective"; + version = "0.1.0.1"; + sha256 = "eb7373511c40549b3440ffeb732db86e6c098589ff183ea0a7122f507321b200"; + libraryHaskellDepends = [ base deepseq selective ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/kowainik/validation-selective"; + description = "Lighweight pure data validation based on Applicative and Selective functors"; + license = lib.licenses.mpl20; }) {}; "validity" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "validity"; - version = "0.9.0.0"; - sha256 = "78fc7728861013f828f389c3fa5ead5ce949f4450e599c4b4ceeec44007fa0e6"; + version = "0.11.0.1"; + sha256 = "5df0f66e55e5aab9ce0237a196bca0effc214983f2499cb8ebbd925b7d91d620"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "Validity typeclass"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "validity-aeson" = callPackage - ({ mkDerivation, aeson, base, stdenv, validity, validity-scientific + ({ mkDerivation, aeson, base, lib, validity, validity-scientific , validity-text, validity-unordered-containers, validity-vector }: mkDerivation { pname = "validity-aeson"; - version = "0.2.0.2"; - sha256 = "fac03d29cf3d6f72c288111b68feb3c656574a1ac616b49f40426a9daf0e1d04"; + version = "0.2.0.4"; + sha256 = "a0fef6b59ee4b6a8a5c9a7e65178fceb39a267383a86f660fae0d79ad4361dcc"; libraryHaskellDepends = [ aeson base validity validity-scientific validity-text validity-unordered-containers validity-vector @@ -35698,94 +43017,120 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "Validity instances for aeson"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "validity-bytestring" = callPackage - ({ mkDerivation, base, bytestring, stdenv, validity }: + ({ mkDerivation, base, bytestring, lib, validity }: mkDerivation { pname = "validity-bytestring"; - version = "0.4.0.0"; - sha256 = "4c86f016d2ed9721e00a85a349c5df5a28ae037787eea01731b76851b310c77d"; + version = "0.4.1.1"; + sha256 = "7db8912c29ceff3fd8943a61845f9c0738d7238ca49bce2e6f3c6bc490bd6732"; libraryHaskellDepends = [ base bytestring validity ]; doHaddock = false; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "Validity instances for bytestring"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "validity-containers" = callPackage - ({ mkDerivation, base, containers, stdenv, validity }: + ({ mkDerivation, base, containers, lib, validity }: mkDerivation { pname = "validity-containers"; - version = "0.3.1.0"; - sha256 = "39096c06200f3ce670c89d557def5dbdd0ba3f608bdc7587b057c2344b3f20b2"; + version = "0.5.0.4"; + sha256 = "8de2ac38381ecc4fd7f3bfe48b2a398de8b9e018ddf84420178d94dc80b985e3"; libraryHaskellDepends = [ base containers validity ]; doHaddock = false; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "Validity instances for containers"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "validity-path" = callPackage - ({ mkDerivation, base, filepath, path, stdenv, validity }: + ({ mkDerivation, base, filepath, lib, path, validity }: mkDerivation { pname = "validity-path"; - version = "0.3.0.2"; - sha256 = "979cda9b9fce257e4793c53e869076cbb41b9516f6a7cef2ea3edca84dc5e146"; + version = "0.4.0.1"; + sha256 = "fda2d4f9f453e2c51d62c549ce7dd39390b834558b7aa8a527a3978b9f14e002"; libraryHaskellDepends = [ base filepath path validity ]; doHaddock = false; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "Validity instances for Path"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "validity-persistent" = callPackage + ({ mkDerivation, base, hspec, lib, persistent, validity }: + mkDerivation { + pname = "validity-persistent"; + version = "0.0.0.0"; + sha256 = "cc38e8f31ef26e1d9a277181792902e568b71e4a159d006e08738e222d8f7e0a"; + libraryHaskellDepends = [ base hspec persistent validity ]; + doHaddock = false; + doCheck = false; + homepage = "http://cs-syd.eu"; + description = "Validity instances for persistent-related types"; + license = lib.licenses.mit; + }) {}; + "validity-primitive" = callPackage + ({ mkDerivation, base, lib, primitive, validity }: + mkDerivation { + pname = "validity-primitive"; + version = "0.0.0.1"; + sha256 = "3ecdef8e94f2a51b0bbcf807b22cc153eeb072f4386d4a8da388898c43f23c65"; + libraryHaskellDepends = [ base primitive validity ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/validity#readme"; + description = "Validity instances for primitive"; + license = lib.licenses.mit; }) {}; "validity-scientific" = callPackage - ({ mkDerivation, base, scientific, stdenv, validity }: + ({ mkDerivation, base, lib, scientific, validity }: mkDerivation { pname = "validity-scientific"; - version = "0.2.0.2"; - sha256 = "8132aa43307c7dcb29718b5c1ef7c2b8e0d1fb6f650c0b117b99397c34da8dc1"; + version = "0.2.0.3"; + sha256 = "773a4a35933637d0bade859dd0e8acadc781d9ccd3b057d60e7ffaaa20e5186f"; libraryHaskellDepends = [ base scientific validity ]; doHaddock = false; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "Validity instances for scientific"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "validity-text" = callPackage - ({ mkDerivation, base, bytestring, stdenv, text, validity }: + ({ mkDerivation, base, bytestring, lib, text, validity }: mkDerivation { pname = "validity-text"; - version = "0.3.1.0"; - sha256 = "edd3f26e97ea07593c3995002a7ef7670f0306bfc31213f6b49ffe1a6fbc4264"; + version = "0.3.1.1"; + sha256 = "8e951fa673b05e2e6a00d7679be177c883957949cf8c3a7f3871af7aea8eace9"; libraryHaskellDepends = [ base bytestring text validity ]; doHaddock = false; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "Validity instances for text"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "validity-time" = callPackage - ({ mkDerivation, base, stdenv, time, validity }: + ({ mkDerivation, base, lib, time, validity }: mkDerivation { pname = "validity-time"; - version = "0.2.0.2"; - sha256 = "51b24adef82f272a1060d5d0dffaa2eb1e54c0016c7dcd75631e5916df45e265"; + version = "0.4.0.0"; + sha256 = "5701b5a7d35878737c24552e51422e6a350b6e79b09577a9a8955482b8509c0a"; libraryHaskellDepends = [ base time validity ]; doHaddock = false; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "Validity instances for time"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "validity-unordered-containers" = callPackage - ({ mkDerivation, base, hashable, stdenv, unordered-containers + ({ mkDerivation, base, hashable, lib, unordered-containers , validity }: mkDerivation { pname = "validity-unordered-containers"; - version = "0.2.0.2"; - sha256 = "50547e85c80e42a90143b816b41389cca1e0fccacd8d620a09142cf65b36181b"; + version = "0.2.0.3"; + sha256 = "f20d6b20b9695379f3478b357cd7c0968c3726ef4336eb0c652b84a34e332a87"; libraryHaskellDepends = [ base hashable unordered-containers validity ]; @@ -35793,36 +43138,36 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "Validity instances for unordered-containers"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "validity-uuid" = callPackage - ({ mkDerivation, base, stdenv, uuid, validity }: + ({ mkDerivation, base, lib, uuid, validity }: mkDerivation { pname = "validity-uuid"; - version = "0.1.0.2"; - sha256 = "95dc31e68630951d6971ad5b425e88d492c7400ccd4937a42252d464d89c564c"; + version = "0.1.0.3"; + sha256 = "343529cf3d3cafb63277fe8df7154c77593903284752a2cccb5a1f50114e9fd4"; libraryHaskellDepends = [ base uuid validity ]; doHaddock = false; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "Validity instances for uuid"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "validity-vector" = callPackage - ({ mkDerivation, base, hashable, stdenv, validity, vector }: + ({ mkDerivation, base, hashable, lib, validity, vector }: mkDerivation { pname = "validity-vector"; - version = "0.2.0.2"; - sha256 = "a7cc60182c9c5c25fa64d1073c1da61e79686fea6d2b2a9cf55690e61b83ce78"; + version = "0.2.0.3"; + sha256 = "3e6c66c10220da63a9d02f77df6394a1428332295961ac948b648199e0686e49"; libraryHaskellDepends = [ base hashable validity vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/NorfairKing/validity#readme"; description = "Validity instances for vector"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "valor" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "valor"; version = "0.1.0.0"; @@ -35832,86 +43177,110 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/reygoch/valor#readme"; description = "Simple general structured validation library"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "vault" = callPackage - ({ mkDerivation, base, containers, hashable, semigroups, stdenv + ({ mkDerivation, base, containers, hashable, lib , unordered-containers }: mkDerivation { pname = "vault"; - version = "0.3.1.2"; - sha256 = "9e00e52ec0b054cfb9b1e44d8ce2eefb499cc1dcd4bcdd0d434b370d635e551c"; + version = "0.3.1.5"; + sha256 = "ac2a6b6adf58598c5c8faa931ae961a8a2aa50ddb2f0f7a2044ff6e8c3d433a0"; libraryHaskellDepends = [ - base containers hashable semigroups unordered-containers + base containers hashable unordered-containers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/HeinrichApfelmus/vault"; description = "a persistent store for values of arbitrary types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "vcs-ignore" = callPackage + ({ mkDerivation, base, containers, directory, exceptions, filepath + , Glob, lib, optparse-applicative, text + }: + mkDerivation { + pname = "vcs-ignore"; + version = "0.0.1.0"; + sha256 = "b52c81c1790ebedec940bf2df087a8ca4bde7214e8320b46bcb8bdfe37dfe47f"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base containers directory exceptions filepath Glob text + ]; + executableHaskellDepends = [ + base containers directory exceptions filepath optparse-applicative + text + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/vaclavsvejcar/vcs-ignore"; + description = "Library for handling files ignored by VCS systems"; + license = lib.licenses.bsd3; }) {}; "vec" = callPackage - ({ mkDerivation, adjunctions, base, base-compat, deepseq - , distributive, fin, hashable, lens, semigroupoids, stdenv + ({ mkDerivation, adjunctions, base, deepseq, distributive, fin + , hashable, indexed-traversable, lib, QuickCheck, semigroupoids + , transformers }: mkDerivation { pname = "vec"; - version = "0.1"; - sha256 = "be54ef0a53ff4f27a7a0f14b249d1fd47ede63c085d4c68962db24bf4ba3e054"; - revision = "3"; - editedCabalFile = "093q5qlhlia12ckhvax322lyy3sb554pg46ghabvsvx8znixw2hh"; + version = "0.4"; + sha256 = "404a56b41f8db926b8dd946a9df430b1fdec15b34671c52a43b4a6f28a64f17c"; libraryHaskellDepends = [ - adjunctions base base-compat deepseq distributive fin hashable lens - semigroupoids + adjunctions base deepseq distributive fin hashable + indexed-traversable QuickCheck semigroupoids transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/phadej/vec"; description = "Vec: length-indexed (sized) list"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "vector" = callPackage - ({ mkDerivation, base, deepseq, ghc-prim, primitive, stdenv }: + ({ mkDerivation, base, deepseq, ghc-prim, lib, primitive }: mkDerivation { pname = "vector"; - version = "0.12.0.2"; - sha256 = "52e89dacaff10bedb8653181963cae928f9674a099bb706713dae83994bbc0f3"; + version = "0.12.3.0"; + sha256 = "15f818505adda63e7f484ecdf92dbb3c1ec76a9def004c9424db8fa6bc41b703"; libraryHaskellDepends = [ base deepseq ghc-prim primitive ]; doHaddock = false; doCheck = false; homepage = "https://github.com/haskell/vector"; description = "Efficient Arrays"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "vector-algorithms" = callPackage - ({ mkDerivation, base, bytestring, primitive, stdenv, vector }: + ({ mkDerivation, base, bytestring, lib, primitive, vector }: mkDerivation { pname = "vector-algorithms"; - version = "0.8.0.1"; - sha256 = "15bcde786dcf03861946885e030d3dbe3b683e1a6fc12d7317e115084f4637fe"; + version = "0.8.0.4"; + sha256 = "76176a56778bf30a275b1089ee6db24ec6c67d92525145f8dfe215b80137af3b"; + revision = "1"; + editedCabalFile = "10zjr2cdsaxb71z9svl7h2bxrxbhr19ckqy9p2mhkvhg7ar60ixz"; libraryHaskellDepends = [ base bytestring primitive vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/erikd/vector-algorithms/"; description = "Efficient algorithms for vector arrays"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "vector-binary-instances" = callPackage - ({ mkDerivation, base, binary, stdenv, vector }: + ({ mkDerivation, base, binary, lib, vector }: mkDerivation { pname = "vector-binary-instances"; - version = "0.2.5.1"; - sha256 = "3945b99f8efd319c837700b7cef5163ee23e656e89227357e0b7a41d2a66c512"; + version = "0.2.5.2"; + sha256 = "b72e3b2109a02c75cb8f07ef0aabba0dba6ec0148e21321a0a2b2197c9a2f54d"; libraryHaskellDepends = [ base binary vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/bos/vector-binary-instances"; description = "Instances of Data.Binary for vector"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "vector-buffer" = callPackage - ({ mkDerivation, base, deepseq, stdenv, vector }: + ({ mkDerivation, base, deepseq, lib, vector }: mkDerivation { pname = "vector-buffer"; version = "0.4.1"; @@ -35920,23 +43289,23 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A buffer compatible with Data.Vector.*"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "vector-builder" = callPackage - ({ mkDerivation, base, base-prelude, semigroups, stdenv, vector }: + ({ mkDerivation, base, lib, vector }: mkDerivation { pname = "vector-builder"; - version = "0.3.6"; - sha256 = "c8562d4d5daecbebc175c5895ecc1e2796dd3dfe4a66430fcdcd8fe582baa219"; - libraryHaskellDepends = [ base base-prelude semigroups vector ]; + version = "0.3.8.2"; + sha256 = "fab14af3bd55e955b4d732d4202e222a01ca08d1181725ce189871d6cded3fbc"; + libraryHaskellDepends = [ base vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/nikita-volkov/vector-builder"; description = "Vector builder"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "vector-bytes-instances" = callPackage - ({ mkDerivation, base, bytes, stdenv, vector }: + ({ mkDerivation, base, bytes, lib, vector }: mkDerivation { pname = "vector-bytes-instances"; version = "0.1.1"; @@ -35946,11 +43315,28 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/k0001/vector-bytes-instances"; description = "Serial (from the bytes package) for Vector (from the vector package)"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "vector-circular" = callPackage + ({ mkDerivation, base, deepseq, lib, nonempty-vector, primitive + , semigroupoids, template-haskell, vector + }: + mkDerivation { + pname = "vector-circular"; + version = "0.1.3"; + sha256 = "6779e9919f36e8ce53fd48eec7ad8c3f2b0f0f9d15e6b85618a7a8d3118ce277"; + libraryHaskellDepends = [ + base deepseq nonempty-vector primitive semigroupoids + template-haskell vector + ]; + doHaddock = false; + doCheck = false; + description = "circular vectors"; + license = lib.licenses.mit; }) {}; "vector-instances" = callPackage - ({ mkDerivation, base, comonad, hashable, keys, pointed - , semigroupoids, semigroups, stdenv, vector + ({ mkDerivation, base, comonad, hashable, keys, lib, pointed + , semigroupoids, semigroups, vector }: mkDerivation { pname = "vector-instances"; @@ -35963,10 +43349,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/ekmett/vector-instances"; description = "Orphan Instances for 'Data.Vector'"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "vector-mmap" = callPackage - ({ mkDerivation, base, mmap, primitive, stdenv, vector }: + ({ mkDerivation, base, lib, mmap, primitive, vector }: mkDerivation { pname = "vector-mmap"; version = "0.0.3"; @@ -35976,43 +43362,54 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/pumpkin/vector-mmap"; description = "Memory map immutable and mutable vectors"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "vector-rotcev" = callPackage + ({ mkDerivation, base, lib, vector }: + mkDerivation { + pname = "vector-rotcev"; + version = "0.1.0.0"; + sha256 = "d278a6db3481d84cc4ba9697e33a7e9461e887bf2be347959dfbff7a2b9785ea"; + libraryHaskellDepends = [ base vector ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/Bodigrim/rotcev"; + description = "Vectors with O(1) reverse"; + license = lib.licenses.bsd3; }) {}; "vector-sized" = callPackage - ({ mkDerivation, adjunctions, base, comonad, deepseq, distributive - , finite-typelits, hashable, indexed-list-literals, primitive - , stdenv, vector + ({ mkDerivation, adjunctions, base, binary, comonad, deepseq + , distributive, finite-typelits, hashable, indexed-list-literals + , lib, primitive, vector }: mkDerivation { pname = "vector-sized"; - version = "1.2.0.0"; - sha256 = "a4c06f26a2f72d51409f24d7876d9753c03ccb1ab92c84ac29cfab0dc61a2413"; + version = "1.4.4"; + sha256 = "2d6cd33c8325c789122ae820255889de91ec00922fca88b93dafe7df59e79f66"; libraryHaskellDepends = [ - adjunctions base comonad deepseq distributive finite-typelits - hashable indexed-list-literals primitive vector + adjunctions base binary comonad deepseq distributive + finite-typelits hashable indexed-list-literals primitive vector ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/expipiplus1/vector-sized#readme"; + homepage = "https://github.com/expipiplus1/vector-sized#readme"; description = "Size tagged vectors"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "vector-space" = callPackage - ({ mkDerivation, base, Boolean, MemoTrie, NumInstances, stdenv }: + ({ mkDerivation, base, Boolean, lib, MemoTrie, NumInstances }: mkDerivation { pname = "vector-space"; - version = "0.15"; - sha256 = "6849b443dbb246fa39ac8dc645cc364ce63bd91fb0761ad759eea10eeca25c0f"; - revision = "1"; - editedCabalFile = "19549mrhg3x0d1ancrxyvrskd6p4x11iprnv0b0d84q7sc40fa8w"; + version = "0.16"; + sha256 = "0c0b2f1209f95045865b968c7aa0a25e155410b3e08cf98a6c8544e48436c79c"; libraryHaskellDepends = [ base Boolean MemoTrie NumInstances ]; doHaddock = false; doCheck = false; description = "Vector & affine spaces, linear maps, and derivatives"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "vector-split" = callPackage - ({ mkDerivation, base, stdenv, vector }: + ({ mkDerivation, base, lib, vector }: mkDerivation { pname = "vector-split"; version = "1.0.0.2"; @@ -36022,178 +43419,194 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/fhaust/vector-split"; description = "Combinator library for splitting vectors"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "vector-th-unbox" = callPackage - ({ mkDerivation, base, stdenv, template-haskell, vector }: + ({ mkDerivation, base, lib, template-haskell, vector }: mkDerivation { pname = "vector-th-unbox"; - version = "0.2.1.6"; - sha256 = "be87d4a6f1005ee2d0de6adf521e05c9e83c441568a8a8b60c79efe24ae90235"; + version = "0.2.1.9"; + sha256 = "d4e337f52fffe7c3c5b2b9fd4f9cc1a61c488aa4371a082ab27d86d4c2a87f49"; libraryHaskellDepends = [ base template-haskell vector ]; doHaddock = false; doCheck = false; + homepage = "https://github.com/tsurucapital/vector-th-unbox"; description = "Deriver for Data.Vector.Unboxed using Template Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "verbosity" = callPackage - ({ mkDerivation, base, binary, data-default-class, deepseq, stdenv + ({ mkDerivation, base, binary, deepseq, dhall, generic-lens, lib + , serialise }: mkDerivation { pname = "verbosity"; - version = "0.2.3.0"; - sha256 = "8b4ce5ab48aab17b6752dec4efba259964b7084ce10330198ae3ff7ea090f264"; - libraryHaskellDepends = [ base binary data-default-class deepseq ]; + version = "0.4.0.0"; + sha256 = "5d3a75c827d926f742154f6a50a59f40565c6c891e99f8cd813d8fa8867f5bc0"; + libraryHaskellDepends = [ + base binary deepseq dhall generic-lens serialise + ]; doHaddock = false; doCheck = false; homepage = "https://github.com/trskop/verbosity"; description = "Simple enum that encodes application verbosity"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "versions" = callPackage - ({ mkDerivation, base, deepseq, hashable, megaparsec, stdenv, text + ({ mkDerivation, base, deepseq, hashable, lib, megaparsec + , parser-combinators, text }: mkDerivation { pname = "versions"; - version = "3.5.0"; - sha256 = "9c707e3e48fdf32188641243e6a7d37dd1bfce57e076cf4b0dd3a3031558cdbc"; - revision = "1"; - editedCabalFile = "13gb4n3bdkbgf199q3px7ihaqycbx76cb8isrs3qn16n67mx5b2f"; - libraryHaskellDepends = [ base deepseq hashable megaparsec text ]; + version = "5.0.0"; + sha256 = "f92fed241d1c30ad53d4257a77b7543a07a48667be61d70e370c2bdd7694dde5"; + libraryHaskellDepends = [ + base deepseq hashable megaparsec parser-combinators text + ]; doHaddock = false; doCheck = false; - homepage = "https://gitlab.com/fosskers/versions"; + homepage = "https://github.com/fosskers/versions"; description = "Types and parsers for software version numbers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "vinyl" = callPackage - ({ mkDerivation, array, base, ghc-prim, stdenv }: + "vformat" = callPackage + ({ mkDerivation, base, containers, exceptions, lib + , template-haskell + }: mkDerivation { - pname = "vinyl"; - version = "0.10.0.1"; - sha256 = "e445737adab5a729b4424aedf36dce8c724bb7d45aaa49f8f74342ff18205df4"; - libraryHaskellDepends = [ array base ghc-prim ]; + pname = "vformat"; + version = "0.14.1.0"; + sha256 = "c9280bd23a189aac4cf3b7a1b2eb35492ddcf0936712ff743551e3866b0ae471"; + revision = "1"; + editedCabalFile = "074y0nkygj8klkpm3rpdp7z2yj9np9y6rzhc7i62j0mykd27h8hq"; + libraryHaskellDepends = [ + base containers exceptions template-haskell + ]; doHaddock = false; doCheck = false; - description = "Extensible Records"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/versioncloud/vformat#readme"; + description = "A Python str.format() like formatter"; + license = lib.licenses.bsd3; }) {}; - "vivid" = callPackage - ({ mkDerivation, base, binary, bytestring, containers, directory - , filepath, hashable, MonadRandom, mtl, network, process, random - , random-shuffle, split, stdenv, stm, time, transformers - , utf8-string, vivid-osc, vivid-supercollider + "vformat-aeson" = callPackage + ({ mkDerivation, aeson, base, bytestring, lib, scientific, text + , unordered-containers, vector, vformat }: mkDerivation { - pname = "vivid"; - version = "0.4.2.3"; - sha256 = "11c0ae576e0cd38894c5ad052c90b7bce33e81abdc6a691c0e1dbb272d4b952b"; + pname = "vformat-aeson"; + version = "0.1.0.1"; + sha256 = "3b04487cbea198464c34fda4f910c01d51ab60f6291b90749306c960cbfd43b2"; + revision = "1"; + editedCabalFile = "1p85qlv9w11mqybcf81xix0lhbgc2bzy9gw83ywci5kmd1s7a2a5"; libraryHaskellDepends = [ - base binary bytestring containers directory filepath hashable - MonadRandom mtl network process random random-shuffle split stm - time transformers utf8-string vivid-osc vivid-supercollider + aeson base bytestring scientific text unordered-containers vector + vformat ]; doHaddock = false; doCheck = false; - description = "Sound synthesis with SuperCollider"; - license = "GPL"; + homepage = "https://github.com/versioncloud/vformat-aeson#readme"; + description = "Extend vformat to Aeson datatypes"; + license = lib.licenses.bsd3; }) {}; - "vivid-osc" = callPackage - ({ mkDerivation, base, bytestring, cereal, stdenv, time }: + "vformat-time" = callPackage + ({ mkDerivation, base, lib, time, vformat }: mkDerivation { - pname = "vivid-osc"; - version = "0.5.0.0"; - sha256 = "46fb67915fdfa37db0ff620b1529caf77a19d41a71007aae2b834facc2243510"; - libraryHaskellDepends = [ base bytestring cereal time ]; + pname = "vformat-time"; + version = "0.1.0.0"; + sha256 = "66d03003395e5ab32f18b5d688f2315fb9126f7eaddbd6af0b7ed7ef7d4e6b68"; + revision = "1"; + editedCabalFile = "0i11kkr8xwrffqz6jb68xfgvsbdkfxzxmw9k1bjc42x9hidgxv47"; + libraryHaskellDepends = [ base time vformat ]; doHaddock = false; doCheck = false; - description = "Open Sound Control encode/decode"; - license = "GPL"; + homepage = "https://github.com/versioncloud/vformat-time#readme"; + description = "Extend vformat to time datatypes"; + license = lib.licenses.bsd3; }) {}; - "vivid-supercollider" = callPackage - ({ mkDerivation, base, binary, bytestring, cereal, split, stdenv - , utf8-string, vivid-osc - }: + "vinyl" = callPackage + ({ mkDerivation, array, base, deepseq, ghc-prim, lib }: mkDerivation { - pname = "vivid-supercollider"; - version = "0.4.1.2"; - sha256 = "d2a40e8f4fff13200e6ead4d6397fe31095d990f75616bf7f89dbf3fa81821cb"; - libraryHaskellDepends = [ - base binary bytestring cereal split utf8-string vivid-osc - ]; + pname = "vinyl"; + version = "0.13.3"; + sha256 = "5474a566e62d0541544b53c6185a0a55db776c9899edc4934750113d2c499356"; + libraryHaskellDepends = [ array base deepseq ghc-prim ]; doHaddock = false; doCheck = false; - description = "Implementation of SuperCollider server specifications"; - license = "GPL"; + description = "Extensible Records"; + license = lib.licenses.mit; }) {}; "void" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "void"; - version = "0.7.2"; - sha256 = "d3fffe66a03e4b53db1e459edf75ad8402385a817cae415d857ec0b03ce0cf2b"; + version = "0.7.3"; + sha256 = "53af758ddc37dc63981671e503438d02c6f64a2d8744e9bec557a894431f7317"; libraryHaskellDepends = [ base ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/void"; description = "A Haskell 98 logically uninhabited data type"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "vty" = callPackage - ({ mkDerivation, base, blaze-builder, bytestring, containers - , deepseq, directory, filepath, hashable, microlens, microlens-mtl - , microlens-th, mtl, parallel, parsec, stdenv, stm, terminfo, text - , transformers, unix, utf8-string, vector + ({ mkDerivation, ansi-terminal, base, binary, blaze-builder + , bytestring, containers, deepseq, directory, filepath, hashable + , lib, microlens, microlens-mtl, microlens-th, mtl, parallel + , parsec, stm, terminfo, text, transformers, unix, utf8-string + , vector }: mkDerivation { pname = "vty"; - version = "5.25.1"; - sha256 = "3cab792e32c59647c2bdb2785c9c9a94bdb84fc85499bb1ab488999e1c9525f4"; + version = "5.33"; + sha256 = "8959b3ed13f2e1202d78ca3fcc556034b0585e4b39d47cb2e7d5dc4939255d63"; + revision = "1"; + editedCabalFile = "1in66nd2xkb6mxxzazny900pz1xj83iqsql42c0rwk72chnnb8cd"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - base blaze-builder bytestring containers deepseq directory filepath - hashable microlens microlens-mtl microlens-th mtl parallel parsec - stm terminfo text transformers unix utf8-string vector + ansi-terminal base binary blaze-builder bytestring containers + deepseq directory filepath hashable microlens microlens-mtl + microlens-th mtl parallel parsec stm terminfo text transformers + unix utf8-string vector ]; executableHaskellDepends = [ - base containers microlens microlens-mtl mtl + base containers directory filepath microlens microlens-mtl mtl ]; doHaddock = false; doCheck = false; homepage = "https://github.com/jtdaugherty/vty"; description = "A simple terminal UI library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "wai" = callPackage - ({ mkDerivation, base, bytestring, http-types, network, stdenv - , text, transformers, vault + ({ mkDerivation, base, bytestring, http-types, lib, network, text + , vault }: mkDerivation { pname = "wai"; - version = "3.2.1.2"; - sha256 = "282351461f19fbac26aa0a7896d7ab583b4abef522fcd9aba944f1848e58234b"; + version = "3.2.3"; + sha256 = "5574d6541000988fe204d3032db87fd0a5404cdbde33ee4fa02e6006768229f8"; libraryHaskellDepends = [ - base bytestring http-types network text transformers vault + base bytestring http-types network text vault ]; doHaddock = false; doCheck = false; homepage = "https://github.com/yesodweb/wai"; description = "Web Application Interface"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "wai-app-static" = callPackage ({ mkDerivation, base, blaze-html, blaze-markup, bytestring , containers, cryptonite, directory, file-embed, filepath - , http-date, http-types, memory, mime-types, old-locale - , optparse-applicative, stdenv, template-haskell, text, time - , transformers, unix-compat, unordered-containers, wai, wai-extra - , warp, zlib + , http-date, http-types, lib, memory, mime-types, old-locale + , optparse-applicative, template-haskell, text, time, transformers + , unix-compat, unordered-containers, wai, wai-extra, warp, zlib }: mkDerivation { pname = "wai-app-static"; - version = "3.1.6.2"; - sha256 = "d0b0a566be61ef4c8f800922a71dbc4de64287f8f73782b1461cd5d294c1dc3e"; + version = "3.1.7.2"; + sha256 = "c8e7db8ddb31d2297df4cae0add63e514f2a8ef92a68541707585f8148690f8d"; + revision = "1"; + editedCabalFile = "1q7zwjasysgbp9rdp75535igd7s6mhi2bnl4pzsn6vbyfw3qnsxd"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -36210,30 +43623,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.yesodweb.com/book/web-application-interface"; description = "WAI application for static serving"; - license = stdenv.lib.licenses.mit; - }) {}; - "wai-cli" = callPackage - ({ mkDerivation, ansi-terminal, base, http-types, monads-tf - , network, options, socket-activation, stdenv, stm - , streaming-commons, unix, wai, wai-extra, warp, warp-tls - }: - mkDerivation { - pname = "wai-cli"; - version = "0.1.1"; - sha256 = "0643ebd8cbd4fcedd2076450b635d020aa2101b26e80f69ade10acd2c3252862"; - libraryHaskellDepends = [ - ansi-terminal base http-types monads-tf network options - socket-activation stm streaming-commons unix wai wai-extra warp - warp-tls - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/myfreeweb/wai-cli"; - description = "Command line runner for Wai apps (using Warp) with TLS, CGI, socket activation & graceful shutdown"; - license = stdenv.lib.licenses.publicDomain; + license = lib.licenses.mit; }) {}; "wai-conduit" = callPackage - ({ mkDerivation, base, bytestring, conduit, http-types, stdenv + ({ mkDerivation, base, bytestring, conduit, http-types, lib , transformers, wai }: mkDerivation { @@ -36247,16 +43640,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/yesodweb/wai"; description = "conduit wrappers for WAI"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "wai-cors" = callPackage ({ mkDerivation, attoparsec, base, base-unicode-symbols, bytestring - , case-insensitive, http-types, mtl, stdenv, transformers, wai + , case-insensitive, http-types, lib, mtl, transformers, wai }: mkDerivation { pname = "wai-cors"; - version = "0.2.6"; - sha256 = "cac61023184404ba5abf8d3739e51c4862561ba56f829f6f5e69dd64216aa986"; + version = "0.2.7"; + sha256 = "2597beb56ebd7148f9755ae2661c065a6c532e0a286717061861b149a51cfb81"; enableSeparateDataOutput = true; libraryHaskellDepends = [ attoparsec base base-unicode-symbols bytestring case-insensitive @@ -36266,10 +43659,30 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/larskuhtz/wai-cors"; description = "CORS for WAI"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "wai-enforce-https" = callPackage + ({ mkDerivation, base, bytestring, case-insensitive, http-types + , lib, network, text, wai + }: + mkDerivation { + pname = "wai-enforce-https"; + version = "0.0.2.1"; + sha256 = "bdbc34dc7384573d58673bb450970ad8e1bfec90cbb4595ef387a820419970d5"; + isLibrary = true; + isExecutable = true; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + base bytestring case-insensitive http-types network text wai + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/turboMaCk/wai-enforce-https"; + description = "Enforce HTTPS in Wai server app safely"; + license = lib.licenses.bsd3; }) {}; "wai-eventsource" = callPackage - ({ mkDerivation, stdenv, wai }: + ({ mkDerivation, lib, wai }: mkDerivation { pname = "wai-eventsource"; version = "3.0.0"; @@ -36279,43 +43692,63 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.yesodweb.com/book/web-application-interface"; description = "WAI support for server-sent events (deprecated)"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "wai-extra" = callPackage ({ mkDerivation, aeson, ansi-terminal, base, base64-bytestring - , bytestring, case-insensitive, containers, cookie - , data-default-class, deepseq, directory, fast-logger, http-types - , iproute, network, old-locale, resourcet, stdenv - , streaming-commons, text, time, transformers, unix, unix-compat - , vault, void, wai, wai-logger, word8, zlib + , bytestring, call-stack, case-insensitive, containers, cookie + , data-default-class, directory, fast-logger, http-types, http2 + , HUnit, iproute, lib, network, resourcet, streaming-commons, text + , time, transformers, unix, vault, wai, wai-logger, word8 }: mkDerivation { pname = "wai-extra"; - version = "3.0.24.3"; - sha256 = "41e8f93ff03947623f5b447c71806f07819e1006f8267c84fd050e89fbafc439"; + version = "3.1.6"; + sha256 = "4632108eaf51242e30c3625d942e892cad59264f8365bd1edc51b0867c856b0d"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - aeson ansi-terminal base base64-bytestring bytestring - case-insensitive containers cookie data-default-class deepseq - directory fast-logger http-types iproute network old-locale - resourcet streaming-commons text time transformers unix unix-compat - vault void wai wai-logger word8 zlib + aeson ansi-terminal base base64-bytestring bytestring call-stack + case-insensitive containers cookie data-default-class directory + fast-logger http-types http2 HUnit iproute network resourcet + streaming-commons text time transformers unix vault wai wai-logger + word8 ]; doHaddock = false; doCheck = false; homepage = "http://github.com/yesodweb/wai"; description = "Provides some basic WAI handlers and middleware"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "wai-feature-flags" = callPackage + ({ mkDerivation, aeson, base, bytestring, lib, random, text + , unordered-containers, wai, warp + }: + mkDerivation { + pname = "wai-feature-flags"; + version = "0.1.0.1"; + sha256 = "d3cac8ac0972bcf091cc60e242c9e69b0074fe6fbbd18a5a30b306f5ac269c3c"; + isLibrary = true; + isExecutable = true; + enableSeparateDataOutput = true; + libraryHaskellDepends = [ + aeson base bytestring random text unordered-containers wai + ]; + executableHaskellDepends = [ base wai warp ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jwoudenberg/wai-feature-flags#readme"; + description = "Feature flag support for WAI applications"; + license = lib.licenses.bsd3; }) {}; "wai-handler-launch" = callPackage - ({ mkDerivation, async, base, bytestring, http-types, process - , stdenv, streaming-commons, transformers, wai, warp + ({ mkDerivation, async, base, bytestring, http-types, lib, process + , streaming-commons, transformers, wai, warp }: mkDerivation { pname = "wai-handler-launch"; - version = "3.0.2.4"; - sha256 = "0e9d9c61310890380dc87807ba1285bc1ab185914be6367ea4bb0a05d3df2900"; + version = "3.0.3.1"; + sha256 = "55009b08ad5620decad37e7f8ee2a64457bf0f8e8116f8ac2a2f3216987fd8c5"; libraryHaskellDepends = [ async base bytestring http-types process streaming-commons transformers wai warp @@ -36323,16 +43756,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Launch a web app in the default browser"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "wai-logger" = callPackage ({ mkDerivation, base, byteorder, bytestring, Cabal, cabal-doctest - , fast-logger, http-types, network, stdenv, wai + , fast-logger, http-types, lib, network, wai }: mkDerivation { pname = "wai-logger"; - version = "2.3.4"; - sha256 = "93fe191310c4054ccf5ad8c431e9075646b0d2b7405faf697640461c72789600"; + version = "2.3.6"; + sha256 = "e2fbd8c74fa0a31f9ea0faa53f4ad4e588644a34d8dfc7cc50d85c245c3c7541"; setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ base byteorder bytestring fast-logger http-types network wai @@ -36340,42 +43773,44 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A logging system for WAI"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "wai-middleware-auth" = callPackage ({ mkDerivation, aeson, base, base64-bytestring, binary , blaze-builder, blaze-html, bytestring, case-insensitive, cereal , clientsession, cookie, exceptions, hoauth2, http-client , http-client-tls, http-conduit, http-reverse-proxy, http-types - , optparse-simple, regex-posix, safe-exceptions, shakespeare - , stdenv, text, unix-compat, unordered-containers, uri-bytestring - , vault, wai, wai-app-static, wai-extra, warp, yaml + , jose, lib, microlens, mtl, optparse-applicative, optparse-simple + , regex-posix, safe-exceptions, shakespeare, text, time + , unix-compat, unordered-containers, uri-bytestring, vault, wai + , wai-app-static, wai-extra, warp, yaml }: mkDerivation { pname = "wai-middleware-auth"; - version = "0.1.2.1"; - sha256 = "4199220758290dd22136fd9f53a8e0a856c217c0b8b26eb6dbf41d2ad81e7d74"; + version = "0.2.5.0"; + sha256 = "84128325af68761d819c370c34ed01349a1a2e025e7ae6a853fab4e55946db8b"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ aeson base base64-bytestring binary blaze-builder blaze-html bytestring case-insensitive cereal clientsession cookie exceptions hoauth2 http-client http-client-tls http-conduit http-reverse-proxy - http-types regex-posix safe-exceptions shakespeare text unix-compat - unordered-containers uri-bytestring vault wai wai-app-static - wai-extra yaml + http-types jose microlens mtl regex-posix safe-exceptions + shakespeare text time unix-compat unordered-containers + uri-bytestring vault wai wai-app-static wai-extra yaml ]; executableHaskellDepends = [ - base bytestring cereal clientsession optparse-simple warp + base bytestring cereal clientsession optparse-applicative + optparse-simple wai-extra warp ]; doHaddock = false; doCheck = false; description = "Authentication middleware that secures WAI application"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "wai-middleware-caching" = callPackage - ({ mkDerivation, base, blaze-builder, bytestring, http-types - , stdenv, wai + ({ mkDerivation, base, blaze-builder, bytestring, http-types, lib + , wai }: mkDerivation { pname = "wai-middleware-caching"; @@ -36388,125 +43823,116 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/yogsototh/wai-middleware-caching/tree/master/wai-middleware-caching#readme"; description = "WAI Middleware to cache things"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "wai-middleware-crowd" = callPackage - ({ mkDerivation, authenticate, base, base64-bytestring, binary - , blaze-builder, bytestring, case-insensitive, clientsession - , containers, cookie, gitrev, http-client, http-client-tls - , http-reverse-proxy, http-types, optparse-applicative, resourcet - , stdenv, template-haskell, text, time, transformers, unix-compat - , vault, wai, wai-app-static, wai-extra, warp + "wai-middleware-clacks" = callPackage + ({ mkDerivation, base, base-compat-batteries, bytestring + , case-insensitive, http-types, lib, text, wai }: mkDerivation { - pname = "wai-middleware-crowd"; - version = "0.1.4.2"; - sha256 = "1136b61a6ce7729093664b63a4ab70de73e356d34b0c7a8114b639b18626b058"; - revision = "1"; - editedCabalFile = "0qvh92p9s80kmzg5w7rga54kfqbwcrkkv5p03pd92px04j2h5lbm"; - isLibrary = true; - isExecutable = true; + pname = "wai-middleware-clacks"; + version = "0.1.0.1"; + sha256 = "0e46b6ae3118c1b7e3f414f1c2284f5b924e253fad339619472b721f7dc5a3d7"; libraryHaskellDepends = [ - authenticate base base64-bytestring binary blaze-builder bytestring - case-insensitive clientsession containers cookie http-client - http-client-tls http-types resourcet text time unix-compat vault - wai + base base-compat-batteries bytestring case-insensitive http-types + text wai ]; - executableHaskellDepends = [ - base bytestring clientsession gitrev http-client http-client-tls - http-reverse-proxy http-types optparse-applicative template-haskell - text transformers wai wai-app-static wai-extra warp + doHaddock = false; + doCheck = false; + homepage = "https://github.com/prikhi/wai-middleware-clacks#readme"; + description = "GNU Terry Pratchett - Add the X-Clacks-Overhead Header to Wai Responses"; + license = lib.licenses.bsd3; + }) {}; + "wai-middleware-prometheus" = callPackage + ({ mkDerivation, base, bytestring, clock, data-default, http-types + , lib, prometheus-client, text, wai + }: + mkDerivation { + pname = "wai-middleware-prometheus"; + version = "1.0.0"; + sha256 = "743e97b2cd3c7f0f840d4eaf647d6d02e23441e555247b1a4963b2810f660430"; + libraryHaskellDepends = [ + base bytestring clock data-default http-types prometheus-client + text wai ]; doHaddock = false; doCheck = false; - description = "Middleware and utilities for using Atlassian Crowd authentication"; - license = stdenv.lib.licenses.mit; + homepage = "https://github.com/fimad/prometheus-haskell"; + description = "WAI middlware for exposing http://prometheus.io metrics."; + license = lib.licenses.asl20; }) {}; "wai-middleware-static" = callPackage ({ mkDerivation, base, bytestring, containers, cryptonite - , directory, expiring-cache-map, filepath, http-types, memory - , mime-types, mtl, old-locale, semigroups, stdenv, text, time, wai + , directory, expiring-cache-map, filepath, http-types, lib, memory + , mime-types, old-locale, semigroups, text, time, wai }: mkDerivation { pname = "wai-middleware-static"; - version = "0.8.2"; - sha256 = "0be4e9fd5252d526334e4e5885a2a75269aaaad560282b5c383c49e4d855befc"; + version = "0.9.0"; + sha256 = "fa0b11f785f6cdfe518c2c485725396e66b0eb7acee014040220899226153a98"; revision = "1"; - editedCabalFile = "0n7i81jrjsrav8bpg31avrd18vh95l5z6bfj4fqkrdj4h1v6armi"; + editedCabalFile = "1lvinpyfyb5ryxn3g41mgg6w7l7nzyh7sylmms7nvdvaqzx7l3lv"; libraryHaskellDepends = [ base bytestring containers cryptonite directory expiring-cache-map - filepath http-types memory mime-types mtl old-locale semigroups - text time wai + filepath http-types memory mime-types old-locale semigroups text + time wai ]; doHaddock = false; doCheck = false; homepage = "https://github.com/scotty-web/wai-middleware-static"; description = "WAI middleware that serves requests to static files"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "wai-middleware-throttle" = callPackage - ({ mkDerivation, base, bytestring, bytestring-builder, cache, clock - , containers, hashable, http-types, mtl, network, safe-exceptions - , stdenv, stm, text, token-bucket, transformers, wai - }: + "wai-rate-limit" = callPackage + ({ mkDerivation, base, http-types, lib, wai }: mkDerivation { - pname = "wai-middleware-throttle"; - version = "0.3.0.0"; - sha256 = "7befb5ed84c06515dcc45891e0d8ef4f051e8d5f4411c0b0f85015071876109b"; - libraryHaskellDepends = [ - base bytestring bytestring-builder cache clock containers hashable - http-types mtl network safe-exceptions stm text token-bucket - transformers wai - ]; + pname = "wai-rate-limit"; + version = "0.1.0.0"; + sha256 = "bcc56ab147b09534fb736a12c648e77e3c8d006f46dd3ab774fe570d1cbbf6fc"; + libraryHaskellDepends = [ base http-types wai ]; doHaddock = false; doCheck = false; - description = "WAI Middleware for Request Throttling"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/mbg/wai-rate-limit#readme"; + description = "Rate limiting as WAI middleware"; + license = lib.licenses.mit; }) {}; - "wai-middleware-travisci" = callPackage - ({ mkDerivation, aeson, base, base64-bytestring, bytestring - , cryptonite, http-types, stdenv, text, transformers, vault, wai - }: + "wai-rate-limit-redis" = callPackage + ({ mkDerivation, base, bytestring, hedis, lib, wai-rate-limit }: mkDerivation { - pname = "wai-middleware-travisci"; - version = "0.1.0"; - sha256 = "bbc9f2fea4c0ee3d9a73fd13dd1a2a7ef85fc294bd311ed519c1e41a1fada828"; - revision = "1"; - editedCabalFile = "0fd99j9lyb562p3rsdb8d7swg31bwahzhgjm6afijc5f6i5awcw3"; - libraryHaskellDepends = [ - aeson base base64-bytestring bytestring cryptonite http-types text - transformers vault wai - ]; + pname = "wai-rate-limit-redis"; + version = "0.1.0.0"; + sha256 = "56ecc56ef3c949375e86ed7750325291cccc0abbc48a2c547137e09ea7e994d3"; + libraryHaskellDepends = [ base bytestring hedis wai-rate-limit ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/mitchellwrosen/wai-middleware-travisci"; - description = "WAI middleware for authenticating webhook payloads from Travis CI"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/mbg/wai-rate-limit#readme"; + description = "Redis backend for rate limiting as WAI middleware"; + license = lib.licenses.mit; }) {}; - "wai-predicates" = callPackage - ({ mkDerivation, attoparsec, base, bytestring - , bytestring-conversion, case-insensitive, cookie, http-types - , singletons, stdenv, text, transformers, vault, vector, wai + "wai-saml2" = callPackage + ({ mkDerivation, base, base64-bytestring, bytestring, c14n + , cryptonite, data-default-class, http-types, lib, mtl, text, time + , vault, wai, wai-extra, x509, x509-store, xml-conduit }: mkDerivation { - pname = "wai-predicates"; - version = "0.10.0"; - sha256 = "b7b3f6d147bbbf7a959c84235d0533763eda8fc4973b42f131fd47fe8ffbd7c2"; + pname = "wai-saml2"; + version = "0.2.1.2"; + sha256 = "94bf9e50a015c2d7917d4351347f8b063a94fae5d9420d1ebe1470a21d02a4c1"; libraryHaskellDepends = [ - attoparsec base bytestring bytestring-conversion case-insensitive - cookie http-types singletons text transformers vault vector wai + base base64-bytestring bytestring c14n cryptonite + data-default-class http-types mtl text time vault wai wai-extra + x509 x509-store xml-conduit ]; doHaddock = false; doCheck = false; - homepage = "https://gitlab.com/twittner/wai-predicates/"; - description = "WAI request predicates"; - license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; + homepage = "https://github.com/mbg/wai-saml2#readme"; + description = "SAML2 assertion validation as WAI middleware"; + license = lib.licenses.mit; }) {}; "wai-session" = callPackage ({ mkDerivation, base, blaze-builder, bytestring - , bytestring-builder, containers, cookie, entropy, http-types - , StateVar, stdenv, time, transformers, vault, wai + , bytestring-builder, containers, cookie, entropy, http-types, lib + , StateVar, time, transformers, vault, wai }: mkDerivation { pname = "wai-session"; @@ -36521,31 +43947,33 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; homepage = "https://github.com/singpolyma/wai-session"; description = "Flexible session middleware for WAI"; license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; + hydraPlatforms = lib.platforms.none; }) {}; - "wai-session-postgresql" = callPackage - ({ mkDerivation, base, bytestring, cereal, cookie, data-default - , entropy, postgresql-simple, resource-pool, stdenv, text, time - , transformers, wai, wai-session + "wai-session-redis" = callPackage + ({ mkDerivation, base, bytestring, cereal, data-default, hedis + , http-types, lib, vault, wai, wai-session, warp }: mkDerivation { - pname = "wai-session-postgresql"; - version = "0.2.1.2"; - sha256 = "39d570dd99b4dc38e7803b60b4da4bc804244ed83b3fb250a6e2191a1419ac83"; + pname = "wai-session-redis"; + version = "0.1.0.2"; + sha256 = "fac348f306f9763e94e57762001a84f757ebcee0cc9d396cbe54d1e40bd68096"; + isLibrary = true; + isExecutable = true; libraryHaskellDepends = [ - base bytestring cereal cookie data-default entropy - postgresql-simple resource-pool text time transformers wai - wai-session + base bytestring cereal data-default hedis vault wai wai-session + ]; + executableHaskellDepends = [ + base bytestring cereal data-default hedis http-types vault wai + wai-session warp ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/hce/postgresql-session#readme"; - description = "PostgreSQL backed Wai session store"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/t4ccer/wai-session-redis#readme"; + description = "Simple Redis backed wai-session backend"; + license = lib.licenses.bsd3; }) {}; "wai-slack-middleware" = callPackage - ({ mkDerivation, aeson, base, http-client, http-types, stdenv, wai - }: + ({ mkDerivation, aeson, base, http-client, http-types, lib, wai }: mkDerivation { pname = "wai-slack-middleware"; version = "0.2.0"; @@ -36553,32 +43981,14 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; libraryHaskellDepends = [ aeson base http-client http-types wai ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/psibi/wai-slack-middleware#readme"; - description = "A Slack middleware for WAI"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "wai-transformers" = callPackage - ({ mkDerivation, base, exceptions, extractable-singleton - , monad-control-aligned, stdenv, transformers, wai, wai-websockets - , websockets - }: - mkDerivation { - pname = "wai-transformers"; - version = "0.1.0"; - sha256 = "17a330c80bad8a95add5d6efb0a12c774c197a2d19f83e6b9dc08ab73d8c8592"; - libraryHaskellDepends = [ - base exceptions extractable-singleton monad-control-aligned - transformers wai wai-websockets websockets - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/athanclark/wai-transformers#readme"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/psibi/wai-slack-middleware#readme"; + description = "A Slack middleware for WAI"; + license = lib.licenses.bsd3; }) {}; "wai-websockets" = callPackage ({ mkDerivation, base, bytestring, case-insensitive, file-embed - , http-types, network, stdenv, text, transformers, wai - , wai-app-static, warp, websockets + , http-types, lib, network, text, transformers, wai, wai-app-static + , warp, websockets }: mkDerivation { pname = "wai-websockets"; @@ -36598,89 +44008,103 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/yesodweb/wai"; description = "Provide a bridge between WAI and the websockets package"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "wakame" = callPackage + ({ mkDerivation, base, lib, sop-core }: + mkDerivation { + pname = "wakame"; + version = "0.1.0.0"; + sha256 = "07c299a46eca317877418f7e49d32a113125ccefe3e14e89dbbf87a7ce3fa8f2"; + libraryHaskellDepends = [ base sop-core ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/kayhide/wakame#readme"; + description = "Functions to manipulate records"; + license = lib.licenses.bsd3; }) {}; "warp" = callPackage - ({ mkDerivation, array, async, auto-update, base, bsb-http-chunked + ({ mkDerivation, array, auto-update, base, bsb-http-chunked , bytestring, case-insensitive, containers, ghc-prim, hashable - , http-date, http-types, http2, iproute, network, simple-sendfile - , stdenv, stm, streaming-commons, text, unix, unix-compat, vault - , wai, word8 + , http-date, http-types, http2, iproute, lib, network + , simple-sendfile, stm, streaming-commons, text, time-manager, unix + , unix-compat, unliftio, vault, wai, word8, x509 }: mkDerivation { pname = "warp"; - version = "3.2.25"; - sha256 = "7e0b8f2c6f156b5969832923e16fbf87cd1ac20678c5c03ce77cb094f44a8566"; + version = "3.3.17"; + sha256 = "a05e1ca23bfa6cb19a1d385e60dac8bb2c04d35e90cf187d7be9a8cb8762a46c"; libraryHaskellDepends = [ - array async auto-update base bsb-http-chunked bytestring - case-insensitive containers ghc-prim hashable http-date http-types - http2 iproute network simple-sendfile stm streaming-commons text - unix unix-compat vault wai word8 + array auto-update base bsb-http-chunked bytestring case-insensitive + containers ghc-prim hashable http-date http-types http2 iproute + network simple-sendfile stm streaming-commons text time-manager + unix unix-compat unliftio vault wai word8 x509 ]; doHaddock = false; doCheck = false; homepage = "http://github.com/yesodweb/wai"; description = "A fast, light-weight web server for WAI applications"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "warp-tls" = callPackage ({ mkDerivation, base, bytestring, cryptonite, data-default-class - , network, stdenv, streaming-commons, tls, tls-session-manager, wai - , warp + , lib, network, streaming-commons, tls, tls-session-manager + , unliftio, wai, warp }: mkDerivation { pname = "warp-tls"; - version = "3.2.4.3"; - sha256 = "84cd511e32019ba5bef07b0e8a3550b2da06d534bf3df1673d14a5ec4a12f29d"; + version = "3.3.1"; + sha256 = "c204cd68d97a309b722b024f014e09f24b7fcdce7746974ce5af9a41411e0ecd"; libraryHaskellDepends = [ base bytestring cryptonite data-default-class network - streaming-commons tls tls-session-manager wai warp + streaming-commons tls tls-session-manager unliftio wai warp ]; doHaddock = false; doCheck = false; homepage = "http://github.com/yesodweb/wai"; description = "HTTP over TLS support for Warp via the TLS package"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "warp-tls-uid" = callPackage - ({ mkDerivation, base, bytestring, network, stdenv - , streaming-commons, unix, wai, warp, warp-tls + ({ mkDerivation, base, bytestring, data-default, lib, network + , streaming-commons, tls, unix, wai, warp, warp-tls, x509 }: mkDerivation { pname = "warp-tls-uid"; - version = "0.2.0.5"; - sha256 = "b856932108364220abbba3cdebc86740a9b7436684f39936c6dda6a8d6ed73ac"; + version = "0.2.0.6"; + sha256 = "9c78b530e5ac00984233913696351132eb48e9ea2da1d1cdadde306bd6e6bb27"; libraryHaskellDepends = [ - base bytestring network streaming-commons unix wai warp warp-tls + base bytestring data-default network streaming-commons tls unix wai + warp warp-tls x509 ]; doHaddock = false; doCheck = false; homepage = "https://github.com/YoshikuniJujo/warp-tls-uid#readme"; description = "set group and user id before running server"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "wave" = callPackage - ({ mkDerivation, base, bytestring, cereal, containers - , data-default-class, stdenv, transformers + ({ mkDerivation, base, bytestring, cereal, containers, lib + , transformers }: mkDerivation { pname = "wave"; - version = "0.1.5"; - sha256 = "250a08b0c36870fb7fd0de7714818784eed0c4ff74377746dc1842967965fe0f"; - revision = "2"; - editedCabalFile = "0zs0mw42z9xzs1r935pd5dssf0x10qbkhxlpfknv0x75n2k0azzj"; + version = "0.2.0"; + sha256 = "71a6224835cfa372b9dbf60d27f6e5402663a4090bcfdbdf611d0ffc2c7f3391"; + revision = "1"; + editedCabalFile = "19rxhnqhhv1qs35y723c15c8nifj8pakcrd09jlvg5271zg4qb0b"; enableSeparateDataOutput = true; libraryHaskellDepends = [ - base bytestring cereal containers data-default-class transformers + base bytestring cereal containers transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mrkkrp/wave"; description = "Work with WAVE and RF64 files"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "wcwidth" = callPackage - ({ mkDerivation, base, containers, stdenv }: + ({ mkDerivation, base, containers, lib }: mkDerivation { pname = "wcwidth"; version = "0.0.2"; @@ -36692,94 +44116,22 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/solidsnack/wcwidth/"; description = "Native wcwidth"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "web-routes" = callPackage - ({ mkDerivation, base, blaze-builder, bytestring, exceptions - , ghc-prim, http-types, mtl, parsec, split, stdenv, text - , utf8-string - }: - mkDerivation { - pname = "web-routes"; - version = "0.27.14.2"; - sha256 = "af8b349c5d17de1d1accc30ab0a21537414a66e9d9515852098443e1d5d1f74a"; - libraryHaskellDepends = [ - base blaze-builder bytestring exceptions ghc-prim http-types mtl - parsec split text utf8-string - ]; - doHaddock = false; - doCheck = false; - homepage = "http://www.happstack.com/docs/crashcourse/index.html#web-routes"; - description = "portable, type-safe URL routing"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "web-routes-hsp" = callPackage - ({ mkDerivation, base, hsp, stdenv, text, web-routes }: - mkDerivation { - pname = "web-routes-hsp"; - version = "0.24.6.1"; - sha256 = "ca7cf5bf026c52fee5b6af3ca173c7341cd991dcd38508d07589cc7ea8102cab"; - libraryHaskellDepends = [ base hsp text web-routes ]; - doHaddock = false; - doCheck = false; - description = "Adds XMLGenerator instance for RouteT monad"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "web-routes-wai" = callPackage - ({ mkDerivation, base, bytestring, http-types, stdenv, text, wai - , web-routes - }: - mkDerivation { - pname = "web-routes-wai"; - version = "0.24.3.1"; - sha256 = "8e1fd187686452af39929bc6b6a31319001859930744e22e2eee1fa9ad103049"; - libraryHaskellDepends = [ - base bytestring http-types text wai web-routes - ]; - doHaddock = false; - doCheck = false; - description = "Library for maintaining correctness of URLs within an application"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "web3" = callPackage - ({ mkDerivation, aeson, async, base, basement, bytestring, cereal - , cryptonite, data-default, exceptions, generics-sop, http-client - , http-client-tls, machines, memory, microlens, microlens-aeson - , microlens-mtl, microlens-th, mtl, OneTuple, parsec, relapse - , stdenv, tagged, template-haskell, text, transformers, uuid-types - , vinyl - }: - mkDerivation { - pname = "web3"; - version = "0.8.3.0"; - sha256 = "38e8810c0b85a9c467711dd03ac4e53f18971cae89c42f82a1ac451ec86e27bd"; - libraryHaskellDepends = [ - aeson async base basement bytestring cereal cryptonite data-default - exceptions generics-sop http-client http-client-tls machines memory - microlens microlens-aeson microlens-mtl microlens-th mtl OneTuple - parsec relapse tagged template-haskell text transformers uuid-types - vinyl - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/airalab/hs-web3#readme"; - description = "Ethereum API for Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "webdriver" = callPackage ({ mkDerivation, aeson, attoparsec, base, base64-bytestring - , bytestring, data-default-class, directory, directory-tree - , exceptions, filepath, http-client, http-types, lifted-base - , monad-control, network, network-uri, scientific, stdenv + , bytestring, call-stack, data-default-class, directory + , directory-tree, exceptions, filepath, http-client, http-types + , lib, lifted-base, monad-control, network, network-uri, scientific , temporary, text, time, transformers, transformers-base , unordered-containers, vector, zip-archive }: mkDerivation { pname = "webdriver"; - version = "0.8.5"; - sha256 = "a8167a8b147411a929e81727a77bc31fcd7d93424442268913fb522e1932c1be"; + version = "0.9.0.1"; + sha256 = "135950889784b9d323c70ebf7ecd75b8df194489a303d85995b1fccc7549dff0"; libraryHaskellDepends = [ - aeson attoparsec base base64-bytestring bytestring + aeson attoparsec base base64-bytestring bytestring call-stack data-default-class directory directory-tree exceptions filepath http-client http-types lifted-base monad-control network network-uri scientific temporary text time transformers @@ -36789,17 +44141,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/kallisti-dev/hs-webdriver"; description = "a Haskell client for the Selenium WebDriver protocol"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "webex-teams-api" = callPackage ({ mkDerivation, aeson, attoparsec, base, bitset-word8, bytestring - , conduit, data-default, http-conduit, network-uri - , optparse-applicative, stdenv, text, utf8-string + , conduit, data-default, http-conduit, lib, network-uri + , optparse-applicative, text, utf8-string }: mkDerivation { pname = "webex-teams-api"; - version = "0.2.0.0"; - sha256 = "7756e38bd54d4dae1f70e7343259438f98bf58ff484ebc1c798166904178a40b"; + version = "0.2.0.1"; + sha256 = "5037888573478c362245202fe681498d6509a56b5fdc75b396a333706bdf1187"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -36814,17 +44166,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/nshimaza/webex-teams-api#readme"; description = "A Haskell bindings for Webex Teams API"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "webex-teams-conduit" = callPackage ({ mkDerivation, base, bytestring, conduit, data-default - , http-client, optparse-applicative, stdenv, text, utf8-string + , http-client, lib, optparse-applicative, text, utf8-string , webex-teams-api }: mkDerivation { pname = "webex-teams-conduit"; - version = "0.2.0.0"; - sha256 = "0d7c7db689092656653d687adadeb92669b647b1d7adc2493d8ca08a87742e5d"; + version = "0.2.0.1"; + sha256 = "274f7773a523bff9d65e841152f5a9c5523ae524cfc88db3a7a608b6599ee445"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base conduit webex-teams-api ]; @@ -36836,17 +44188,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/nshimaza/webex-teams-api#readme"; description = "Conduit wrapper of Webex Teams List API"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "webex-teams-pipes" = callPackage - ({ mkDerivation, base, bytestring, data-default, http-client - , optparse-applicative, pipes, stdenv, text, utf8-string - , webex-teams-api + ({ mkDerivation, base, bytestring, data-default, http-client, lib + , optparse-applicative, pipes, text, utf8-string, webex-teams-api }: mkDerivation { pname = "webex-teams-pipes"; - version = "0.2.0.0"; - sha256 = "77fad574346613e4989997852ca5972185a6321290caa718ce081be985a33100"; + version = "0.2.0.1"; + sha256 = "8fc4e35ee395063b3297bc74e54ee48541c123bb64281fc17d0918b06dde9c24"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base pipes webex-teams-api ]; @@ -36858,10 +44209,31 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/nshimaza/webex-teams-api#readme"; description = "Pipes wrapper of Webex Teams List API"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "webgear-server" = callPackage + ({ mkDerivation, aeson, base, base64-bytestring, bytestring + , bytestring-conversion, case-insensitive, http-api-data + , http-types, lib, mtl, network, template-haskell, text + , unordered-containers, wai + }: + mkDerivation { + pname = "webgear-server"; + version = "0.2.1"; + sha256 = "50ae50b8f2497dcc04d7c466189d42e0af9fc28f67ccee298a8cd433b7e0c361"; + libraryHaskellDepends = [ + aeson base base64-bytestring bytestring bytestring-conversion + case-insensitive http-api-data http-types mtl network + template-haskell text unordered-containers wai + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/rkaippully/webgear#readme"; + description = "Composable, type-safe library to build HTTP API servers"; + license = lib.licenses.mpl20; }) {}; "webrtc-vad" = callPackage - ({ mkDerivation, base, primitive, stdenv, vector }: + ({ mkDerivation, base, lib, primitive, vector }: mkDerivation { pname = "webrtc-vad"; version = "0.1.0.3"; @@ -36870,38 +44242,39 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Easy voice activity detection"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "websockets" = callPackage - ({ mkDerivation, attoparsec, base, base64-bytestring, binary - , bytestring, bytestring-builder, case-insensitive, containers - , entropy, network, random, SHA, stdenv, streaming-commons, text + ({ mkDerivation, async, attoparsec, base, base64-bytestring, binary + , bytestring, bytestring-builder, case-insensitive, clock + , containers, entropy, lib, network, random, SHA, streaming-commons + , text }: mkDerivation { pname = "websockets"; - version = "0.12.5.2"; - sha256 = "912d256bce5d460f9185e843c9fa31c772602e6275e980bbd96e4ebda48b4c71"; + version = "0.12.7.2"; + sha256 = "84c45a5db481b4c969dddfa7d3cca257ac2a97801594f1180b596d41035122ad"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - attoparsec base base64-bytestring binary bytestring - bytestring-builder case-insensitive containers entropy network - random SHA streaming-commons text + async attoparsec base base64-bytestring binary bytestring + bytestring-builder case-insensitive clock containers entropy + network random SHA streaming-commons text ]; doHaddock = false; doCheck = false; homepage = "http://jaspervdj.be/websockets"; description = "A sensible and clean way to write WebSocket-capable servers in Haskell"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "websockets-snap" = callPackage ({ mkDerivation, base, bytestring, bytestring-builder, io-streams - , mtl, snap-core, snap-server, stdenv, websockets + , lib, mtl, snap-core, snap-server, websockets }: mkDerivation { pname = "websockets-snap"; - version = "0.10.3.0"; - sha256 = "b34a40583a2111bb44233b728095fac38b8de1ab74c027fc4ee92a65af373be4"; + version = "0.10.3.1"; + sha256 = "13afb464748b796fdb9222c07e3009d1ebeeda34e599d6b77b0bf66016fefac2"; libraryHaskellDepends = [ base bytestring bytestring-builder io-streams mtl snap-core snap-server websockets @@ -36909,68 +44282,48 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Snap integration for the websockets library"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "weeder" = callPackage - ({ mkDerivation, aeson, base, bytestring, cmdargs, deepseq - , directory, extra, filepath, foundation, hashable, process, stdenv - , text, unordered-containers, vector, yaml - }: - mkDerivation { - pname = "weeder"; - version = "1.0.8"; - sha256 = "26204eeabb0cdce707548b3be451b1947567b0a13bcfe28bbdd7f48340c09cfa"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - aeson base bytestring cmdargs deepseq directory extra filepath - foundation hashable process text unordered-containers vector yaml - ]; - executableHaskellDepends = [ base ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/ndmitchell/weeder#readme"; - description = "Detect dead code"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "weigh" = callPackage - ({ mkDerivation, base, deepseq, mtl, process, split, stdenv + ({ mkDerivation, base, deepseq, ghc, lib, mtl, process, split , temporary }: mkDerivation { pname = "weigh"; - version = "0.0.13"; - sha256 = "e4baa4b5dd90e882f83c13a3f653204d3dbb6ba285c6c6a96003a29a3ce88efa"; + version = "0.0.16"; + sha256 = "a92a19209b6e8999be21fed8c6ddad8cddf5b98352341b58d2c3e3ef4e96eb8e"; libraryHaskellDepends = [ - base deepseq mtl process split temporary + base deepseq ghc mtl process split temporary ]; doHaddock = false; doCheck = false; homepage = "https://github.com/fpco/weigh#readme"; description = "Measure allocations of a Haskell functions/values"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "wide-word" = callPackage - ({ mkDerivation, base, deepseq, ghc-prim, stdenv }: + ({ mkDerivation, base, deepseq, lib, primitive }: mkDerivation { pname = "wide-word"; - version = "0.1.0.7"; - sha256 = "2d7796a5987af65f246e12fac22d1695ea2f74a6069588f220b86bdd75a80a63"; - libraryHaskellDepends = [ base deepseq ghc-prim ]; + version = "0.1.1.2"; + sha256 = "19c9d153b5022522fee0ef8d44559002bbdc4bba96c53817396a69a1983d5283"; + revision = "2"; + editedCabalFile = "09nr9ni9vs38ldzrx3vmlm6dr2avmwx6p9wlaml0nhr6sh4lbjsr"; + libraryHaskellDepends = [ base deepseq primitive ]; doHaddock = false; doCheck = false; homepage = "https://github.com/erikd/wide-word"; description = "Data types for large but fixed width signed and unsigned integers"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; }) {}; "wikicfp-scraper" = callPackage - ({ mkDerivation, attoparsec, base, bytestring, scalpel-core, stdenv + ({ mkDerivation, attoparsec, base, bytestring, lib, scalpel-core , text, time }: mkDerivation { pname = "wikicfp-scraper"; - version = "0.1.0.9"; - sha256 = "9e3cfd6dae669c34c8037cfc0996f371799297f4d08588702399413d8a4242e2"; + version = "0.1.0.12"; + sha256 = "5d27d4e5634f809aed123a6f54955f8a95c5417936e7e470e9efe069ed7b880e"; libraryHaskellDepends = [ attoparsec base bytestring scalpel-core text time ]; @@ -36978,16 +44331,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/debug-ito/wikicfp-scraper"; description = "Scrape WikiCFP web site"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "wild-bind" = callPackage - ({ mkDerivation, base, containers, semigroups, stdenv, text + ({ mkDerivation, base, containers, lib, semigroups, text , transformers }: mkDerivation { pname = "wild-bind"; - version = "0.1.2.3"; - sha256 = "22bc0e4bd9dff23fb50869d3f3df67571cf428c7feaae6aba0b51adb09dc83b6"; + version = "0.1.2.7"; + sha256 = "40376e172ffcdd8ce742e1c8f134fcbeba4b4cbab365c7d371e9424d4440e8ee"; libraryHaskellDepends = [ base containers semigroups text transformers ]; @@ -36995,16 +44348,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/debug-ito/wild-bind"; description = "Dynamic key binding framework"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "wild-bind-x11" = callPackage - ({ mkDerivation, base, containers, fold-debounce, mtl, semigroups - , stdenv, stm, text, transformers, wild-bind, X11 + ({ mkDerivation, base, containers, fold-debounce, lib, mtl + , semigroups, stm, text, transformers, wild-bind, X11 }: mkDerivation { pname = "wild-bind-x11"; - version = "0.2.0.6"; - sha256 = "496dc4068050ff1e7fc585c6cced0b7633c0a82d6bdac6efc436b6d15b651d37"; + version = "0.2.0.13"; + sha256 = "8531e61c04886c8cfe03f87c4c3670fbe0976f474794e17bc2d8d4efa698483b"; libraryHaskellDepends = [ base containers fold-debounce mtl semigroups stm text transformers wild-bind X11 @@ -37013,71 +44366,42 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/debug-ito/wild-bind"; description = "X11-specific implementation for WildBind"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "windns" = callPackage - ({ mkDerivation, base, bytestring, deepseq, dnsapi, stdenv }: + ({ mkDerivation, base, bytestring, deepseq, dnsapi, lib }: mkDerivation { pname = "windns"; version = "0.1.0.1"; sha256 = "087fa65c99021f4233102430d554aebe114af68f6b1647ff821bcb501c0bcd04"; + revision = "3"; + editedCabalFile = "10jidn34rmv0amhw3c24pkl64q5xl3c6l9yqwcvqdn0vkbd0bf2v"; configureFlags = [ "-fallow-non-windows" ]; libraryHaskellDepends = [ base bytestring deepseq ]; librarySystemDepends = [ dnsapi ]; doHaddock = false; doCheck = false; description = "Domain Name Service (DNS) lookup via the /dnsapi.dll standard library"; - license = stdenv.lib.licenses.gpl2; + license = lib.licenses.gpl2Only; }) {inherit (pkgs) dnsapi;}; - "winery" = callPackage - ({ mkDerivation, aeson, base, bytestring, containers, cpu, hashable - , megaparsec, mtl, prettyprinter, prettyprinter-ansi-terminal - , scientific, semigroups, stdenv, text, time, transformers - , unordered-containers, vector - }: - mkDerivation { - pname = "winery"; - version = "0.3.1"; - sha256 = "fef1c0ea4228b713c5dc6067e78aba63c4fdbac43007321b68d3f879f873c3b8"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ - aeson base bytestring containers cpu hashable megaparsec mtl - prettyprinter prettyprinter-ansi-terminal scientific semigroups - text time transformers unordered-containers vector - ]; - executableHaskellDepends = [ - aeson base bytestring containers cpu hashable megaparsec mtl - prettyprinter prettyprinter-ansi-terminal scientific semigroups - text time transformers unordered-containers vector - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/fumieval/winery#readme"; - description = "Sustainable serialisation library"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "wire-streams" = callPackage - ({ mkDerivation, base, binary, binary-parsers, bytestring - , io-streams, stdenv + "witch" = callPackage + ({ mkDerivation, base, bytestring, containers, lib + , template-haskell, text, time }: mkDerivation { - pname = "wire-streams"; - version = "0.1.1.0"; - sha256 = "96dffb70c08c89589881c96f199d271b55e4a5b3cc5be0f3e24e101858e2fb27"; - revision = "1"; - editedCabalFile = "1j7gpk3k82h0kxnhpv40jmnqxpnr0v0m4lj6bhpga81vlmznr088"; + pname = "witch"; + version = "0.3.3.0"; + sha256 = "7d2f6aa87641396cfea37282c97ecab9e21f05e5b097505c4a08777fbc949371"; libraryHaskellDepends = [ - base binary binary-parsers bytestring io-streams + base bytestring containers template-haskell text time ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/winterland1989/wire-streams"; - description = "Fast binary io-streams adapter"; - license = stdenv.lib.licenses.bsd3; + description = "Convert values from one type into another"; + license = lib.licenses.isc; }) {}; "with-location" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "with-location"; version = "0.1.0"; @@ -37087,61 +44411,84 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/sol/with-location#readme"; description = "Use ImplicitParams-based source locations in a backward compatible way"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "with-utf8" = callPackage + ({ mkDerivation, base, directory, filepath, lib, process + , safe-exceptions, text, th-env + }: + mkDerivation { + pname = "with-utf8"; + version = "1.0.2.2"; + sha256 = "b8b2a59841af7cae33441d762556b699197bb705d08372685b3a45ea415ad513"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base safe-exceptions text ]; + executableHaskellDepends = [ + base directory filepath process safe-exceptions text th-env + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/serokell/haskell-with-utf8#readme"; + description = "Get your IO right on the first try"; + license = lib.licenses.mpl20; }) {}; "witherable" = callPackage - ({ mkDerivation, base, base-orphans, containers, hashable, stdenv - , transformers, transformers-compat, unordered-containers, vector + ({ mkDerivation, base, base-orphans, containers, hashable + , indexed-traversable, indexed-traversable-instances, lib + , transformers, unordered-containers, vector }: mkDerivation { pname = "witherable"; - version = "0.3"; - sha256 = "620f619d37d50e5248a985888153149531155455f037746fdeca9c2c9fdf19c0"; + version = "0.4.1"; + sha256 = "0b153f0632af584bb43b97627d2d512e054ac30f3b5b3de1d842a9d6006e42ca"; libraryHaskellDepends = [ - base base-orphans containers hashable transformers - transformers-compat unordered-containers vector + base base-orphans containers hashable indexed-traversable + indexed-traversable-instances transformers unordered-containers + vector ]; doHaddock = false; doCheck = false; homepage = "https://github.com/fumieval/witherable"; description = "filterable traversable"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "witness" = callPackage - ({ mkDerivation, base, constraints, semigroupoids, stdenv - , transformers + "within" = callPackage + ({ mkDerivation, base, comonad, exceptions, free, hashable, lib + , path, path-like }: mkDerivation { - pname = "witness"; - version = "0.4"; - sha256 = "93c6c83681a3ab94f53e49c07d0d1474e21169f779c917a896c9d6ed1bf01ea0"; + pname = "within"; + version = "0.2.0.1"; + sha256 = "2c260193316911dc2d37d6aa1732dbe723da21fa893fa8d7decf16d27ffceefb"; libraryHaskellDepends = [ - base constraints semigroupoids transformers + base comonad exceptions free hashable path path-like ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/AshleyYakeley/witness"; - description = "values that witness types"; - license = stdenv.lib.licenses.bsd3; + description = "A value within another path"; + license = lib.licenses.mit; }) {}; "wizards" = callPackage ({ mkDerivation, base, containers, control-monad-free, haskeline - , mtl, stdenv, transformers + , lib, mtl, transformers }: mkDerivation { pname = "wizards"; version = "1.0.3"; sha256 = "05650d7bf6dd0e6b87d0d7da6fb003601ce5d7b1f3d69571127ec3c9425b9bb2"; + revision = "1"; + editedCabalFile = "095qd17zrdhqmcvmslbyzfa5sh9glvvsnsvnlz31gzsmi8nnsgim"; libraryHaskellDepends = [ base containers control-monad-free haskeline mtl transformers ]; doHaddock = false; doCheck = false; description = "High level, generic library for interrogative user interfaces"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "wl-pprint-annotated" = callPackage - ({ mkDerivation, base, containers, deepseq, stdenv, text }: + ({ mkDerivation, base, containers, deepseq, lib, text }: mkDerivation { pname = "wl-pprint-annotated"; version = "0.1.0.1"; @@ -37151,10 +44498,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/minad/wl-pprint-annotated#readme"; description = "Pretty printer with annotation support"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "wl-pprint-console" = callPackage - ({ mkDerivation, base, bytestring, colorful-monoids, stdenv, text + ({ mkDerivation, base, bytestring, colorful-monoids, lib, text , wl-pprint-annotated }: mkDerivation { @@ -37168,22 +44515,22 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/minad/wl-pprint-console#readme"; description = "Wadler/Leijen pretty printer supporting colorful console output"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "wl-pprint-text" = callPackage - ({ mkDerivation, base, base-compat, stdenv, text }: + ({ mkDerivation, base, base-compat, lib, text }: mkDerivation { pname = "wl-pprint-text"; - version = "1.2.0.0"; - sha256 = "40dd4c2d2b8a2884616f3a240f01143d0aadd85f5988e5ee55a59ba6b2487c3c"; + version = "1.2.0.1"; + sha256 = "9e6efdba61da70caf85560570648ec097b88cc2b92bc1306135b93f0ff9b0c0c"; libraryHaskellDepends = [ base base-compat text ]; doHaddock = false; doCheck = false; description = "A Wadler/Leijen Pretty Printer for Text values"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "word-trie" = callPackage - ({ mkDerivation, base, binary, containers, stdenv }: + ({ mkDerivation, base, binary, containers, lib }: mkDerivation { pname = "word-trie"; version = "0.3.0"; @@ -37195,10 +44542,25 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/yi-editor/word-trie"; description = "Implementation of a finite trie over words"; - license = stdenv.lib.licenses.gpl2; + license = lib.licenses.gpl2Only; + }) {}; + "word-wrap" = callPackage + ({ mkDerivation, base, lib, text }: + mkDerivation { + pname = "word-wrap"; + version = "0.4.1"; + sha256 = "eb72f91947c0c62cb862feb33cad9efdc5e720f456fa9ca68ef8ac9d1ec42c97"; + revision = "1"; + editedCabalFile = "1k4w4g053vhmpp08542hrqaw81p3p35i567xgdarqmpghfrk68pp"; + libraryHaskellDepends = [ base text ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/jtdaugherty/word-wrap/"; + description = "A library for word-wrapping"; + license = lib.licenses.bsd3; }) {}; "word24" = callPackage - ({ mkDerivation, base, deepseq, stdenv }: + ({ mkDerivation, base, deepseq, lib }: mkDerivation { pname = "word24"; version = "2.0.1"; @@ -37208,10 +44570,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/winterland1989/word24"; description = "24-bit word and int types for GHC"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "word8" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "word8"; version = "0.1.3"; @@ -37220,24 +44582,43 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Word8 library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "world-peace" = callPackage - ({ mkDerivation, aeson, base, deepseq, profunctors, stdenv, tagged + "wordpress-auth" = callPackage + ({ mkDerivation, base, base16-bytestring, bytestring, cookie + , cryptohash-md5, cryptohash-sha256, hs-php-session, http-types + , lib, mtl, text, time, uri-encode }: + mkDerivation { + pname = "wordpress-auth"; + version = "1.0.0.1"; + sha256 = "126844d8bc9ffcd9f6e34f1b6e7a02f09dac48ad6d5d7510bce2bc052abdb981"; + libraryHaskellDepends = [ + base base16-bytestring bytestring cookie cryptohash-md5 + cryptohash-sha256 hs-php-session http-types mtl text time + uri-encode + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/prikhi/wordpress-auth#readme"; + description = "Validate Wordpress Cookies & Nonces; Build Wordpress Hashes & Salts"; + license = lib.licenses.bsd3; + }) {}; + "world-peace" = callPackage + ({ mkDerivation, aeson, base, deepseq, lib, profunctors, tagged }: mkDerivation { pname = "world-peace"; - version = "0.1.0.0"; - sha256 = "737685799cdd97c2178c749a60906d15548b040570b90f1bbb4f259ba0e756a5"; + version = "1.0.2.0"; + sha256 = "abb1ff7e54c02dddb21b37ce69b4cb5a65c619af0241d375189bd508348d2417"; libraryHaskellDepends = [ aeson base deepseq profunctors tagged ]; doHaddock = false; doCheck = false; homepage = "https://github.com/cdepillabout/world-peace"; description = "Open Union and Open Product Types"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "wrap" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "wrap"; version = "0.0.0"; @@ -37246,23 +44627,20 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Wrap a function's return value with another function"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "wreq" = callPackage ({ mkDerivation, aeson, attoparsec, authenticate-oauth, base , base16-bytestring, bytestring, Cabal, cabal-doctest , case-insensitive, containers, cryptonite, exceptions, ghc-prim , hashable, http-client, http-client-tls, http-types, lens - , lens-aeson, memory, mime-types, psqueues, stdenv - , template-haskell, text, time, time-locale-compat - , unordered-containers + , lens-aeson, lib, memory, mime-types, psqueues, template-haskell + , text, time, time-locale-compat, unordered-containers }: mkDerivation { pname = "wreq"; - version = "0.5.3.1"; - sha256 = "e33b4ea7a4008ed933744de13d98f6e8d0a54b8778ecf4e7c78812d4fb124ec4"; - revision = "1"; - editedCabalFile = "016sf02sm58fjsa7nmj12y8m2rwg34md8cnn533kdxm831jc9zyb"; + version = "0.5.3.3"; + sha256 = "bcf31dd31f7c8d023ec36170f1bb4bd187906dd277d05a15dc27838b0808657f"; isLibrary = true; isExecutable = true; setupHaskellDepends = [ base Cabal cabal-doctest ]; @@ -37277,16 +44655,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.serpentine.com/wreq"; description = "An easy-to-use HTTP client library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "writer-cps-exceptions" = callPackage - ({ mkDerivation, base, exceptions, stdenv, transformers + ({ mkDerivation, base, exceptions, lib, transformers , writer-cps-transformers }: mkDerivation { pname = "writer-cps-exceptions"; - version = "0.1.0.0"; - sha256 = "9bb4d8df625bc0822d4e2040a66f141f4ef304963bbb62e4e08720075a8184e8"; + version = "0.1.0.1"; + sha256 = "9a1a5dc53a53e19f0d0dacdcb88bbfc3cde64379413982e8581043da6cc5ee43"; libraryHaskellDepends = [ base exceptions transformers writer-cps-transformers ]; @@ -37294,67 +44672,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/minad/writer-cps-exceptions"; description = "Control.Monad.Catch instances for the stricter CPS WriterT and RWST"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "writer-cps-full" = callPackage - ({ mkDerivation, base, stdenv, writer-cps-lens, writer-cps-morph - , writer-cps-mtl, writer-cps-transformers - }: - mkDerivation { - pname = "writer-cps-full"; - version = "0.1.0.0"; - sha256 = "ba51df5149470be6d70fd179f2af4cae30824a3a63528f1549a97f57610a5e95"; - libraryHaskellDepends = [ - base writer-cps-lens writer-cps-morph writer-cps-mtl - writer-cps-transformers - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/minad/writer-cps-full#readme"; - description = "WriteT and RWST monad transformers (Reexport with all dependencies)"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "writer-cps-lens" = callPackage - ({ mkDerivation, base, lens, profunctors, stdenv, transformers - , writer-cps-mtl, writer-cps-transformers - }: - mkDerivation { - pname = "writer-cps-lens"; - version = "0.1.0.1"; - sha256 = "2d6b8b6f4f86dcb3cc75bdd25d4ab186d09c2859023f3a6ef2171576b0d306ef"; - libraryHaskellDepends = [ - base lens profunctors transformers writer-cps-mtl - writer-cps-transformers - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/louispan/writer-cps-lens#readme"; - description = "Lens instances for the stricter CPS WriterT and RWST"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "writer-cps-morph" = callPackage - ({ mkDerivation, base, mmorph, stdenv, writer-cps-transformers }: - mkDerivation { - pname = "writer-cps-morph"; - version = "0.1.0.2"; - sha256 = "e91d07b7dce83973c8ad8f489e161ea8092bd3c7d161f4e57cddeedd2f3fd5d8"; - revision = "1"; - editedCabalFile = "0dqpbpaidwa7ahk0n7pv397mv7ncr26p3vcrjh1xzl6vk26bdah5"; - libraryHaskellDepends = [ base mmorph writer-cps-transformers ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/louispan/writer-cps-morph#readme"; - description = "MFunctor instance for CPS style WriterT and RWST"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "writer-cps-mtl" = callPackage - ({ mkDerivation, base, mtl, stdenv, transformers + ({ mkDerivation, base, lib, mtl, transformers , writer-cps-transformers }: mkDerivation { pname = "writer-cps-mtl"; - version = "0.1.1.5"; - sha256 = "1557f5a4ee9d320f62acd0aee99164774327bdb3578e1f63dd695cc839de5627"; + version = "0.1.1.6"; + sha256 = "06f9fb60dc41ad26f3d18089a0b7ff1e1aeb15dc862508c59b6b577c0914dd36"; libraryHaskellDepends = [ base mtl transformers writer-cps-transformers ]; @@ -37362,67 +44689,58 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/minad/writer-cps-mtl#readme"; description = "MonadWriter orphan instances for writer-cps-transformers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "writer-cps-transformers" = callPackage - ({ mkDerivation, base, stdenv, transformers }: + ({ mkDerivation, base, lib, transformers }: mkDerivation { pname = "writer-cps-transformers"; - version = "0.1.1.4"; - sha256 = "d6f08b4e20399cec93d8f61fd99c2fbaf0abb67364c4a9f713c5fdab110185fd"; + version = "0.5.6.1"; + sha256 = "76eacf1c3df8f86b6d11507219d7e840d7fb2898f53959aa3dad40791b8f321c"; libraryHaskellDepends = [ base transformers ]; doHaddock = false; doCheck = false; homepage = "https://github.com/minad/writer-cps-transformers#readme"; description = "WriteT and RWST monad transformers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "ws" = callPackage - ({ mkDerivation, async, attoparsec, attoparsec-uri, base - , bytestring, exceptions, haskeline, mtl, network - , optparse-applicative, stdenv, strict, text, vector, websockets - , wuss + "wss-client" = callPackage + ({ mkDerivation, base, bytestring, http-client, http-client-tls + , lib, network-uri, websockets }: mkDerivation { - pname = "ws"; - version = "0.0.5"; - sha256 = "a62b1f08248b401bc532fbbc6dca6e75b1605988c83bcc9e4488d6f305f644e2"; + pname = "wss-client"; + version = "0.3.0.0"; + sha256 = "a8211bf7aa3e2597b4acb88bfcb18d49cbebd51bcaebdb1fc1cd416fa1f52cd2"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - async attoparsec-uri base bytestring exceptions haskeline mtl - network text websockets wuss - ]; - executableHaskellDepends = [ - async attoparsec attoparsec-uri base bytestring exceptions - haskeline mtl network optparse-applicative strict text vector - websockets wuss + base bytestring http-client http-client-tls network-uri websockets ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/athanclark/ws#readme"; - description = "A simple CLI utility for interacting with a websocket"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/iij-ii/direct-hs/tree/master/wss-client"; + description = "A-little-higher-level WebSocket client"; + license = lib.licenses.bsd3; }) {}; "wuss" = callPackage - ({ mkDerivation, base, bytestring, connection, network, stdenv + ({ mkDerivation, base, bytestring, connection, lib, network , websockets }: mkDerivation { pname = "wuss"; - version = "1.1.11"; - sha256 = "e06ee98d38d2083f76d82b21ac6d249610102e8f8a828c8a04ab950c507c98d6"; + version = "1.1.18"; + sha256 = "8e88fc3e678c7ead3ffe463e5c48431f5d5496b65d226e0a8601ea077098bd45"; libraryHaskellDepends = [ base bytestring connection network websockets ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/tfausak/wuss#readme"; description = "Secure WebSocket (WSS) clients"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "x11-xim" = callPackage - ({ mkDerivation, base, stdenv, utf8-string, X11 }: + ({ mkDerivation, base, lib, utf8-string, X11 }: mkDerivation { pname = "x11-xim"; version = "0.0.9.0"; @@ -37434,12 +44752,12 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/YoshikuniJujo/x11-xim_haskell/wiki/"; description = "A binding to the xim of X11 graphics library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "x509" = callPackage ({ mkDerivation, asn1-encoding, asn1-parse, asn1-types, base - , bytestring, containers, cryptonite, hourglass, memory, mtl, pem - , stdenv + , bytestring, containers, cryptonite, hourglass, lib, memory, mtl + , pem }: mkDerivation { pname = "x509"; @@ -37455,12 +44773,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/vincenthz/hs-certificate"; description = "X509 reader and writer"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "x509-store" = callPackage ({ mkDerivation, asn1-encoding, asn1-types, base, bytestring - , containers, cryptonite, directory, filepath, mtl, pem, stdenv - , x509 + , containers, cryptonite, directory, filepath, lib, mtl, pem, x509 }: mkDerivation { pname = "x509-store"; @@ -37476,11 +44793,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/vincenthz/hs-certificate"; description = "X.509 collection accessing and storing methods"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "x509-system" = callPackage ({ mkDerivation, base, bytestring, containers, directory, filepath - , mtl, pem, process, stdenv, x509, x509-store + , lib, mtl, pem, process, x509, x509-store }: mkDerivation { pname = "x509-system"; @@ -37494,12 +44811,12 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/vincenthz/hs-certificate"; description = "Handle per-operating-system X.509 accessors and storage"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "x509-validation" = callPackage ({ mkDerivation, asn1-encoding, asn1-types, base, bytestring - , containers, cryptonite, data-default-class, hourglass, memory - , mtl, pem, stdenv, x509, x509-store + , containers, cryptonite, data-default-class, hourglass, lib + , memory, mtl, pem, x509, x509-store }: mkDerivation { pname = "x509-validation"; @@ -37513,10 +44830,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/vincenthz/hs-certificate"; description = "X.509 Certificate and CRL validation"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "xdg-basedir" = callPackage - ({ mkDerivation, base, directory, filepath, stdenv }: + ({ mkDerivation, base, directory, filepath, lib }: mkDerivation { pname = "xdg-basedir"; version = "0.2.2"; @@ -37526,85 +44843,54 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/willdonnelly/xdg-basedir"; description = "A basic implementation of the XDG Base Directory specification"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; - "xeno" = callPackage - ({ mkDerivation, array, base, bytestring, deepseq, hspec, mtl - , mutable-containers, stdenv, vector + "xdg-userdirs" = callPackage + ({ mkDerivation, base, containers, directory, filepath, lib + , xdg-basedir }: mkDerivation { - pname = "xeno"; - version = "0.3.5.1"; - sha256 = "c054d631fc0a7258cda979087d462e647a38e8442d0932d6463161407191bbad"; + pname = "xdg-userdirs"; + version = "0.1.0.2"; + sha256 = "88aabbcb80dee5b669ad533af20000d561e6fe59ab1014ccc2482055d0a8046e"; libraryHaskellDepends = [ - array base bytestring deepseq hspec mtl mutable-containers vector + base containers directory filepath xdg-basedir ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/ocramz/xeno"; - description = "A fast event-based XML parser in pure Haskell"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "xenstore" = callPackage - ({ mkDerivation, base, bytestring, cereal, mtl, network, stdenv }: - mkDerivation { - pname = "xenstore"; - version = "0.1.1"; - sha256 = "c2b538c9ce6716f4a1b4c0cb63ed5c6e5ee3e69e80dbb7826ee7f5392f45e874"; - isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ base bytestring cereal mtl network ]; - doHaddock = false; - doCheck = false; - description = "Xenstore client access"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "xhtml" = callPackage - ({ mkDerivation, base, stdenv }: - mkDerivation { - pname = "xhtml"; - version = "3000.2.2.1"; - sha256 = "5cc869013ecc07ff68b3f873c0ab7f03b943fd7fa16d6f8725d4601b2f9f6924"; - libraryHaskellDepends = [ base ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/haskell/xhtml"; - description = "An XHTML combinator library"; - license = stdenv.lib.licenses.bsd3; + homepage = "http://redmine.iportnov.ru/projects/xdg-userdirs"; + description = "Basic implementation of XDG user directories specification"; + license = lib.licenses.bsd3; }) {}; - "xls" = callPackage - ({ mkDerivation, base, conduit, filepath, getopt-generics - , resourcet, stdenv, transformers + "xeno" = callPackage + ({ mkDerivation, array, base, bytestring, deepseq, lib, mtl + , mutable-containers, vector }: mkDerivation { - pname = "xls"; - version = "0.1.1"; - sha256 = "097711246a78389bdde19484d422ffb2248d46ab62248e4ca653c50e12ff0928"; - isLibrary = true; - isExecutable = true; + pname = "xeno"; + version = "0.4.2"; + sha256 = "b288d929d5e6e68b06745a61bbccb300264b69a7bc04619af05c46ef0ffc7237"; + enableSeparateDataOutput = true; libraryHaskellDepends = [ - base conduit filepath resourcet transformers - ]; - executableHaskellDepends = [ - base conduit getopt-generics resourcet transformers + array base bytestring deepseq mtl mutable-containers vector ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/harendra-kumar/xls"; - description = "Parse Microsoft Excel xls files (BIFF/Excel 97-2004)"; - license = stdenv.lib.licenses.bsd3; + homepage = "https://github.com/ocramz/xeno"; + description = "A fast event-based XML parser in pure Haskell"; + license = lib.licenses.bsd3; }) {}; "xlsx" = callPackage ({ mkDerivation, attoparsec, base, base64-bytestring, binary-search , bytestring, conduit, containers, data-default, deepseq, errors - , extra, filepath, lens, mtl, network-uri, old-locale, safe, stdenv + , extra, filepath, lens, lib, mtl, network-uri, old-locale, safe , text, time, transformers, vector, xeno, xml-conduit, zip-archive , zlib }: mkDerivation { pname = "xlsx"; - version = "0.7.2"; - sha256 = "b2560467ea5639d7bbd97ecf492f2e2cc9fa34e0b05fc5d55243304bbe7f1103"; + version = "0.8.4"; + sha256 = "81d06b3cf0bb3cae485b7e2f773e358beb4e743a55782d33e54f7c8f2f4ebf76"; libraryHaskellDepends = [ attoparsec base base64-bytestring binary-search bytestring conduit containers data-default deepseq errors extra filepath lens mtl @@ -37615,11 +44901,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/qrilka/xlsx"; description = "Simple and incomplete Excel file parser/writer"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "xlsx-tabular" = callPackage ({ mkDerivation, aeson, base, bytestring, containers, data-default - , lens, stdenv, text, xlsx + , lens, lib, text, xlsx }: mkDerivation { pname = "xlsx-tabular"; @@ -37632,24 +44918,26 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/kkazuo/xlsx-tabular"; description = "Xlsx table cell value extraction utility"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "xml" = callPackage - ({ mkDerivation, base, bytestring, stdenv, text }: + ({ mkDerivation, base, bytestring, lib, text }: mkDerivation { pname = "xml"; version = "1.3.14"; sha256 = "32d1a1a9f21a59176d84697f96ae3a13a0198420e3e4f1c48abbab7d2425013d"; + revision = "2"; + editedCabalFile = "15cxa19dp8nqvrrp0bmndkdas2jzg573x8ri75r6kiv8r4vkv8y7"; libraryHaskellDepends = [ base bytestring text ]; doHaddock = false; doCheck = false; - homepage = "http://code.galois.com"; + homepage = "https://github.com/GaloisInc/xml"; description = "A simple XML library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "xml-basic" = callPackage ({ mkDerivation, base, containers, data-accessor - , explicit-exception, semigroups, stdenv, utility-ht + , explicit-exception, lib, semigroups, utility-ht }: mkDerivation { pname = "xml-basic"; @@ -37662,18 +44950,19 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Basics for XML/HTML representation and processing"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "xml-conduit" = callPackage ({ mkDerivation, attoparsec, base, blaze-html, blaze-markup - , bytestring, conduit, conduit-extra, containers - , data-default-class, deepseq, resourcet, stdenv, text + , bytestring, Cabal, cabal-doctest, conduit, conduit-extra + , containers, data-default-class, deepseq, lib, resourcet, text , transformers, xml-types }: mkDerivation { pname = "xml-conduit"; - version = "1.8.0.1"; - sha256 = "980b2f13ab8f54d8c2cbf92d186d5fac6c6ead42197c6687bd81e2fea2afef9c"; + version = "1.9.1.1"; + sha256 = "bdb117606c0b56ca735564465b14b50f77f84c9e52e31d966ac8d4556d3ff0ff"; + setupHaskellDepends = [ base Cabal cabal-doctest ]; libraryHaskellDepends = [ attoparsec base blaze-html blaze-markup bytestring conduit conduit-extra containers data-default-class deepseq resourcet text @@ -37683,31 +44972,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/snoyberg/xml"; description = "Pure-Haskell utilities for dealing with XML with the conduit package"; - license = stdenv.lib.licenses.mit; - }) {}; - "xml-conduit-parse" = callPackage - ({ mkDerivation, base, conduit, conduit-parse, containers - , exceptions, parsers, stdenv, text, xml-conduit, xml-types - }: - mkDerivation { - pname = "xml-conduit-parse"; - version = "0.3.1.2"; - sha256 = "c1aae117720128195dbbf2ce196271e4ca2973163c6a03a1b0ead3b32f936308"; - revision = "1"; - editedCabalFile = "0jnnr4z3c6rq2dz0ldiic5zwkrp36igf6gip11qrm9ss2pk9khbl"; - libraryHaskellDepends = [ - base conduit conduit-parse containers exceptions parsers text - xml-conduit xml-types - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/k0ral/xml-conduit-parse"; - description = "Streaming XML parser based on conduits"; - license = "unknown"; - hydraPlatforms = stdenv.lib.platforms.none; + license = lib.licenses.mit; }) {}; "xml-conduit-writer" = callPackage - ({ mkDerivation, base, containers, data-default, dlist, mtl, stdenv + ({ mkDerivation, base, containers, data-default, dlist, lib, mtl , text, xml-conduit, xml-types }: mkDerivation { @@ -37721,16 +44989,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://bitbucket.org/dpwiz/xml-conduit-writer"; description = "Warm and fuzzy creation of XML documents"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "xml-hamlet" = callPackage - ({ mkDerivation, base, containers, parsec, shakespeare, stdenv + ({ mkDerivation, base, containers, lib, parsec, shakespeare , template-haskell, text, xml-conduit }: mkDerivation { pname = "xml-hamlet"; - version = "0.5.0"; - sha256 = "7bcec0aad83e72c2870efd3327553b3d78f6332cf01c12ad4b67c02f499015a3"; + version = "0.5.0.1"; + sha256 = "920ed9736117c09bcec04133beaa14dc05d7c413ee14f49c6aa9707ebc64304b"; libraryHaskellDepends = [ base containers parsec shakespeare template-haskell text xml-conduit @@ -37739,11 +45007,24 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.yesodweb.com/"; description = "Hamlet-style quasiquoter for XML content"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "xml-helpers" = callPackage + ({ mkDerivation, base, lib, xml }: + mkDerivation { + pname = "xml-helpers"; + version = "1.0.0"; + sha256 = "9b02c5bfd831e4e275745a3ca521a528a64ab0cf84022e17344873548f043367"; + libraryHaskellDepends = [ base xml ]; + doHaddock = false; + doCheck = false; + homepage = "http://github.com/acw/xml-helpers"; + description = "Some useful helper functions for the xml library"; + license = lib.licenses.bsd3; }) {}; "xml-html-qq" = callPackage ({ mkDerivation, base, blaze-markup, conduit, data-default - , from-sum, heterocephalus, html-conduit, resourcet, stdenv + , from-sum, heterocephalus, html-conduit, lib, resourcet , template-haskell, text, th-lift, th-lift-instances, xml-conduit }: mkDerivation { @@ -37759,10 +45040,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/cdepillabout/xml-html-qq"; description = "Quasi-quoters for XML and HTML Documents"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "xml-indexed-cursor" = callPackage - ({ mkDerivation, base, bytestring, containers, data-default, stdenv + ({ mkDerivation, base, bytestring, containers, data-default, lib , text, xml-conduit }: mkDerivation { @@ -37776,37 +45057,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/cdepillabout/xml-indexed-cursor"; description = "Indexed XML cursors similar to 'Text.XML.Cursor' from xml-conduit"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "xml-isogen" = callPackage - ({ mkDerivation, base, deepseq, dom-parser, lens, mtl, QuickCheck - , semigroups, stdenv, template-haskell, text, xml-conduit - , xml-conduit-writer - }: - mkDerivation { - pname = "xml-isogen"; - version = "0.3.0"; - sha256 = "9f812d7bb5dd280e62f5013fd77af27e3710fb1a76dcf7a12f0abbfae5400a17"; - libraryHaskellDepends = [ - base deepseq dom-parser lens mtl QuickCheck semigroups - template-haskell text xml-conduit xml-conduit-writer - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/typeable/xml-isogen"; - description = "Generate XML-isomorphic types"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.bsd3; }) {}; "xml-lens" = callPackage - ({ mkDerivation, base, case-insensitive, containers, lens, stdenv + ({ mkDerivation, base, case-insensitive, containers, lens, lib , text, xml-conduit }: mkDerivation { pname = "xml-lens"; - version = "0.1.6.3"; - sha256 = "4dd7f1a91fbb12ae52d5a14badd9f38c0f0d7556f08ee77d79a67cc546dcb1e8"; + version = "0.3"; + sha256 = "bf112458f5d040639c39ff1f6c7047799df29cf99f5f47e54e70baf3b5106bc4"; revision = "1"; - editedCabalFile = "1fbk4wv7zr10wsh8a0svd799im64fybnlb09rjpfl2pvb6i6h1qs"; + editedCabalFile = "0is48y2k6lsdwd2cqwvhxfjs7q5qccis8vcmw7cws18cb7vjks1x"; libraryHaskellDepends = [ base case-insensitive containers lens text xml-conduit ]; @@ -37814,10 +45076,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/fumieval/xml-lens"; description = "Lenses, traversals, and prisms for xml-conduit"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "xml-picklers" = callPackage - ({ mkDerivation, base, containers, stdenv, text, xml-types }: + ({ mkDerivation, base, containers, lib, text, xml-types }: mkDerivation { pname = "xml-picklers"; version = "0.3.6"; @@ -37826,12 +45088,12 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "XML picklers based on xml-types, ported from hexpat-pickle"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "xml-to-json" = callPackage ({ mkDerivation, aeson, base, bytestring, containers, curl - , hashable, hxt, hxt-curl, hxt-expat, hxt-tagsoup, regex-posix - , stdenv, tagsoup, text, unordered-containers, vector + , hashable, hxt, hxt-curl, hxt-expat, hxt-tagsoup, lib, regex-posix + , tagsoup, text, unordered-containers, vector }: mkDerivation { pname = "xml-to-json"; @@ -37849,96 +45111,66 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/sinelaw/xml-to-json"; description = "Library and command line tool for converting XML files to json"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "xml-to-json-fast" = callPackage - ({ mkDerivation, base, directory, process, stdenv, tagsoup, text }: + ({ mkDerivation, base, directory, lib, process, tagsoup, text }: mkDerivation { pname = "xml-to-json-fast"; version = "2.0.0"; sha256 = "dd852fe1aa54db3c6d87a2e74b5345b0f14effdd49bad5b73d79571e1b47563f"; isLibrary = true; - isExecutable = true; - libraryHaskellDepends = [ base tagsoup text ]; - executableHaskellDepends = [ base directory process ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/sinelaw/xml-to-json-fast"; - description = "Fast, light converter of xml to json capable of handling huge xml files"; - license = stdenv.lib.licenses.mit; - }) {}; - "xml-types" = callPackage - ({ mkDerivation, base, deepseq, stdenv, text }: - mkDerivation { - pname = "xml-types"; - version = "0.3.6"; - sha256 = "9937d440072552c03c6d8ad79f61e61467dc28dcd5adeaad81038b9b94eef8c9"; - libraryHaskellDepends = [ base deepseq text ]; - doHaddock = false; - doCheck = false; - homepage = "https://john-millikin.com/software/haskell-xml/"; - description = "Basic types for representing XML"; - license = stdenv.lib.licenses.mit; - }) {}; - "xmlbf" = callPackage - ({ mkDerivation, base, bytestring, containers, stdenv, text - , transformers, unordered-containers - }: - mkDerivation { - pname = "xmlbf"; - version = "0.4.1"; - sha256 = "189a02e8b54c3576c3a919799def7b83c0e602b222264901c644c941c34fdc75"; - libraryHaskellDepends = [ - base bytestring containers text transformers unordered-containers - ]; + isExecutable = true; + libraryHaskellDepends = [ base tagsoup text ]; + executableHaskellDepends = [ base directory process ]; doHaddock = false; doCheck = false; - homepage = "https://gitlab.com/k0001/xmlbf"; - description = "XML back and forth! Parser, renderer, ToXml, FromXml, fixpoints"; - license = stdenv.lib.licenses.asl20; + homepage = "https://github.com/sinelaw/xml-to-json-fast"; + description = "Fast, light converter of xml to json capable of handling huge xml files"; + license = lib.licenses.mit; }) {}; - "xmlbf-xeno" = callPackage - ({ mkDerivation, base, bytestring, html-entities, stdenv, text - , unordered-containers, xeno, xmlbf - }: + "xml-types" = callPackage + ({ mkDerivation, base, deepseq, lib, text }: mkDerivation { - pname = "xmlbf-xeno"; - version = "0.1.1"; - sha256 = "6c1c4e419240c1e480d5543e89883cd2a356c1bb470a452f935424a80367dd32"; - libraryHaskellDepends = [ - base bytestring html-entities text unordered-containers xeno xmlbf - ]; + pname = "xml-types"; + version = "0.3.8"; + sha256 = "dad5e4ce602b7d1f4be37c0cfd99a261a4573746bfd80d917dc955b72da84c80"; + libraryHaskellDepends = [ base deepseq text ]; doHaddock = false; doCheck = false; - homepage = "https://gitlab.com/k0001/xmlbf"; - description = "xeno backend support for the xmlbf library"; - license = stdenv.lib.licenses.asl20; + homepage = "https://git.singpolyma.net/xml-types-haskell"; + description = "Basic types for representing XML"; + license = lib.licenses.mit; }) {}; "xmlgen" = callPackage - ({ mkDerivation, base, blaze-builder, bytestring, containers, mtl - , stdenv, text + ({ mkDerivation, base, blaze-builder, bytestring, containers, lib + , mtl, text }: mkDerivation { pname = "xmlgen"; version = "0.6.2.2"; sha256 = "926fa98c77525f5046274758fcebd190e86de3f53a4583179e8ce328f25a34d6"; + revision = "1"; + editedCabalFile = "0vwnqd0lsw81llsn0psga5r6pw7jh69vfbj3rnz7c2fpkc0gjh3j"; libraryHaskellDepends = [ base blaze-builder bytestring containers mtl text ]; doHaddock = false; doCheck = false; description = "Fast XML generation library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "xmonad" = callPackage ({ mkDerivation, base, containers, data-default, directory - , extensible-exceptions, filepath, mtl, process, setlocale, stdenv + , extensible-exceptions, filepath, lib, mtl, process, setlocale , unix, utf8-string, X11 }: mkDerivation { pname = "xmonad"; version = "0.15"; sha256 = "4a7948e6eee5e34a27d15444589ade3b3fa1adecadbf37b943cff8348380f928"; + revision = "1"; + editedCabalFile = "0yqh96qqphllr0zyz5j93cij5w2qvf39xxnrb52pz0qz3pywz9wd"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -37949,23 +45181,25 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; postInstall = '' - install -D man/xmonad.1 $doc/share/man/man1/xmonad.1 - install -D man/xmonad.hs $doc/share/doc/$name/sample-xmonad.hs + install -D man/xmonad.1 ''${!outputDoc}/share/man/man1/xmonad.1 + install -D man/xmonad.hs ''${!outputDoc}/share/doc/$name/sample-xmonad.hs ''; homepage = "http://xmonad.org"; description = "A tiling window manager"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "xmonad-contrib" = callPackage ({ mkDerivation, base, bytestring, containers, directory - , extensible-exceptions, filepath, mtl, old-locale, old-time - , process, random, semigroups, stdenv, unix, utf8-string, X11 - , X11-xft, xmonad + , extensible-exceptions, filepath, lib, mtl, old-locale, old-time + , process, random, semigroups, unix, utf8-string, X11, X11-xft + , xmonad }: mkDerivation { pname = "xmonad-contrib"; - version = "0.15"; - sha256 = "ba7686007037fc081de09fc05914fbb84cad8123e1f4eedb8895c863fcfb3e65"; + version = "0.16"; + sha256 = "ad72c38de1bf4f9e176bd0da7ee62a6153b03c9087313b3d4782f365f77caddd"; + revision = "1"; + editedCabalFile = "0vimkby2gq6sgzxzbvz67caba609xqlv2ii2gi8a1cjrnn6ib011"; libraryHaskellDepends = [ base bytestring containers directory extensible-exceptions filepath mtl old-locale old-time process random semigroups unix utf8-string @@ -37975,17 +45209,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://xmonad.org/"; description = "Third party extensions for xmonad"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "xmonad-extras" = callPackage ({ mkDerivation, alsa-mixer, base, bytestring, containers, hint - , libmpd, mtl, network, regex-posix, stdenv, X11, xmonad + , lib, libmpd, mtl, network, regex-posix, X11, xmonad , xmonad-contrib }: mkDerivation { pname = "xmonad-extras"; - version = "0.15.1"; - sha256 = "b8086169d15feb65c85b513ba19576c7caa2f4a5f234be503402569b03d2c1f4"; + version = "0.15.3"; + sha256 = "4963306321d7308abed4ee9bd173b4e68f12b88babd5d32d1db949770ad8085a"; configureFlags = [ "-f-with_hlist" "-fwith_parsec" "-fwith_split" ]; @@ -37997,11 +45231,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/xmonad/xmonad-extras"; description = "Third party extensions for xmonad with wacky dependencies"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "xss-sanitize" = callPackage - ({ mkDerivation, attoparsec, base, containers, css-text - , network-uri, stdenv, tagsoup, text, utf8-string + ({ mkDerivation, attoparsec, base, containers, css-text, lib + , network-uri, tagsoup, text, utf8-string }: mkDerivation { pname = "xss-sanitize"; @@ -38015,10 +45249,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/yesodweb/haskell-xss-sanitize#readme"; description = "sanitize untrusted HTML to prevent XSS attacks"; - license = stdenv.lib.licenses.bsd2; + license = lib.licenses.bsd2; }) {}; "xxhash-ffi" = callPackage - ({ mkDerivation, base, bytestring, stdenv }: + ({ mkDerivation, base, bytestring, lib }: mkDerivation { pname = "xxhash-ffi"; version = "0.2.0.0"; @@ -38028,59 +45262,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/haskell-haskey/xxhash-ffi#readme"; description = "Bindings to the C implementation the xxHash algorithm"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "yam" = callPackage - ({ mkDerivation, base, base16-bytestring, binary, bytestring - , data-default, fast-logger, http-types, lens, monad-logger, mtl - , mwc-random, reflection, salak, scientific, servant-server - , servant-swagger, servant-swagger-ui, stdenv, swagger2, text, time - , unliftio-core, unordered-containers, vault, wai, warp - }: - mkDerivation { - pname = "yam"; - version = "0.5.6"; - sha256 = "a2b4a1d4d3581e8a7f6378cb6d873efc1d5144c431d4c24b506ae6e6639a392c"; - libraryHaskellDepends = [ - base base16-bytestring binary bytestring data-default fast-logger - http-types lens monad-logger mtl mwc-random reflection salak - scientific servant-server servant-swagger servant-swagger-ui - swagger2 text time unliftio-core unordered-containers vault wai - warp - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/leptonyu/yam/yam#readme"; - description = "Yam Web"; - license = stdenv.lib.licenses.bsd3; - }) {}; - "yam-datasource" = callPackage - ({ mkDerivation, base, conduit, persistent, resource-pool - , resourcet, stdenv, unliftio-core, yam - }: - mkDerivation { - pname = "yam-datasource"; - version = "0.5.6"; - sha256 = "dfefeb0851b9d4c9f67e9fa44e9c97a7b52b665caa4e40b67e5b84e6df3b54fa"; - libraryHaskellDepends = [ - base conduit persistent resource-pool resourcet unliftio-core yam - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/leptonyu/yam/yam-datasource#readme"; - description = "Yam DataSource Middleware"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "yaml" = callPackage ({ mkDerivation, aeson, attoparsec, base, bytestring, conduit - , containers, directory, filepath, libyaml, mtl, resourcet - , scientific, stdenv, template-haskell, text, transformers + , containers, directory, filepath, lib, libyaml, mtl, resourcet + , scientific, template-haskell, text, transformers , unordered-containers, vector }: mkDerivation { pname = "yaml"; - version = "0.11.0.0"; - sha256 = "e66466cd29a4d256c3dd4dd4ab366033dbc5fa1fb67fdc6f7ac7aa3f161527bf"; + version = "0.11.5.0"; + sha256 = "b28e748bd69948cb1b43694d4d7c74756e060e09ca91688d0485e23f19d6cdad"; configureFlags = [ "-fsystem-libyaml" ]; isLibrary = true; isExecutable = true; @@ -38093,11 +45286,31 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/snoyberg/yaml#readme"; description = "Support for parsing and rendering YAML documents"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "yamlparse-applicative" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers, lib + , optparse-applicative, path, path-io, prettyprinter + , safe-coloured-text, scientific, text, unordered-containers + , validity, validity-text, vector, yaml + }: + mkDerivation { + pname = "yamlparse-applicative"; + version = "0.2.0.0"; + sha256 = "531b045c650f12311650d8aca410fa2d89ae4d0d85bfb13487ddd07c583d48b0"; + libraryHaskellDepends = [ + aeson base bytestring containers optparse-applicative path path-io + prettyprinter safe-coloured-text scientific text + unordered-containers validity validity-text vector yaml + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/NorfairKing/yamlparse-applicative#readme"; + description = "Declaritive configuration parsing with free docs"; + license = lib.licenses.mit; }) {}; "yes-precure5-command" = callPackage - ({ mkDerivation, base, Cabal, containers, mtl, parsec, random - , stdenv + ({ mkDerivation, base, Cabal, containers, lib, mtl, parsec, random }: mkDerivation { pname = "yes-precure5-command"; @@ -38115,113 +45328,46 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/igrep/yes-precure5-command/"; description = "Extended yes command to reproduce phrases in Yes! Precure 5"; - license = stdenv.lib.licenses.mit; - }) {}; - "yeshql" = callPackage - ({ mkDerivation, base, stdenv, yeshql-core, yeshql-hdbc }: - mkDerivation { - pname = "yeshql"; - version = "4.1.0.1"; - sha256 = "c4c590682d6581cf49893bdcd3c2d0e4046d81240a7f5abd7bcaa17037c29db6"; - libraryHaskellDepends = [ base yeshql-core yeshql-hdbc ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/tdammers/yeshql"; - description = "YesQL-style SQL database abstraction (legacy compatibility wrapper)"; - license = stdenv.lib.licenses.mit; - }) {}; - "yeshql-core" = callPackage - ({ mkDerivation, base, containers, convertible, filepath, parsec - , stdenv, template-haskell - }: - mkDerivation { - pname = "yeshql-core"; - version = "4.1.0.2"; - sha256 = "c0db2a2f415846236e9c38a652dc38e56f2a68baa72b61bdf5c5238f1b6317fe"; - libraryHaskellDepends = [ - base containers convertible filepath parsec template-haskell - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/tdammers/yeshql"; - description = "YesQL-style SQL database abstraction (core)"; - license = stdenv.lib.licenses.mit; - }) {}; - "yeshql-hdbc" = callPackage - ({ mkDerivation, base, containers, convertible, filepath, HDBC - , parsec, stdenv, template-haskell, yeshql-core - }: - mkDerivation { - pname = "yeshql-hdbc"; - version = "4.1.0.2"; - sha256 = "f4ac521c6970d9a06d321e9f2b1143e6901c9875314281505aafcda3bd0352dc"; - libraryHaskellDepends = [ - base containers convertible filepath HDBC parsec template-haskell - yeshql-core - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/tdammers/yeshql"; - description = "YesQL-style SQL database abstraction (HDBC backend)"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "yesod" = callPackage - ({ mkDerivation, aeson, base, blaze-html, blaze-markup, bytestring - , conduit, data-default-class, directory, fast-logger, monad-logger - , resourcet, semigroups, shakespeare, stdenv, streaming-commons - , template-haskell, text, transformers, unix, unordered-containers - , wai, wai-extra, wai-logger, warp, yaml, yesod-core, yesod-form - , yesod-persistent + ({ mkDerivation, aeson, base, bytestring, conduit + , data-default-class, directory, fast-logger, file-embed, lib + , monad-logger, shakespeare, streaming-commons, template-haskell + , text, unix, unordered-containers, wai, wai-extra, wai-logger + , warp, yaml, yesod-core, yesod-form, yesod-persistent }: mkDerivation { pname = "yesod"; - version = "1.6.0"; - sha256 = "8a242ffe1df10bc2c5dffb6e255ad21b11e96a9c4794bac20504b67f973da773"; + version = "1.6.1.2"; + sha256 = "4e70f8078430025882f696b6bae47dd5f51c3cfc87cd2cec9b81c87caf8e208f"; libraryHaskellDepends = [ - aeson base blaze-html blaze-markup bytestring conduit - data-default-class directory fast-logger monad-logger resourcet - semigroups shakespeare streaming-commons template-haskell text - transformers unix unordered-containers wai wai-extra wai-logger - warp yaml yesod-core yesod-form yesod-persistent + aeson base bytestring conduit data-default-class directory + fast-logger file-embed monad-logger shakespeare streaming-commons + template-haskell text unix unordered-containers wai wai-extra + wai-logger warp yaml yesod-core yesod-form yesod-persistent ]; doHaddock = false; doCheck = false; homepage = "http://www.yesodweb.com/"; description = "Creation of type-safe, RESTful web applications"; - license = stdenv.lib.licenses.mit; - }) {}; - "yesod-alerts" = callPackage - ({ mkDerivation, alerts, base, blaze-html, blaze-markup, safe - , stdenv, text, yesod-core - }: - mkDerivation { - pname = "yesod-alerts"; - version = "0.1.2.0"; - sha256 = "8e52c8a7ec9cdbe7cdc06f39ea4e27b852be0391cf78652e349f0f2c169b146f"; - libraryHaskellDepends = [ - alerts base blaze-html blaze-markup safe text yesod-core - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/alx741/yesod-alerts#readme"; - description = "Alert messages for the Yesod framework"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; "yesod-auth" = callPackage ({ mkDerivation, aeson, authenticate, base, base16-bytestring , base64-bytestring, binary, blaze-builder, blaze-html , blaze-markup, bytestring, conduit, conduit-extra, containers , cryptonite, data-default, email-validate, file-embed, http-client - , http-client-tls, http-conduit, http-types, memory, network-uri - , nonce, persistent, random, safe, shakespeare, stdenv + , http-client-tls, http-conduit, http-types, lib, memory + , network-uri, nonce, persistent, random, safe, shakespeare , template-haskell, text, time, transformers, unliftio , unliftio-core, unordered-containers, wai, yesod-core, yesod-form , yesod-persistent }: mkDerivation { pname = "yesod-auth"; - version = "1.6.5"; - sha256 = "b9dd963473a4d18d6a6921c0c321d86c77f264d8be2849b4aadcfa8f3ac337b3"; + version = "1.6.10.3"; + sha256 = "0f6a7ff7c11df6f436f2271928995134bc2273b5620ad37b8fe67d26ee7a4701"; libraryHaskellDepends = [ aeson authenticate base base16-bytestring base64-bytestring binary blaze-builder blaze-html blaze-markup bytestring conduit @@ -38235,16 +45381,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.yesodweb.com/"; description = "Authentication for Yesod"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "yesod-auth-hashdb" = callPackage - ({ mkDerivation, aeson, base, bytestring, persistent, stdenv, text + ({ mkDerivation, aeson, base, bytestring, lib, persistent, text , yesod-auth, yesod-core, yesod-form, yesod-persistent }: mkDerivation { pname = "yesod-auth-hashdb"; - version = "1.7.1"; - sha256 = "0d6f27a49aa862af8f4d1a84f8fe540300e42f9208728fba03a7996a5517dfe5"; + version = "1.7.1.7"; + sha256 = "45c2218bae054c2c32cf6c7e906cbc8f72163d54de69706f1881435cec5c51b5"; libraryHaskellDepends = [ aeson base bytestring persistent text yesod-auth yesod-core yesod-form yesod-persistent @@ -38253,230 +45399,155 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/paul-rouse/yesod-auth-hashdb"; description = "Authentication plugin for Yesod"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "yesod-auth-oauth2" = callPackage - ({ mkDerivation, aeson, base, bytestring, errors, hoauth2 - , http-client, http-conduit, http-types, microlens, random - , safe-exceptions, stdenv, text, uri-bytestring, yesod-auth - , yesod-core + ({ mkDerivation, aeson, base, bytestring, cryptonite, errors + , hoauth2, http-client, http-conduit, http-types, lib, memory + , microlens, mtl, safe-exceptions, text, unliftio, uri-bytestring + , yesod-auth, yesod-core }: mkDerivation { pname = "yesod-auth-oauth2"; - version = "0.6.1.0"; - sha256 = "5ad514358e1f29a65cf0f06bf821961e5a8938fd22f7ea3d36b602672c131c91"; + version = "0.6.3.4"; + sha256 = "5fb61b946209ed431fd23b2d9d9edacc3af82fae47cca2f7795314377e04c9c3"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - aeson base bytestring errors hoauth2 http-client http-conduit - http-types microlens random safe-exceptions text uri-bytestring - yesod-auth yesod-core + aeson base bytestring cryptonite errors hoauth2 http-client + http-conduit http-types memory microlens mtl safe-exceptions text + unliftio uri-bytestring yesod-auth yesod-core ]; doHaddock = false; doCheck = false; - homepage = "http://github.com/thoughtbot/yesod-auth-oauth2"; + homepage = "http://github.com/freckle/yesod-auth-oauth2"; description = "OAuth 2.0 authentication plugins"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "yesod-bin" = callPackage - ({ mkDerivation, attoparsec, base, base64-bytestring, blaze-builder - , bytestring, Cabal, conduit, conduit-extra, containers - , data-default-class, directory, file-embed, filepath, fsnotify - , http-client, http-client-tls, http-reverse-proxy, http-types - , network, optparse-applicative, parsec, process, project-template - , resourcet, say, shakespeare, split, stdenv, stm - , streaming-commons, tar, template-haskell, text, time - , transformers, transformers-compat, unix-compat, unliftio + ({ mkDerivation, base, bytestring, Cabal, conduit, conduit-extra + , containers, data-default-class, directory, file-embed, filepath + , fsnotify, http-client, http-client-tls, http-reverse-proxy + , http-types, lib, network, optparse-applicative, process + , project-template, say, split, stm, streaming-commons, tar, text + , time, transformers, transformers-compat, unliftio , unordered-containers, wai, wai-extra, warp, warp-tls, yaml, zlib }: mkDerivation { pname = "yesod-bin"; - version = "1.6.0.3"; - sha256 = "e4db295b4c651c205a1730df38501c217d9b600f3dbc1eea21d5fa47e832aedc"; - revision = "4"; - editedCabalFile = "1iw9m3z6m4n9dlwamf1kwr7pp2wpk6awf1m63zjkgw5j4vwxlcpg"; + version = "1.6.1"; + sha256 = "9dff8bb3e69e911f5d48e8b297da3eef16c62e4f5e6f0c910bc9f9e7592b5f69"; isLibrary = false; isExecutable = true; executableHaskellDepends = [ - attoparsec base base64-bytestring blaze-builder bytestring Cabal - conduit conduit-extra containers data-default-class directory - file-embed filepath fsnotify http-client http-client-tls - http-reverse-proxy http-types network optparse-applicative parsec - process project-template resourcet say shakespeare split stm - streaming-commons tar template-haskell text time transformers - transformers-compat unix-compat unliftio unordered-containers wai - wai-extra warp warp-tls yaml zlib + base bytestring Cabal conduit conduit-extra containers + data-default-class directory file-embed filepath fsnotify + http-client http-client-tls http-reverse-proxy http-types network + optparse-applicative process project-template say split stm + streaming-commons tar text time transformers transformers-compat + unliftio unordered-containers wai wai-extra warp warp-tls yaml zlib ]; doHaddock = false; doCheck = false; homepage = "http://www.yesodweb.com/"; description = "The yesod helper executable"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "yesod-core" = callPackage ({ mkDerivation, aeson, auto-update, base, blaze-html, blaze-markup - , byteable, bytestring, case-insensitive, cereal, clientsession - , conduit, conduit-extra, containers, cookie, deepseq, fast-logger - , http-types, monad-logger, mtl, parsec, path-pieces, primitive - , random, resourcet, rio, shakespeare, stdenv, template-haskell - , text, time, transformers, unix-compat, unliftio - , unordered-containers, vector, wai, wai-extra, wai-logger, warp - , word8 + , bytestring, case-insensitive, cereal, clientsession, conduit + , conduit-extra, containers, cookie, deepseq, entropy, fast-logger + , http-types, lib, memory, monad-logger, mtl, parsec, path-pieces + , primitive, random, resourcet, shakespeare, template-haskell, text + , time, transformers, unix-compat, unliftio, unordered-containers + , vector, wai, wai-extra, wai-logger, warp, word8 }: mkDerivation { pname = "yesod-core"; - version = "1.6.9"; - sha256 = "ca64d08184c7775e2a985c903e74f32efedcf6c217b3370ca7e136082eeb8e4b"; + version = "1.6.20.2"; + sha256 = "cbffa61bb163723e7cc976d537411910fca09f8991765d3fe1dd654eb53592a0"; libraryHaskellDepends = [ - aeson auto-update base blaze-html blaze-markup byteable bytestring + aeson auto-update base blaze-html blaze-markup bytestring case-insensitive cereal clientsession conduit conduit-extra - containers cookie deepseq fast-logger http-types monad-logger mtl - parsec path-pieces primitive random resourcet rio shakespeare - template-haskell text time transformers unix-compat unliftio - unordered-containers vector wai wai-extra wai-logger warp word8 + containers cookie deepseq entropy fast-logger http-types memory + monad-logger mtl parsec path-pieces primitive random resourcet + shakespeare template-haskell text time transformers unix-compat + unliftio unordered-containers vector wai wai-extra wai-logger warp + word8 ]; doHaddock = false; doCheck = false; homepage = "http://www.yesodweb.com/"; description = "Creation of type-safe, RESTful web applications"; - license = stdenv.lib.licenses.mit; - }) {}; - "yesod-csp" = callPackage - ({ mkDerivation, attoparsec, base, case-insensitive - , mono-traversable, network-uri, semigroups, stdenv, syb - , template-haskell, text, wai, yesod, yesod-core - }: - mkDerivation { - pname = "yesod-csp"; - version = "0.2.4.0"; - sha256 = "e05d31857d6d0e8aececdd83b6a896267ecab2c29426d559e3dafb259eac92a5"; - libraryHaskellDepends = [ - attoparsec base case-insensitive mono-traversable network-uri - semigroups syb template-haskell text wai yesod yesod-core - ]; - doHaddock = false; - doCheck = false; - description = "Add CSP headers to Yesod apps"; - license = stdenv.lib.licenses.mit; - }) {}; - "yesod-eventsource" = callPackage - ({ mkDerivation, base, blaze-builder, conduit, stdenv, transformers - , wai, wai-eventsource, wai-extra, yesod-core - }: - mkDerivation { - pname = "yesod-eventsource"; - version = "1.6.0"; - sha256 = "6fceeca34d5e80c8a0d65ab95fab3c53807d1f18eb506abdef67a8f70d0e418b"; - libraryHaskellDepends = [ - base blaze-builder conduit transformers wai wai-eventsource - wai-extra yesod-core - ]; - doHaddock = false; - doCheck = false; - homepage = "http://www.yesodweb.com/"; - description = "Server-sent events support for Yesod apps"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "yesod-fb" = callPackage - ({ mkDerivation, aeson, base, bytestring, conduit, crypto-api, fb - , http-client-tls, http-conduit, stdenv, text, wai, yesod-core + ({ mkDerivation, aeson, base, bytestring, conduit, fb + , http-client-tls, http-conduit, lib, memory, text, wai, yesod-core }: mkDerivation { pname = "yesod-fb"; - version = "0.5.0"; - sha256 = "de375004c12e89eec47738d60465c7c63b5f0c7bfc3591c70a35522fdc0841db"; + version = "0.6.1"; + sha256 = "d4a963c904c655250a8c9a2b73981261e5661127d0e836255d4afb82ae2cd1db"; libraryHaskellDepends = [ - aeson base bytestring conduit crypto-api fb http-client-tls - http-conduit text wai yesod-core + aeson base bytestring conduit fb http-client-tls http-conduit + memory text wai yesod-core ]; doHaddock = false; doCheck = false; homepage = "https://github.com/psibi/yesod-fb"; description = "Useful glue functions between the fb library and Yesod"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "yesod-form" = callPackage ({ mkDerivation, aeson, attoparsec, base, blaze-builder, blaze-html , blaze-markup, byteable, bytestring, containers, data-default - , email-validate, network-uri, persistent, resourcet, semigroups - , shakespeare, stdenv, text, time, transformers, wai, xss-sanitize + , email-validate, lib, network-uri, persistent, resourcet + , shakespeare, text, time, transformers, wai, xss-sanitize , yesod-core, yesod-persistent }: mkDerivation { pname = "yesod-form"; - version = "1.6.3"; - sha256 = "40d7d85039fb2bb3081f695cfed4a6d4f8adac413d86dd11ccfc948b677e9b97"; + version = "1.7.0"; + sha256 = "711be0e224a765f1ae2d2c8f9ece8e3e8c24ba6708242b6d7ab7c080865f0f9c"; libraryHaskellDepends = [ aeson attoparsec base blaze-builder blaze-html blaze-markup byteable bytestring containers data-default email-validate - network-uri persistent resourcet semigroups shakespeare text time - transformers wai xss-sanitize yesod-core yesod-persistent + network-uri persistent resourcet shakespeare text time transformers + wai xss-sanitize yesod-core yesod-persistent ]; doHaddock = false; doCheck = false; homepage = "http://www.yesodweb.com/"; description = "Form handling support for Yesod Web Framework"; - license = stdenv.lib.licenses.mit; - }) {}; - "yesod-form-bootstrap4" = callPackage - ({ mkDerivation, base, stdenv, text, yesod-core, yesod-form }: - mkDerivation { - pname = "yesod-form-bootstrap4"; - version = "2.1.0"; - sha256 = "2c42f2c38549e0f782572162a215cbb86bffa09a39db7c4e2ac711ede092c1f1"; - libraryHaskellDepends = [ base text yesod-core yesod-form ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/ncaq/yesod-form-bootstrap4#readme"; - description = "renderBootstrap4"; - license = stdenv.lib.licenses.mit; - }) {}; - "yesod-gitrepo" = callPackage - ({ mkDerivation, base, directory, http-types, process, stdenv - , temporary, text, unliftio, wai, yesod-core - }: - mkDerivation { - pname = "yesod-gitrepo"; - version = "0.3.0"; - sha256 = "b03c67c506bc3fc402cb41759d69f2c3159af47959cbd964cb6531996084981e"; - libraryHaskellDepends = [ - base directory http-types process temporary text unliftio wai - yesod-core - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/snoyberg/yesod-gitrepo#readme"; - description = "Host content provided by a Git repo"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "yesod-gitrev" = callPackage - ({ mkDerivation, aeson, base, gitrev, stdenv, template-haskell + ({ mkDerivation, aeson, base, githash, lib, template-haskell , yesod-core }: mkDerivation { pname = "yesod-gitrev"; - version = "0.2.0.0"; - sha256 = "df9f374e6099e55eb62cc273451605ce8746785a293e76115d25002355fee052"; - revision = "1"; - editedCabalFile = "1b0df34lz569gnwbbz0p20dml6bi2nbva9wfdsxyvva0dhvxjaz5"; + version = "0.2.1"; + sha256 = "fc34c48eee25a15a55a6052fc1d15bb63bbc63514059483cb2212895f0eea671"; libraryHaskellDepends = [ - aeson base gitrev template-haskell yesod-core + aeson base githash template-haskell yesod-core ]; doHaddock = false; doCheck = false; homepage = "https://github.com/DanBurton/yesod-gitrev"; description = "A subsite for displaying git information"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "yesod-markdown" = callPackage ({ mkDerivation, base, blaze-html, blaze-markup, bytestring - , directory, pandoc, persistent, shakespeare, stdenv, text + , directory, lib, pandoc, persistent, shakespeare, text , xss-sanitize, yesod-core, yesod-form }: mkDerivation { pname = "yesod-markdown"; - version = "0.12.6.0"; - sha256 = "9569b16ae115e4da9817aae8688f143a2c9143146a9eee06c8068bf231ccab00"; + version = "0.12.6.11"; + sha256 = "298e7101c76076b30b3c2820b3b6a4bb371d82ae25b0b5badf2efa4492329510"; libraryHaskellDepends = [ base blaze-html blaze-markup bytestring directory pandoc persistent shakespeare text xss-sanitize yesod-core yesod-form @@ -38485,17 +45556,16 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/pbrisbin/yesod-markdown"; description = "Tools for using markdown in a yesod application"; - license = stdenv.lib.licenses.gpl2; + license = lib.licenses.gpl2Only; }) {}; "yesod-newsfeed" = callPackage ({ mkDerivation, base, blaze-html, blaze-markup, bytestring - , containers, shakespeare, stdenv, text, time, xml-conduit - , yesod-core + , containers, lib, shakespeare, text, time, xml-conduit, yesod-core }: mkDerivation { pname = "yesod-newsfeed"; - version = "1.6.1.0"; - sha256 = "6d0b97592d74ca45e204f1876fb113a4830c5f35612b876175169af3d2f79615"; + version = "1.7.0.0"; + sha256 = "8f2ce7022fedf719d8f87ea4af401a2d77f686f42e5736055536baac7f4af63c"; libraryHaskellDepends = [ base blaze-html blaze-markup bytestring containers shakespeare text time xml-conduit yesod-core @@ -38504,16 +45574,33 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.yesodweb.com/"; description = "Helper functions and data types for producing News feeds"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; + }) {}; + "yesod-page-cursor" = callPackage + ({ mkDerivation, aeson, base, bytestring, containers + , http-link-header, lib, network-uri, text, unliftio, yesod-core + }: + mkDerivation { + pname = "yesod-page-cursor"; + version = "2.0.0.8"; + sha256 = "5e26c5605d44a85dfab7137d722baa86a82486ad07153abecfd38c55f614edab"; + libraryHaskellDepends = [ + aeson base bytestring containers http-link-header network-uri text + unliftio yesod-core + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/freckle/yesod-page-cursor#readme"; + license = lib.licenses.mit; }) {}; "yesod-paginator" = callPackage - ({ mkDerivation, base, blaze-markup, path-pieces, persistent, safe - , stdenv, text, transformers, uri-encode, yesod-core + ({ mkDerivation, base, blaze-markup, lib, path-pieces, persistent + , safe, text, transformers, uri-encode, yesod-core }: mkDerivation { pname = "yesod-paginator"; - version = "1.1.0.1"; - sha256 = "6e241fb7e55debfe3b674e62faeb02967abb982cd77295847085423d23230b90"; + version = "1.1.1.0"; + sha256 = "921d8cd2d199966f77b2f21d532b2049fe22ad8237802904f19df6dbe9aceb1b"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -38524,17 +45611,17 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/pbrisbin/yesod-paginator"; description = "A pagination approach for yesod"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "yesod-persistent" = callPackage - ({ mkDerivation, base, blaze-builder, conduit, persistent - , persistent-template, resource-pool, resourcet, stdenv - , transformers, yesod-core + ({ mkDerivation, base, blaze-builder, conduit, lib, persistent + , persistent-template, resource-pool, resourcet, transformers + , yesod-core }: mkDerivation { pname = "yesod-persistent"; - version = "1.6.0.1"; - sha256 = "748acc0a08e371548920a1b5e2e8b2c95b95014becd63acf259712d306a9bd4f"; + version = "1.6.0.7"; + sha256 = "6406b9d87baf425b078ad56aac7f7078a62d2cbd328c9dcb0b532360cfad5d80"; libraryHaskellDepends = [ base blaze-builder conduit persistent persistent-template resource-pool resourcet transformers yesod-core @@ -38543,29 +45630,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.yesodweb.com/"; description = "Some helpers for using Persistent from Yesod"; - license = stdenv.lib.licenses.mit; - }) {}; - "yesod-recaptcha2" = callPackage - ({ mkDerivation, aeson, base, classy-prelude, http-conduit, stdenv - , yesod-auth, yesod-core, yesod-form - }: - mkDerivation { - pname = "yesod-recaptcha2"; - version = "0.3.0"; - sha256 = "0c42aad0943a1a1518d23632b243709542690921bdf25262367357b74d906f89"; - libraryHaskellDepends = [ - aeson base classy-prelude http-conduit yesod-auth yesod-core - yesod-form - ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/ncaq/yesod-recaptcha2#readme"; - description = "yesod recaptcha2"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "yesod-sitemap" = callPackage - ({ mkDerivation, base, conduit, containers, data-default, stdenv - , text, time, xml-conduit, xml-types, yesod-core + ({ mkDerivation, base, conduit, containers, data-default, lib, text + , time, xml-conduit, xml-types, yesod-core }: mkDerivation { pname = "yesod-sitemap"; @@ -38579,21 +45648,20 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.yesodweb.com/"; description = "Generate XML sitemaps"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "yesod-static" = callPackage ({ mkDerivation, async, attoparsec, base, base64-bytestring , blaze-builder, bytestring, conduit, containers, cryptonite , cryptonite-conduit, css-text, data-default, directory, file-embed - , filepath, hashable, hjsmin, http-types, memory, mime-types - , process, stdenv, template-haskell, text, transformers - , unix-compat, unordered-containers, wai, wai-app-static - , yesod-core + , filepath, hashable, hjsmin, http-types, lib, memory, mime-types + , process, template-haskell, text, transformers, unix-compat + , unordered-containers, wai, wai-app-static, yesod-core }: mkDerivation { pname = "yesod-static"; - version = "1.6.0.1"; - sha256 = "abe7e802f5efd064823b827074fea3613f4ba46115afedb5e2d96f919dcfa0c9"; + version = "1.6.1.0"; + sha256 = "9794262f4ad3f834bd76aa105e348e65821f087a2c0d3b17a27f6e665385c5a1"; libraryHaskellDepends = [ async attoparsec base base64-bytestring blaze-builder bytestring conduit containers cryptonite cryptonite-conduit css-text @@ -38606,56 +45674,39 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://www.yesodweb.com/"; description = "Static file serving subsite for Yesod Web Framework"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {}; "yesod-test" = callPackage - ({ mkDerivation, attoparsec, base, blaze-builder, blaze-html + ({ mkDerivation, aeson, attoparsec, base, blaze-builder, blaze-html , bytestring, case-insensitive, conduit, containers, cookie - , hspec-core, html-conduit, http-types, HUnit, network, pretty-show - , semigroups, stdenv, text, time, transformers, wai, wai-extra + , hspec-core, html-conduit, http-types, HUnit, lib, memory, mtl + , network, pretty-show, text, time, transformers, wai, wai-extra , xml-conduit, xml-types, yesod-core }: mkDerivation { pname = "yesod-test"; - version = "1.6.5.1"; - sha256 = "523f2f1f8e38a83824433b5c03382f196c8d9f2512e1979650962eb9ac211520"; + version = "1.6.12"; + sha256 = "880aee27034e5b7cf889764b1d98f8749bd7ae06ba7b7f19a6f4490c7f3bfef5"; libraryHaskellDepends = [ - attoparsec base blaze-builder blaze-html bytestring + aeson attoparsec base blaze-builder blaze-html bytestring case-insensitive conduit containers cookie hspec-core html-conduit - http-types HUnit network pretty-show semigroups text time + http-types HUnit memory mtl network pretty-show text time transformers wai wai-extra xml-conduit xml-types yesod-core ]; doHaddock = false; doCheck = false; homepage = "http://www.yesodweb.com"; description = "integration testing for WAI/Yesod Applications"; - license = stdenv.lib.licenses.mit; - }) {}; - "yesod-text-markdown" = callPackage - ({ mkDerivation, aeson, base, markdown, persistent, shakespeare - , stdenv, text, yesod-core, yesod-form, yesod-persistent - }: - mkDerivation { - pname = "yesod-text-markdown"; - version = "0.1.10"; - sha256 = "3cee8b3d8d84f30e8b825076d650afb05e79ebd22f34a21fc7ad7f45e1637ddc"; - libraryHaskellDepends = [ - aeson base markdown persistent shakespeare text yesod-core - yesod-form yesod-persistent - ]; - doHaddock = false; - doCheck = false; - description = "Yesod support for Text.Markdown."; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.mit; }) {}; "yesod-websockets" = callPackage - ({ mkDerivation, base, conduit, mtl, stdenv, transformers, unliftio + ({ mkDerivation, base, conduit, lib, mtl, transformers, unliftio , wai-websockets, websockets, yesod-core }: mkDerivation { pname = "yesod-websockets"; - version = "0.3.0.1"; - sha256 = "86c947aa0354c8b98ec7364b51df2ba98ac7c8e184d6ebfcf4bfb9b2e8c381cc"; + version = "0.3.0.3"; + sha256 = "d6f8ab586dc58ac2d21cb9c0e5a67500c9bb7a80813db85d3d94e309ecc7a442"; libraryHaskellDepends = [ base conduit mtl transformers unliftio wai-websockets websockets yesod-core @@ -38664,33 +45715,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/yesodweb/yesod"; description = "WebSockets support for Yesod"; - license = stdenv.lib.licenses.mit; - }) {}; - "yi-language" = callPackage - ({ mkDerivation, alex, array, base, binary, containers - , data-default, hashable, microlens-platform, oo-prototypes - , pointedlist, regex-base, regex-tdfa, stdenv, template-haskell - , transformers-base, unordered-containers - }: - mkDerivation { - pname = "yi-language"; - version = "0.18.0"; - sha256 = "e86eaae8c0c21834d14dd9aaec50730df92c08e4ffa8846dc750d6b0033cc470"; - libraryHaskellDepends = [ - array base binary containers data-default hashable - microlens-platform oo-prototypes pointedlist regex-base regex-tdfa - template-haskell transformers-base unordered-containers - ]; - libraryToolDepends = [ alex ]; - doHaddock = false; - doCheck = false; - homepage = "https://github.com/yi-editor/yi#readme"; - description = "Collection of language-related Yi libraries"; - license = stdenv.lib.licenses.gpl2; + license = lib.licenses.mit; }) {}; "yi-rope" = callPackage - ({ mkDerivation, base, binary, bytestring, deepseq, fingertree - , stdenv, text + ({ mkDerivation, base, binary, bytestring, deepseq, fingertree, lib + , text }: mkDerivation { pname = "yi-rope"; @@ -38702,10 +45731,22 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "A rope data structure used by Yi"; - license = stdenv.lib.licenses.gpl2; + license = lib.licenses.gpl2Only; + }) {}; + "yjsvg" = callPackage + ({ mkDerivation, base, HaXml, lib }: + mkDerivation { + pname = "yjsvg"; + version = "0.2.0.1"; + sha256 = "f737b7d43b7b3fd3237d07761c672569a2b5d0c1e1b26d48097b9e96b1262e7e"; + libraryHaskellDepends = [ base HaXml ]; + doHaddock = false; + doCheck = false; + description = "make SVG string from Haskell data"; + license = lib.licenses.bsd3; }) {}; "yjtools" = callPackage - ({ mkDerivation, base, stdenv }: + ({ mkDerivation, base, lib }: mkDerivation { pname = "yjtools"; version = "0.9.18"; @@ -38718,7 +45759,7 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; license = "LGPL"; }) {}; "yoga" = callPackage - ({ mkDerivation, base, bindings-DSL, ieee754, stdenv }: + ({ mkDerivation, base, bindings-DSL, ieee754, lib }: mkDerivation { pname = "yoga"; version = "0.0.0.5"; @@ -38729,10 +45770,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Bindings to Facebook's Yoga layout library"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "youtube" = callPackage - ({ mkDerivation, base, bytestring, process, stdenv, utility-ht }: + ({ mkDerivation, base, bytestring, lib, process, utility-ht }: mkDerivation { pname = "youtube"; version = "0.2.1.1"; @@ -38744,30 +45785,68 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Upload video to YouTube via YouTube API"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "zenacy-html" = callPackage + ({ mkDerivation, base, bytestring, containers, data-default, dlist + , extra, lib, mtl, pretty-show, safe, safe-exceptions, text + , transformers, vector, word8 + }: + mkDerivation { + pname = "zenacy-html"; + version = "2.0.3"; + sha256 = "cc0634401febc17e08f899b433b3b55a1fef7e45accc0be863f906919ea06fd1"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base bytestring containers data-default dlist extra mtl pretty-show + safe safe-exceptions text transformers vector word8 + ]; + executableHaskellDepends = [ + base bytestring containers data-default dlist extra pretty-show + text vector + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/mlcfp/zenacy-html"; + description = "A standard compliant HTML parsing library"; + license = lib.licenses.mit; + }) {}; + "zenacy-unicode" = callPackage + ({ mkDerivation, base, bytestring, lib, vector, word8 }: + mkDerivation { + pname = "zenacy-unicode"; + version = "1.0.1"; + sha256 = "7c838704146d820846c56aac54fa8061c5f2c238b39a6f730930402343fe03d0"; + libraryHaskellDepends = [ base bytestring vector word8 ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/mlcfp/zenacy-unicode"; + description = "Unicode utilities for Haskell"; + license = lib.licenses.mit; }) {}; "zero" = callPackage - ({ mkDerivation, base, semigroups, stdenv }: + ({ mkDerivation, base, lib, semigroups }: mkDerivation { pname = "zero"; - version = "0.1.4"; - sha256 = "38cdc62d9673b8b40999de69da2ec60dab7a65fb1c22133ecd54e0a2ec61d5d5"; + version = "0.1.5"; + sha256 = "9c52083fc246299bf63df0363e950e19a88c6f6fbab7891cfd9379f6180760f9"; libraryHaskellDepends = [ base semigroups ]; doHaddock = false; doCheck = false; homepage = "https://github.com/phaazon/zero"; description = "Semigroups with absorption"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "zeromq4-haskell" = callPackage ({ mkDerivation, async, base, bytestring, containers, exceptions - , monad-control, semigroups, stdenv, transformers - , transformers-base, zeromq + , lib, monad-control, semigroups, transformers, transformers-base + , zeromq }: mkDerivation { pname = "zeromq4-haskell"; - version = "0.7.0"; - sha256 = "58d4504ee607cb681fc3da2474ed92afaefdb2dc34752b145aa9f746ab29079f"; + version = "0.8.0"; + sha256 = "d3be996589e126e30cb000545c56907e44a2a1d10960e4c7698b7941d0dff66b"; libraryHaskellDepends = [ async base bytestring containers exceptions monad-control semigroups transformers transformers-base @@ -38777,11 +45856,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://gitlab.com/twittner/zeromq-haskell/"; description = "Bindings to ZeroMQ 4.x"; - license = stdenv.lib.licenses.mit; + license = lib.licenses.mit; }) {inherit (pkgs) zeromq;}; "zeromq4-patterns" = callPackage - ({ mkDerivation, async, base, binary, bytestring, exceptions - , stdenv, stm, zeromq4-haskell + ({ mkDerivation, async, base, binary, bytestring, exceptions, lib + , stm, zeromq4-haskell }: mkDerivation { pname = "zeromq4-patterns"; @@ -38797,11 +45876,11 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/hverr/zeromq4-patterns#readme"; description = "Haskell implementation of several ZeroMQ patterns"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "zim-parser" = callPackage ({ mkDerivation, array, base, base-compat, binary, binary-conduit - , bytestring, conduit, conduit-extra, lzma, stdenv + , bytestring, conduit, conduit-extra, lib, lzma }: mkDerivation { pname = "zim-parser"; @@ -38815,44 +45894,61 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "https://github.com/robbinch/zim-parser#readme"; description = "Read and parse ZIM files"; - license = stdenv.lib.licenses.gpl3; + license = lib.licenses.gpl3Only; + }) {}; + "zio" = callPackage + ({ mkDerivation, base, lib, mtl, transformers, unexceptionalio + , unexceptionalio-trans + }: + mkDerivation { + pname = "zio"; + version = "0.1.0.2"; + sha256 = "d3007a80f3f8d70c66fad981faacecccd533f02ba72a964b277bec6e282a6a96"; + libraryHaskellDepends = [ + base mtl transformers unexceptionalio unexceptionalio-trans + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/bbarker/haskell-zio#readme"; + description = "App-centric Monad-transformer based on Scala ZIO (UIO + ReaderT + ExceptT)"; + license = lib.licenses.mpl20; }) {}; "zip" = callPackage ({ mkDerivation, base, bytestring, bzlib-conduit, case-insensitive - , cereal, conduit, conduit-extra, containers, digest, directory - , dlist, exceptions, filepath, monad-control, mtl, resourcet - , stdenv, text, time, transformers, transformers-base + , cereal, conduit, conduit-extra, conduit-zstd, containers, digest + , directory, dlist, exceptions, filepath, lib, monad-control, mtl + , resourcet, text, time, transformers, transformers-base, unix }: mkDerivation { pname = "zip"; - version = "1.2.0"; - sha256 = "b61de150884e376923e247f8f7386966d6d5d1804238c42fd874b61fe3b27dc9"; - revision = "1"; - editedCabalFile = "084dfylc1h45r4v2zyld1vvrxs6x1ljq8hzinqrkv2ii748cmzdb"; + version = "1.7.1"; + sha256 = "0d7f02bbdf6c49e9a33d2eca4b3d7644216a213590866dafdd2b47ddd38eb746"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ base bytestring bzlib-conduit case-insensitive cereal conduit - conduit-extra containers digest directory dlist exceptions filepath - monad-control mtl resourcet text time transformers - transformers-base + conduit-extra conduit-zstd containers digest directory dlist + exceptions filepath monad-control mtl resourcet text time + transformers transformers-base unix ]; executableHaskellDepends = [ base filepath ]; doHaddock = false; doCheck = false; homepage = "https://github.com/mrkkrp/zip"; description = "Operations on zip archives"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "zip-archive" = callPackage ({ mkDerivation, array, base, binary, bytestring, containers - , digest, directory, filepath, mtl, pretty, stdenv, text, time - , unix, zlib + , digest, directory, filepath, lib, mtl, pretty, text, time, unix + , zlib }: mkDerivation { pname = "zip-archive"; - version = "0.4"; - sha256 = "5fbea91d95ae1b1ec73aed8a8c67c8bae89bc3b6f7d9da898f07209e4a4ada19"; + version = "0.4.1"; + sha256 = "c5d5c9976241dcc25b0d8753dc526bb1bfef60f30dee38c53a7ae56e6be9b1b1"; + revision = "1"; + editedCabalFile = "1mv6jns7zf0fi7lrhzk007g12v6x7yf5ycbj67rbh83xfkf4nxsi"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -38863,18 +45959,18 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/jgm/zip-archive"; description = "Library for creating and modifying zip archives"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "zip-stream" = callPackage ({ mkDerivation, base, binary, binary-conduit, bytestring, conduit - , conduit-extra, digest, directory, exceptions, filepath, mtl - , primitive, resourcet, stdenv, text, time, transformers - , transformers-base, zlib + , conduit-extra, digest, directory, exceptions, filepath, lib, mtl + , primitive, resourcet, text, time, transformers, transformers-base + , zlib }: mkDerivation { pname = "zip-stream"; - version = "0.2.0.1"; - sha256 = "b7c45c612f1f53546923162d73c644b9704d5293b1e767108728d3c08b46a587"; + version = "0.2.1.0"; + sha256 = "91eeff0334c97452e7ae6007e8082a0481589f3ada36985f29655419819ca83b"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -38888,43 +45984,57 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "ZIP archive streaming using conduits"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "zipper-extra" = callPackage + ({ mkDerivation, base, comonad, comonad-extras, exceptions, lib + , split + }: + mkDerivation { + pname = "zipper-extra"; + version = "0.1.3.2"; + sha256 = "915506b760a770840c76ac341c1fcd7a25b0ccd530ce946311e062401c0c0233"; + libraryHaskellDepends = [ + base comonad comonad-extras exceptions split + ]; + doHaddock = false; + doCheck = false; + description = "Zipper utils that weren't in Control.Comonad.Store.Zipper"; + license = lib.licenses.mit; }) {}; "zippers" = callPackage - ({ mkDerivation, base, Cabal, cabal-doctest, lens, profunctors - , semigroupoids, semigroups, stdenv + ({ mkDerivation, base, fail, indexed-traversable, lens, lib + , profunctors, semigroupoids, semigroups }: mkDerivation { pname = "zippers"; - version = "0.2.5"; - sha256 = "2d127772564655df0cb99d5191b91a555797e66e535d0b8b4f5ed4d54097c085"; - revision = "3"; - editedCabalFile = "0y0klc2jaj611cjvmqi95dyj9yvribf9xhibn1andrz5rs6ysz3p"; - setupHaskellDepends = [ base Cabal cabal-doctest ]; + version = "0.3.1"; + sha256 = "a3a4d5d41be74ea02fa9cb7e22e11152c2ddf8abd17f72f5794899f653fce19f"; libraryHaskellDepends = [ - base lens profunctors semigroupoids semigroups + base fail indexed-traversable lens profunctors semigroupoids + semigroups ]; doHaddock = false; doCheck = false; homepage = "http://github.com/ekmett/zippers/"; description = "Traversal based zippers"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "zlib" = callPackage - ({ mkDerivation, base, bytestring, stdenv, zlib }: + ({ mkDerivation, base, bytestring, lib, zlib }: mkDerivation { pname = "zlib"; - version = "0.6.2"; - sha256 = "0dcc7d925769bdbeb323f83b66884101084167501f11d74d21eb9bc515707fed"; + version = "0.6.2.3"; + sha256 = "807f6bddf9cb3c517ce5757d991dde3c7e319953a22c86ee03d74534bd5abc88"; libraryHaskellDepends = [ base bytestring ]; librarySystemDepends = [ zlib ]; doHaddock = false; doCheck = false; description = "Compression and decompression in the gzip and zlib formats"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {inherit (pkgs) zlib;}; "zlib-bindings" = callPackage - ({ mkDerivation, base, bytestring, stdenv, zlib }: + ({ mkDerivation, base, bytestring, lib, zlib }: mkDerivation { pname = "zlib-bindings"; version = "0.1.1.5"; @@ -38936,10 +46046,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://github.com/snapframework/zlib-bindings"; description = "Low-level bindings to the zlib package"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "zlib-lens" = callPackage - ({ mkDerivation, base, bytestring, profunctors, stdenv, zlib }: + ({ mkDerivation, base, bytestring, lib, profunctors, zlib }: mkDerivation { pname = "zlib-lens"; version = "0.1.2.1"; @@ -38949,10 +46059,10 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doCheck = false; homepage = "http://lens.github.io/"; description = "Lenses for zlib"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "zot" = callPackage - ({ mkDerivation, base, monads-tf, stdenv }: + ({ mkDerivation, base, lib, monads-tf }: mkDerivation { pname = "zot"; version = "0.0.3"; @@ -38966,31 +46076,31 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Zot language"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "zstd" = callPackage - ({ mkDerivation, base, bytestring, deepseq, ghc-prim, stdenv }: + ({ mkDerivation, base, bytestring, deepseq, ghc-prim, lib }: mkDerivation { pname = "zstd"; - version = "0.1.0.0"; - sha256 = "0875840799d987cf8f8dd5e0a7686978084b3088c07123e66f6f88561f474bff"; + version = "0.1.2.0"; + sha256 = "68f680bf08523ca23765c69abdc213e3013c15fa7c3a3d0c3372a61942465c6e"; libraryHaskellDepends = [ base bytestring deepseq ghc-prim ]; doHaddock = false; doCheck = false; - homepage = "https://github.com/facebookexperimental/hs-zstd"; + homepage = "https://github.com/luispedro/hs-zstd"; description = "Haskell bindings to the Zstandard compression algorithm"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; }) {}; "ztail" = callPackage - ({ mkDerivation, array, base, bytestring, filepath, hinotify - , process, regex-posix, stdenv, time, unix, unordered-containers + ({ mkDerivation, array, base, bytestring, filepath, hinotify, lib + , process, regex-posix, time, unix, unordered-containers }: mkDerivation { pname = "ztail"; version = "1.2.0.2"; sha256 = "a14341d51da6dbef9f0edcdefe185dbd7726880ec4e230855fb9871de7c07717"; - revision = "1"; - editedCabalFile = "0d0cpgb0v849zxl12c2gkm3x4nmyfycka1pcfix43lawx62rky8s"; + revision = "2"; + editedCabalFile = "16w0hgjvj45azdgkzvykiznds5sa38mq9xf5022r7qfhpvps65y0"; isLibrary = false; isExecutable = true; executableHaskellDepends = [ @@ -39000,7 +46110,52 @@ inherit (pkgs) libjpeg; inherit (pkgs) libpng; inherit (pkgs) zlib;}; doHaddock = false; doCheck = false; description = "Multi-file, colored, filtered log tailer"; - license = stdenv.lib.licenses.bsd3; + license = lib.licenses.bsd3; + }) {}; + "zydiskell" = callPackage + ({ mkDerivation, base, bytestring, containers, fixed-vector, lib + , storable-record + }: + mkDerivation { + pname = "zydiskell"; + version = "0.2.0.0"; + sha256 = "68723d63d9021b83271b6c05194779a52eccecc532cabb3398c5b96ae8867c5d"; + libraryHaskellDepends = [ + base bytestring containers fixed-vector storable-record + ]; + doHaddock = false; + doCheck = false; + homepage = "https://github.com/nerded1337/zydiskell#readme"; + description = "Haskell language binding for the Zydis library, a x86/x86-64 disassembler"; + license = lib.licenses.gpl3Only; + }) {}; + "stack2nix" = callPackage + ({ mkDerivation, async, base, bytestring, Cabal, cabal2nix + , containers, directory, distribution-nixpkgs, filepath, hackage-db + , language-nix, lens, lib, optparse-applicative, path, path-io + , pretty, process, regex-pcre, SafeSemaphore, split, stack + , temporary, text, time + }: + mkDerivation { + pname = "stack2nix"; + version = "0.2.3"; + src = /home/niklas/src/haskell/stack2nix; + configureFlags = [ "--ghc-option=-Werror" ]; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + async base bytestring Cabal cabal2nix containers directory + distribution-nixpkgs filepath hackage-db language-nix lens + optparse-applicative path path-io pretty process regex-pcre + SafeSemaphore stack temporary text time + ]; + executableHaskellDepends = [ + base Cabal optparse-applicative split time + ]; + doHaddock = false; + doCheck = false; + description = "Convert stack.yaml files into Nix build instructions."; + license = lib.licenses.mit; }) {}; }; in compiler.override { @@ -39008,4 +46163,3 @@ in compiler.override { configurationCommon = { ... }: self: super: {}; compilerConfig = self: super: {}; } - diff --git a/stack2nix/Main.hs b/stack2nix/Main.hs index 16f07d8..b8101fe 100644 --- a/stack2nix/Main.hs +++ b/stack2nix/Main.hs @@ -1,17 +1,23 @@ +{-# LANGUAGE LambdaCase #-} + module Main ( main ) where -import Data.Semigroup ((<>)) +import Data.List (intercalate, isPrefixOf) +import Data.List.Split (splitOn) +import Data.Maybe (fromMaybe, listToMaybe) import Data.Time (UTCTime, defaultTimeLocale, parseTimeM) -import qualified Distribution.Compat.ReadP as P +import Data.Version (showVersion) import Distribution.System (Arch (..), OS (..), Platform (..), - buildPlatform) + ClassificationStrictness(..), + buildPlatform, classifyArch, classifyOS) import Distribution.Text (display) import Options.Applicative import Stack2nix import System.IO (BufferMode (..), hSetBuffering, stderr, stdout) + args :: Parser Args args = Args <$> optional (strOption $ long "revision" <> help "revision to use when fetching from VCS") @@ -22,7 +28,7 @@ args = Args <*> switch (long "bench" <> help "enable benchmarks") <*> switch (long "haddock" <> help "enable documentation generation") <*> optional (option utcTimeReader (long "hackage-snapshot" <> help "hackage snapshot time, ISO format")) - <*> option (readP platformReader) (long "platform" <> help "target platform to use when invoking stack or cabal2nix" <> value buildPlatform <> showDefaultWith display) + <*> option (maybeReader parsePlatform) (long "platform" <> help "target platform to use when invoking stack or cabal2nix" <> value buildPlatform <> showDefaultWith display) <*> strArgument (metavar "URI") <*> flag True False (long "no-indent" <> help "disable indentation and place one item per line") <*> switch (long "verbose" <> help "verbose output") @@ -39,26 +45,49 @@ args = Args -- | A String parser for Distribution.System.Platform -- | Copied from cabal2nix/src/Cabal2nix.hs - platformReader :: P.ReadP r Platform - platformReader = do - arch <- P.choice - [ P.string "i686" >> return I386 - , P.string "x86_64" >> return X86_64 - ] - _ <- P.char '-' - os <- P.choice - [ P.string "linux" >> return Linux - , P.string "osx" >> return OSX - , P.string "darwin" >> return OSX - ] - return (Platform arch os) + parsePlatform :: String -> Maybe Platform + parsePlatform = parsePlatformParts . splitOn "-" + + parsePlatformParts :: [String] -> Maybe Platform + parsePlatformParts = \case + [arch, os] -> + Just $ Platform (parseArch arch) (parseOS os) + (arch : _ : osParts) -> + Just $ Platform (parseArch arch) $ parseOS $ intercalate "-" osParts + _ -> Nothing + + parseArch :: String -> Arch + parseArch = classifyArch Permissive . ghcConvertArch - readP :: P.ReadP a a -> ReadM a - readP p = eitherReader $ \s -> - case [ r' | (r',"") <- P.readP_to_S p s ] of - (r:_) -> Right r - _ -> Left ("invalid value " ++ show s) + parseOS :: String -> OS + parseOS = classifyOS Permissive . ghcConvertOS + ghcConvertArch :: String -> String + ghcConvertArch arch = case arch of + "i486" -> "i386" + "i586" -> "i386" + "i686" -> "i386" + "amd64" -> "x86_64" + _ -> fromMaybe arch $ listToMaybe + [prefix | prefix <- archPrefixes, prefix `isPrefixOf` arch] + where archPrefixes = + [ "aarch64", "alpha", "arm", "hppa1_1", "hppa", "m68k", "mipseb" + , "mipsel", "mips", "powerpc64le", "powerpc64", "powerpc", "s390x" + , "sparc64", "sparc" + ] + -- | Replicate the normalization performed by GHC_CONVERT_OS in GHC's aclocal.m4 + -- since the output of that is what Cabal parses. + ghcConvertOS :: String -> String + ghcConvertOS os = case os of + "watchos" -> "ios" + "tvos" -> "ios" + "linux-android" -> "linux-android" + "linux-androideabi" -> "linux-androideabi" + _ | "linux-" `isPrefixOf` os -> "linux" + _ -> fromMaybe os $ listToMaybe + [prefix | prefix <- osPrefixes, prefix `isPrefixOf` os] + where osPrefixes = + [ "gnu", "openbsd", "aix", "darwin", "solaris2", "freebsd", "nto-qnx"] main :: IO () main = do @@ -68,7 +97,7 @@ main = do where opts = info (helper - <*> infoOption ("stack2nix " ++ display version) (long "version" <> help "Show version number") + <*> infoOption ("stack2nix " ++ showVersion version) (long "version" <> help "Show version number") <*> args) $ fullDesc <> progDesc "Generate a nix expression for a Haskell package using stack"