diff --git a/maintainers/maintainer-list.nix b/maintainers/maintainer-list.nix index dca8f9b96762..6afb908b7236 100644 --- a/maintainers/maintainer-list.nix +++ b/maintainers/maintainer-list.nix @@ -3591,6 +3591,12 @@ githubId = 606000; name = "Gabriel Adomnicai"; }; + Gabriel439 = { + email = "Gabriel439@gmail.com"; + github = "Gabriel439"; + githubId = 1313787; + name = "Gabriel Gonzalez"; + }; gal_bolle = { email = "florent.becker@ens-lyon.org"; github = "FlorentBecker"; diff --git a/maintainers/scripts/haskell/hydra-report.hs b/maintainers/scripts/haskell/hydra-report.hs index 3772b230f866..fd6430d43c9a 100755 --- a/maintainers/scripts/haskell/hydra-report.hs +++ b/maintainers/scripts/haskell/hydra-report.hs @@ -17,6 +17,7 @@ Because step 1) is quite expensive and takes roughly ~5 minutes the result is ca {-# LANGUAGE BlockArguments #-} {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE MultiWayIf #-} @@ -36,8 +37,6 @@ import Data.Aeson ( encodeFile, ) import Data.Foldable (Foldable (toList), foldl') -import Data.Function ((&)) -import Data.Functor ((<&>)) import Data.List.NonEmpty (NonEmpty, nonEmpty) import qualified Data.List.NonEmpty as NonEmpty import Data.Map.Strict (Map) @@ -71,7 +70,6 @@ import System.Directory (XdgDirectory (XdgCache), getXdgDirectory) import System.Environment (getArgs) import System.Process (readProcess) import Prelude hiding (id) -import qualified Prelude newtype JobsetEvals = JobsetEvals { evals :: Seq Eval @@ -132,30 +130,117 @@ getBuildReports = runReq defaultHttpConfig do hydraEvalCommand :: FilePath hydraEvalCommand = "hydra-eval-jobs" + hydraEvalParams :: [String] hydraEvalParams = ["-I", ".", "pkgs/top-level/release-haskell.nix"] + handlesCommand :: FilePath handlesCommand = "nix-instantiate" + handlesParams :: [String] handlesParams = ["--eval", "--strict", "--json", "-"] + handlesExpression :: String handlesExpression = "with import ./. {}; with lib; zipAttrsWith (_: builtins.head) (mapAttrsToList (_: v: if v ? github then { \"${v.email}\" = v.github; } else {}) (import maintainers/maintainer-list.nix))" -newtype Maintainers = Maintainers {maintainers :: Maybe Text} deriving (Generic, ToJSON, FromJSON) +-- | This newtype is used to parse a Hydra job output from @hydra-eval-jobs@. +-- The only field we are interested in is @maintainers@, which is why this +-- is just a newtype. +-- +-- Note that there are occassionally jobs that don't have a maintainers +-- field, which is why this has to be @Maybe Text@. +newtype Maintainers = Maintainers { maintainers :: Maybe Text } + deriving stock (Generic, Show) + deriving anyclass (FromJSON, ToJSON) +-- | This is a 'Map' from Hydra job name to maintainer email addresses. +-- +-- It has values similar to the following: +-- +-- @@ +-- fromList +-- [ ("arion.aarch64-linux", Maintainers (Just "robert@example.com")) +-- , ("bench.x86_64-linux", Maintainers (Just "")) +-- , ("conduit.x86_64-linux", Maintainers (Just "snoy@man.com, web@ber.com")) +-- , ("lens.x86_64-darwin", Maintainers (Just "ek@category.com")) +-- ] +-- @@ +-- +-- Note that Hydra jobs without maintainers will have an empty string for the +-- maintainer list. type HydraJobs = Map Text Maintainers + +-- | Map of email addresses to GitHub handles. +-- This is built from the file @../../maintainer-list.nix@. +-- +-- It has values similar to the following: +-- +-- @@ +-- fromList +-- [ ("robert@example.com", "rob22") +-- , ("ek@category.com", "edkm") +-- ] +-- @@ +type EmailToGitHubHandles = Map Text Text + +-- | Map of Hydra jobs to maintainer GitHub handles. +-- +-- It has values similar to the following: +-- +-- @@ +-- fromList +-- [ ("arion.aarch64-linux", ["rob22"]) +-- , ("conduit.x86_64-darwin", ["snoyb", "webber"]) +-- ] +-- @@ type MaintainerMap = Map Text (NonEmpty Text) +-- | Generate a mapping of Hydra job names to maintainer GitHub handles. getMaintainerMap :: IO MaintainerMap getMaintainerMap = do - hydraJobs :: HydraJobs <- get hydraEvalCommand hydraEvalParams "" "Failed to decode hydra-eval-jobs output: " - handlesMap :: Map Text Text <- get handlesCommand handlesParams handlesExpression "Failed to decode nix output for lookup of github handles: " - pure $ hydraJobs & Map.mapMaybe (nonEmpty . mapMaybe (`Map.lookup` handlesMap) . Text.splitOn ", " . fromMaybe "" . maintainers) - where - get c p i e = readProcess c p i <&> \x -> either (error . (<> " Raw:'" <> take 1000 x <> "'") . (e <>)) Prelude.id . eitherDecodeStrict' . encodeUtf8 . Text.pack $ x + hydraJobs :: HydraJobs <- + readJSONProcess hydraEvalCommand hydraEvalParams "" "Failed to decode hydra-eval-jobs output: " + handlesMap :: EmailToGitHubHandles <- + readJSONProcess handlesCommand handlesParams handlesExpression "Failed to decode nix output for lookup of github handles: " + pure $ Map.mapMaybe (splitMaintainersToGitHubHandles handlesMap) hydraJobs + where + -- Split a comma-spearated string of Maintainers into a NonEmpty list of + -- GitHub handles. + splitMaintainersToGitHubHandles + :: EmailToGitHubHandles -> Maintainers -> Maybe (NonEmpty Text) + splitMaintainersToGitHubHandles handlesMap (Maintainers maint) = + nonEmpty . mapMaybe (`Map.lookup` handlesMap) . Text.splitOn ", " $ fromMaybe "" maint + +-- | Run a process that produces JSON on stdout and and decode the JSON to a +-- data type. +-- +-- If the JSON-decoding fails, throw the JSON-decoding error. +readJSONProcess + :: FromJSON a + => FilePath -- ^ Filename of executable. + -> [String] -- ^ Arguments + -> String -- ^ stdin to pass to the process + -> String -- ^ String to prefix to JSON-decode error. + -> IO a +readJSONProcess exe args input err = do + output <- readProcess exe args input + let eitherDecodedOutput = eitherDecodeStrict' . encodeUtf8 . Text.pack $ output + case eitherDecodedOutput of + Left decodeErr -> error $ err <> decodeErr <> "\nRaw: '" <> take 1000 output <> "'" + Right decodedOutput -> pure decodedOutput -- BuildStates are sorted by subjective importance/concerningness -data BuildState = Failed | DependencyFailed | OutputLimitExceeded | Unknown (Maybe Int) | TimedOut | Canceled | HydraFailure | Unfinished | Success deriving (Show, Eq, Ord) +data BuildState + = Failed + | DependencyFailed + | OutputLimitExceeded + | Unknown (Maybe Int) + | TimedOut + | Canceled + | HydraFailure + | Unfinished + | Success + deriving stock (Show, Eq, Ord) icon :: BuildState -> Text icon = \case @@ -243,7 +328,7 @@ printJob evalId name (Table mapping, maintainers) = printSingleRow set = "- [ ] " <> printState set <> " " <> makeJobSearchLink set (makePkgName set) <> " " <> maintainers makePkgName set = (if Text.null set then "" else set <> ".") <> name printState set = Text.intercalate " " $ map (\pf -> maybe "" (label pf) $ Map.lookup (set, pf) mapping) platforms - makeJobSearchLink set linkLabel= makeSearchLink evalId linkLabel (makePkgName set <> ".") -- Append '.' to the search query to prevent e.g. "hspec." matching "hspec-golden.x86_64-linux" + makeJobSearchLink set linkLabel= makeSearchLink evalId linkLabel (makePkgName set) sets = toList $ Set.fromList (fst <$> Map.keys mapping) platforms = toList $ Set.fromList (snd <$> Map.keys mapping) label pf (BuildResult s i) = "[[" <> platformIcon pf <> icon s <> "]](https://hydra.nixos.org/build/" <> showT i <> ")" diff --git a/pkgs/data/misc/hackage/pin.json b/pkgs/data/misc/hackage/pin.json index 66830ea017ce..43c45c95cd6b 100644 --- a/pkgs/data/misc/hackage/pin.json +++ b/pkgs/data/misc/hackage/pin.json @@ -1,6 +1,6 @@ { - "commit": "b963dde27c24394c4be0031039dae4cb6a363aed", - "url": "https://github.com/commercialhaskell/all-cabal-hashes/archive/b963dde27c24394c4be0031039dae4cb6a363aed.tar.gz", - "sha256": "1yr9j4ldpi2p2zgdq4mky6y5yh7nilasdmskapbdxp9fxwba2r0x", - "msg": "Update from Hackage at 2021-05-10T22:01:59Z" + "commit": "2295bd36e0d36af6e862dfdb7b0694fba2e7cb58", + "url": "https://github.com/commercialhaskell/all-cabal-hashes/archive/2295bd36e0d36af6e862dfdb7b0694fba2e7cb58.tar.gz", + "sha256": "1bzqy6kbw0i1ryg3ia5spg6m62zkc46xhhn0h76pfq7mfmm3fqf8", + "msg": "Update from Hackage at 2021-05-12T11:46:04Z" } diff --git a/pkgs/development/compilers/ghc/head.nix b/pkgs/development/compilers/ghc/head.nix index 74e03550255a..a0ca13270a24 100644 --- a/pkgs/development/compilers/ghc/head.nix +++ b/pkgs/development/compilers/ghc/head.nix @@ -10,7 +10,9 @@ , # GHC can be built with system libffi or a bundled one. libffi ? null -, enableDwarf ? !stdenv.targetPlatform.isDarwin && + # Libdw.c only supports x86_64, i686 and s390x +, enableDwarf ? stdenv.targetPlatform.isx86 && + !stdenv.targetPlatform.isDarwin && !stdenv.targetPlatform.isWindows , elfutils # for DWARF support @@ -259,6 +261,8 @@ stdenv.mkDerivation (rec { description = "The Glasgow Haskell Compiler"; maintainers = with lib.maintainers; [ marcweber andres peti ]; inherit (ghc.meta) license platforms; + # ghcHEAD times out on aarch64-linux on Hydra. + hydraPlatforms = builtins.filter (p: p != "aarch64-linux") ghc.meta.platforms; }; dontStrip = (targetPlatform.useAndroidPrebuilt || targetPlatform.isWasm); diff --git a/pkgs/development/haskell-modules/configuration-arm.nix b/pkgs/development/haskell-modules/configuration-arm.nix index af4893afe54f..57e71f0e00e9 100644 --- a/pkgs/development/haskell-modules/configuration-arm.nix +++ b/pkgs/development/haskell-modules/configuration-arm.nix @@ -62,6 +62,30 @@ self: super: { hsemail-ns = dontCheck super.hsemail-ns; openapi3 = dontCheck super.openapi3; strict-writer = dontCheck super.strict-writer; + xml-html-qq = dontCheck super.xml-html-qq; + static = dontCheck super.static; + hhp = dontCheck super.hhp; + groupBy = dontCheck super.groupBy; + greskell = dontCheck super.greskell; + html-validator-cli = dontCheck super.html-validator-cli; + hw-fingertree-strict = dontCheck super.hw-fingertree-strict; + hw-prim = dontCheck super.hw-prim; + hw-packed-vector = dontCheck super.hw-packed-vector; + hw-xml = dontCheck super.hw-xml; + lens-regex = dontCheck super.lens-regex; + meep = dontCheck super.meep; + ranged-list = dontCheck super.ranged-list; + rank2classes = dontCheck super.rank2classes; + schedule = dontCheck super.schedule; + twiml = dontCheck super.twiml; + twitter-conduit = dontCheck super.twitter-conduit; + validationt = dontCheck super.validationt; + vgrep = dontCheck super.vgrep; + vulkan-utils = dontCheck super.vulkan-utils; + yaml-combinators = dontCheck super.yaml-combinators; + yesod-paginator = dontCheck super.yesod-paginator; + grammatical-parsers = dontCheck super.grammatical-parsers; + construct = dontCheck super.construct; # https://github.com/ekmett/half/issues/35 half = dontCheck super.half; diff --git a/pkgs/development/haskell-modules/configuration-common.nix b/pkgs/development/haskell-modules/configuration-common.nix index 473c2a45bfcb..693a5b61fbc4 100644 --- a/pkgs/development/haskell-modules/configuration-common.nix +++ b/pkgs/development/haskell-modules/configuration-common.nix @@ -170,18 +170,39 @@ self: super: { # base bound digit = doJailbreak super.digit; - # 2020-06-05: HACK: does not pass own build suite - `dontCheck` hnix = generateOptparseApplicativeCompletion "hnix" (overrideCabal super.hnix (drv: { + # 2020-06-05: HACK: does not pass own build suite - `dontCheck` doCheck = false; - prePatch = '' - # fix encoding problems when patching - ${pkgs.dos2unix}/bin/dos2unix hnix.cabal - '' + (drv.prePatch or ""); + # 2021-05-12: Revert a few dependency cleanups which depend on release + # that are not in stackage yet: + # * Depend on semialign-indexed for Data.Semialign.Indexed + # (remove when semialign >= 1.2 in stackage) + # * Readd dependencies to text and unordered-containers. + # (remove when relude >= 1.0.0.0 is in stackage, see + # https://github.com/haskell-nix/hnix/issues/933) + libraryHaskellDepends = [ + self.semialign-indexed + ] ++ drv.libraryHaskellDepends; patches = [ - # support ref-tf in hnix 0.12.0.1, can be removed after - # https://github.com/haskell-nix/hnix/pull/918 - ./patches/hnix-ref-tf-0.5-support.patch + # depend on semialign-indexed again + (pkgs.fetchpatch { + url = "https://github.com/haskell-nix/hnix/commit/16fc342a4f2974f855968472252cd9274609f177.patch"; + sha256 = "0gm4gy3jpn4dqnrhnqlsavfpw9c1j1xa8002v54knnlw6vpk9niy"; + revert = true; + }) + # depend on text again + (pkgs.fetchpatch { + url = "https://github.com/haskell-nix/hnix/commit/73057618576e86bb87dfd42f62b855d24bbdf469.patch"; + sha256 = "03cyk96d5ad362i1pnz9bs8ifr84kpv8phnr628gys4j6a0bqwzc"; + revert = true; + }) + # depend on unordered-containers again + (pkgs.fetchpatch { + url = "https://github.com/haskell-nix/hnix/commit/70643481883ed448b51221a030a76026fb5eb731.patch"; + sha256 = "0pqmijfkysjixg3gb4kmrqdif7s2saz8qi6k337jf15i0npzln8d"; + revert = true; + }) ] ++ (drv.patches or []); })); @@ -922,7 +943,16 @@ self: super: { # https://github.com/commercialhaskell/stackage/issues/5795 # This issue can be mitigated with 'dontCheck' which skips the tests and their compilation. dhall-json = generateOptparseApplicativeCompletions ["dhall-to-json" "dhall-to-yaml"] (dontCheck super.dhall-json); - dhall-nix = generateOptparseApplicativeCompletion "dhall-to-nix" super.dhall-nix; + # dhall-nix, dhall-nixpkgs: pull updated cabal files with updated bounds. + # Remove at next hackage update. + dhall-nix = generateOptparseApplicativeCompletion "dhall-to-nix" (overrideCabal super.dhall-nix { + revision = "2"; + editedCabalFile = "1w90jrkzmbv5nasafkkv0kyfmnqkngldx2lr891113h2mqbbr3wx"; + }); + dhall-nixpkgs = overrideCabal super.dhall-nixpkgs { + revision = "1"; + editedCabalFile = "1y08jxg51sbxx0i7ra45ii2v81plzf4hssmwlrw35l8n5gib1vcg"; + }; dhall-yaml = generateOptparseApplicativeCompletions ["dhall-to-yaml-ng" "yaml-to-dhall"] super.dhall-yaml; # https://github.com/haskell-hvr/netrc/pull/2#issuecomment-469526558 @@ -1378,6 +1408,15 @@ self: super: { # 2021-04-09: test failure # PR pending https://github.com/expipiplus1/update-nix-fetchgit/pull/60 doCheck = false; + + patches = [ + # 2021-05-17 compile with hnix >= 0.13 + # https://github.com/expipiplus1/update-nix-fetchgit/pull/64 + (pkgs.fetchpatch { + url = "https://github.com/expipiplus1/update-nix-fetchgit/commit/bc28c8b26c38093aa950574802012c0cd8447ce8.patch"; + sha256 = "1dwd1jdsrx3ss6ql1bk2ch7ln74mkq6jy9ms8vi8kmf3gbg8l9fg"; + }) + ] ++ (drv.patches or []); })); # Our quickcheck-instances is too old for the newer binary-instances, but @@ -1897,4 +1936,8 @@ EOT network = self.network-bsd; }) "-f-_old_network"; + # 2021-05-14: Testsuite is failing. + # https://github.com/kcsongor/generic-lens/issues/133 + generic-optics = dontCheck super.generic-optics; + } // import ./configuration-tensorflow.nix {inherit pkgs haskellLib;} self super diff --git a/pkgs/development/haskell-modules/configuration-hackage2nix/broken.yaml b/pkgs/development/haskell-modules/configuration-hackage2nix/broken.yaml index 5419e3f16e31..0aade87acbf2 100644 --- a/pkgs/development/haskell-modules/configuration-hackage2nix/broken.yaml +++ b/pkgs/development/haskell-modules/configuration-hackage2nix/broken.yaml @@ -1510,7 +1510,6 @@ broken-packages: - generic-lens-labels - generic-lucid-scaffold - generic-maybe - - generic-optics - generic-override-aeson - generic-pretty - genericserialize @@ -1676,6 +1675,7 @@ broken-packages: - grasp - gray-code - greencard + - greenclip - greg-client - gremlin-haskell - Grempa @@ -3037,6 +3037,7 @@ broken-packages: - multext-east-msd - multiaddr - multiarg + - multi-except - multihash - multi-instance - multilinear @@ -5155,6 +5156,7 @@ broken-packages: - yampa-glut - yampa-sdl2 - YampaSynth + - yampa-test - yam-servant - yandex-translate - yaop diff --git a/pkgs/development/haskell-modules/configuration-hackage2nix/main.yaml b/pkgs/development/haskell-modules/configuration-hackage2nix/main.yaml index 1fb67026d111..e4760fa54a23 100644 --- a/pkgs/development/haskell-modules/configuration-hackage2nix/main.yaml +++ b/pkgs/development/haskell-modules/configuration-hackage2nix/main.yaml @@ -85,6 +85,8 @@ default-package-overrides: - ghcide == 1.2.* - hls-plugin-api == 1.1.0.0 - hls-explicit-imports-plugin < 1.0.0.2 + # 2021-05-12: remove once versions >= 5.0.0 is in stackage + - futhark < 0.19.5 extra-packages: - base16-bytestring < 1 # required for cabal-install etc. @@ -115,6 +117,97 @@ extra-packages: - ShellCheck == 0.7.1 # 2021-05-09: haskell-ci 0.12.1 pins this version package-maintainers: + abbradar: + - Agda + bdesham: + - pinboard-notes-backup + cdepillabout: + - password + - password-instances + - pretty-simple + - spago + - termonad + Gabriel439: + - annah + - bench + - break + - dhall-bash + - dhall-docs + - dhall-json + - dhall-lsp-server + - dhall-nix + - dhall-nixpkgs + - dhall-openapi + - dhall-text + - dhall-yaml + - dhall + - dirstream + - errors + - foldl + - index-core + - lens-tutorial + - list-transformer + - managed + - mmorph + - morte + - mvc-updates + - mvc + - nix-derivation + - nix-diff + - optional-args + - optparse-generic + - pipes-bytestring + - pipes-concurrency + - pipes-csv + - pipes-extras + - pipes-group + - pipes-http + - pipes-parse + - pipes-safe + - pipes + - server-generic + - total + - turtle + - typed-spreadsheet + gridaphobe: + - located-base + jb55: + # - bson-lens + - cased + - elm-export-persistent + # - pipes-mongodb + - streaming-wai + kiwi: + - config-schema + - config-value + - glirc + - irc-core + - matterhorn + - mattermost-api + - mattermost-api-qc + - Unique + maralorn: + - arbtt + - cabal-fmt + - generic-optics + - ghcup + - haskell-language-server + - hedgehog + - hmatrix + - iCalendar + - neuron + - optics + - reflex-dom + - releaser + - req + - shake-bench + - shh + - snap + - stm-containers + - streamly + - taskwarrior + pacien: + - ldgallery-compiler peti: - cabal-install - cabal2nix @@ -140,31 +233,14 @@ package-maintainers: - titlecase - xmonad - xmonad-contrib - gridaphobe: - - located-base - jb55: - # - bson-lens - - cased - - elm-export-persistent - # - pipes-mongodb - - streaming-wai - kiwi: - - config-schema - - config-value - - glirc - - irc-core - - matterhorn - - mattermost-api - - mattermost-api-qc - - Unique + poscat: + - hinit psibi: - path-pieces - persistent - persistent-sqlite - persistent-template - shakespeare - abbradar: - - Agda roberth: - arion-compose - hercules-ci-agent @@ -174,22 +250,10 @@ package-maintainers: - hercules-ci-cli - hercules-ci-cnix-expr - hercules-ci-cnix-store - cdepillabout: - - pretty-simple - - spago - terlar: - - nix-diff - maralorn: - - reflex-dom - - cabal-fmt - - shh - - neuron - - releaser - - taskwarrior - - haskell-language-server - - shake-bench - - iCalendar - - stm-containers + rvl: + - taffybar + - arbtt + - lentil sorki: - cayenne-lpp - data-stm32 @@ -200,20 +264,6 @@ package-maintainers: - ttn-client - update-nix-fetchgit - zre - utdemir: - - nix-tree - turion: - - rhine - - rhine-gloss - - essence-of-live-coding - - essence-of-live-coding-gloss - - essence-of-live-coding-pulse - - essence-of-live-coding-quickcheck - - Agda - - dunai - - finite-typelits - - pulse-simple - - simple-affine-space sternenseemann: # also maintain upstream package - spacecookie @@ -229,14 +279,22 @@ package-maintainers: - yarn-lock - yarn2nix - large-hashable - poscat: - - hinit - bdesham: - - pinboard-notes-backup - rvl: - - taffybar - - arbtt - - lentil + terlar: + - nix-diff + turion: + - rhine + - rhine-gloss + - essence-of-live-coding + - essence-of-live-coding-gloss + - essence-of-live-coding-pulse + - essence-of-live-coding-quickcheck + - Agda + - dunai + - finite-typelits + - pulse-simple + - simple-affine-space + utdemir: + - nix-tree unsupported-platforms: Allure: [ x86_64-darwin ] @@ -248,6 +306,7 @@ unsupported-platforms: bdcs-api: [ x86_64-darwin ] bindings-directfb: [ x86_64-darwin ] bindings-sane: [ x86_64-darwin ] + charsetdetect: [ aarch64-linux ] # not supported by vendored lib / not configured properly https://github.com/batterseapower/libcharsetdetect/issues/3 cut-the-crap: [ x86_64-darwin ] d3d11binding: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] DirectSound: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] @@ -255,11 +314,12 @@ unsupported-platforms: dx9d3d: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] dx9d3dx: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] Euterpea: [ x86_64-darwin ] + follow-file: [ x86_64-darwin ] freenect: [ x86_64-darwin ] FTGL: [ x86_64-darwin ] ghcjs-dom-hello: [ x86_64-darwin ] - gi-dbusmenu: [ x86_64-darwin ] gi-dbusmenugtk3: [ x86_64-darwin ] + gi-dbusmenu: [ x86_64-darwin ] gi-ggit: [ x86_64-darwin ] gi-ibus: [ x86_64-darwin ] gi-ostree: [ x86_64-darwin ] @@ -271,7 +331,9 @@ unsupported-platforms: hcwiid: [ x86_64-darwin ] HFuse: [ x86_64-darwin ] hidapi: [ x86_64-darwin ] + hinotify-bytestring: [ x86_64-darwin ] hommage-ds: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] + honk: [ x86_64-darwin ] hpapi: [ x86_64-darwin ] HSoM: [ x86_64-darwin ] iwlib: [ x86_64-darwin ] @@ -283,16 +345,26 @@ unsupported-platforms: libtelnet: [ x86_64-darwin ] libzfs: [ x86_64-darwin ] linearEqSolver: [ aarch64-linux ] + linux-evdev: [ x86_64-darwin ] + linux-file-extents: [ x86_64-darwin ] + linux-inotify: [ x86_64-darwin ] + linux-mount: [ x86_64-darwin ] + linux-namespaces: [ x86_64-darwin ] lio-fs: [ x86_64-darwin ] logging-facade-journald: [ x86_64-darwin ] midi-alsa: [ x86_64-darwin ] + mpi-hs: [ aarch64-linux, x86_64-darwin ] mpi-hs-binary: [ aarch64-linux, x86_64-darwin ] mpi-hs-cereal: [ aarch64-linux, x86_64-darwin ] mpi-hs-store: [ aarch64-linux, x86_64-darwin ] - mpi-hs: [ aarch64-linux, x86_64-darwin ] mplayer-spot: [ aarch64-linux ] + netlink: [ x86_64-darwin ] oculus: [ x86_64-darwin ] pam: [ x86_64-darwin ] + parport: [ x86_64-darwin ] + password: [ aarch64-linux, armv7l-linux ] # uses scrypt, which requries x86 + password-instances: [ aarch64-linux, armv7l-linux ] # uses scrypt, which requries x86 + persist-state: [ aarch64-linux, armv7l-linux ] # https://github.com/minad/persist-state/blob/6fd68c0b8b93dec78218f6d5a1f4fa06ced4e896/src/Data/PersistState.hs#L122-L128 piyo: [ x86_64-darwin ] PortMidi-simple: [ x86_64-darwin ] PortMidi: [ x86_64-darwin ] @@ -305,6 +377,8 @@ unsupported-platforms: rtlsdr: [ x86_64-darwin ] rubberband: [ x86_64-darwin ] sbv: [ aarch64-linux ] + scat: [ aarch64-linux, armv7l-linux ] # uses scrypt, which requries x86 + scrypt: [ aarch64-linux, armv7l-linux ] # https://github.com/informatikr/scrypt/issues/8 sdl2-mixer: [ x86_64-darwin ] sdl2-ttf: [ x86_64-darwin ] synthesizer-alsa: [ x86_64-darwin ] @@ -312,22 +386,23 @@ unsupported-platforms: termonad: [ x86_64-darwin ] tokyotyrant-haskell: [ x86_64-darwin ] udev: [ x86_64-darwin ] + Unixutils-shadow: [ x86_64-darwin ] verifiable-expressions: [ aarch64-linux ] vrpn: [ x86_64-darwin ] - vulkan-utils: [ x86_64-darwin ] vulkan: [ i686-linux, armv7l-linux, x86_64-darwin ] VulkanMemoryAllocator: [ i686-linux, armv7l-linux, x86_64-darwin ] + vulkan-utils: [ x86_64-darwin ] webkit2gtk3-javascriptcore: [ x86_64-darwin ] Win32-console: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] Win32-dhcp-server: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] Win32-errors: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] Win32-extras: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] + Win32: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] Win32-junction-point: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] Win32-notify: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] Win32-security: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] - Win32-services-wrapper: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] Win32-services: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] - Win32: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] + Win32-services-wrapper: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] xattr: [ x86_64-darwin ] xgboost-haskell: [ aarch64-linux, armv7l-linux ] XInput: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] diff --git a/pkgs/development/haskell-modules/configuration-hackage2nix/transitive-broken.yaml b/pkgs/development/haskell-modules/configuration-hackage2nix/transitive-broken.yaml index e37785a67950..8acd56668d3a 100644 --- a/pkgs/development/haskell-modules/configuration-hackage2nix/transitive-broken.yaml +++ b/pkgs/development/haskell-modules/configuration-hackage2nix/transitive-broken.yaml @@ -942,7 +942,6 @@ dont-distribute-packages: - ghcjs-hplay - ghc-mod - ghc-tags-plugin - - ghcup - ghc-vis - ght - gi-cairo-again @@ -3276,6 +3275,7 @@ dont-distribute-packages: - yu-launch - yuuko - zasni-gerna + - Z-Botan - zephyr - zerobin - zeromq3-conduit diff --git a/pkgs/development/haskell-modules/configuration-nix.nix b/pkgs/development/haskell-modules/configuration-nix.nix index c5d8b418b512..52f9e94401f1 100644 --- a/pkgs/development/haskell-modules/configuration-nix.nix +++ b/pkgs/development/haskell-modules/configuration-nix.nix @@ -485,7 +485,7 @@ self: super: builtins.intersectAttrs super { # Compile manpages (which are in RST and are compiled with Sphinx). futhark = with pkgs; - overrideCabal (addBuildTools super.futhark [makeWrapper python37Packages.sphinx]) + overrideCabal (addBuildTools super.futhark [makeWrapper python3Packages.sphinx]) (_drv: { postBuild = (_drv.postBuild or "") + '' make -C docs man @@ -616,7 +616,7 @@ self: super: builtins.intersectAttrs super { primitive_0_7_1_0 = dontCheck super.primitive_0_7_1_0; cut-the-crap = - let path = pkgs.lib.makeBinPath [ pkgs.ffmpeg_3 pkgs.youtube-dl ]; + let path = pkgs.lib.makeBinPath [ pkgs.ffmpeg pkgs.youtube-dl ]; in overrideCabal (addBuildTool super.cut-the-crap pkgs.makeWrapper) (_drv: { postInstall = '' wrapProgram $out/bin/cut-the-crap \ @@ -747,6 +747,21 @@ self: super: builtins.intersectAttrs super { platforms = pkgs.lib.platforms.x86; }; + # uses x86 intrinsics + blake3 = overrideCabal super.blake3 { + platforms = pkgs.lib.platforms.x86; + }; + + # uses x86 intrinsics, see also https://github.com/NixOS/nixpkgs/issues/122014 + crc32c = overrideCabal super.crc32c { + platforms = pkgs.lib.platforms.x86; + }; + + # uses x86 intrinsics + seqalign = overrideCabal super.seqalign { + platforms = pkgs.lib.platforms.x86; + }; + hls-brittany-plugin = overrideCabal super.hls-brittany-plugin (drv: { testToolDepends = [ pkgs.git ]; preCheck = '' @@ -772,4 +787,20 @@ self: super: builtins.intersectAttrs super { export HOME=$TMPDIR/home ''; }); + + taglib = overrideCabal super.taglib (drv: { + librarySystemDepends = [ + pkgs.zlib + ] ++ (drv.librarySystemDepends or []); + }); + + # uses x86 assembler + inline-asm = overrideCabal super.inline-asm { + platforms = pkgs.lib.platforms.x86; + }; + + # uses x86 assembler in C bits + hw-prim-bits = overrideCabal super.hw-prim-bits { + platforms = pkgs.lib.platforms.x86; + }; } diff --git a/pkgs/development/haskell-modules/hackage-packages.nix b/pkgs/development/haskell-modules/hackage-packages.nix index edf0d51783ee..c04898da5280 100644 --- a/pkgs/development/haskell-modules/hackage-packages.nix +++ b/pkgs/development/haskell-modules/hackage-packages.nix @@ -20313,6 +20313,9 @@ self: { libraryHaskellDepends = [ base unix ]; description = "A simple interface to shadow passwords (aka, shadow.h)"; license = lib.licenses.bsd3; + platforms = [ + "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" + ]; }) {}; "Updater" = callPackage @@ -21749,6 +21752,29 @@ self: { hydraPlatforms = lib.platforms.none; }) {inherit (pkgs) readline;}; + "Z-Botan" = callPackage + ({ mkDerivation, base, Cabal, directory, filepath, ghc-prim, hspec + , hspec-discover, HUnit, integer-gmp, QuickCheck + , quickcheck-instances, scientific, stm, time, Z-Data, Z-IO + }: + mkDerivation { + pname = "Z-Botan"; + version = "0.2.0.0"; + sha256 = "0xxi19gfzglp93jxxq7sq9z1ijxa5jys917a156gd4hrcqqhwi63"; + enableSeparateDataOutput = true; + setupHaskellDepends = [ base Cabal directory filepath ]; + libraryHaskellDepends = [ + base ghc-prim integer-gmp scientific stm time Z-Data Z-IO + ]; + libraryToolDepends = [ hspec-discover ]; + testHaskellDepends = [ + base hspec HUnit QuickCheck quickcheck-instances Z-Data Z-IO + ]; + description = "Crypto for Haskell"; + license = lib.licenses.bsd3; + hydraPlatforms = lib.platforms.none; + }) {}; + "Z-Data" = callPackage ({ mkDerivation, base, bytestring, Cabal, case-insensitive , containers, deepseq, ghc-prim, hashable, hspec, hspec-discover @@ -29519,6 +29545,27 @@ self: { license = lib.licenses.gpl3Only; }) {}; + "amqp-utils_0_6_1_1" = callPackage + ({ mkDerivation, amqp, base, bytestring, connection, containers + , data-default-class, directory, hinotify, magic, network, process + , text, time, tls, unix, utf8-string, x509-system + }: + mkDerivation { + pname = "amqp-utils"; + version = "0.6.1.1"; + sha256 = "1lffc76ybvk73k57qn5m6788m2nkfsqavs7mfs1kaqw38pya940c"; + 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 + ]; + description = "AMQP toolset for the command line"; + license = lib.licenses.gpl3Only; + hydraPlatforms = lib.platforms.none; + }) {}; + "amqp-worker" = callPackage ({ mkDerivation, aeson, amqp, base, bytestring, data-default , exceptions, monad-control, monad-loops, mtl, resource-pool @@ -29990,6 +30037,7 @@ self: { description = "Medium-level language that desugars to Morte"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "annihilator" = callPackage @@ -32045,7 +32093,7 @@ self: { ]; description = "Automatic Rule-Based Time Tracker"; license = lib.licenses.gpl2Only; - maintainers = with lib.maintainers; [ rvl ]; + maintainers = with lib.maintainers; [ maralorn rvl ]; }) {}; "arcgrid" = callPackage @@ -39310,6 +39358,7 @@ self: { ]; description = "Command-line benchmark tool"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "bench-graph" = callPackage @@ -41955,21 +42004,24 @@ self: { }) {}; "bisc" = callPackage - ({ mkDerivation, base, configurator, directory, filepath, mtl - , selda, selda-sqlite, text + ({ mkDerivation, base, bytestring, configurator, data-default + , directory, exceptions, filepath, leveldb-haskell, mtl, selda + , selda-sqlite, snappy, text }: mkDerivation { pname = "bisc"; - version = "0.2.3.0"; - sha256 = "0x03smkfx0qnsxznlp1591gi938f15w057hywfp9497mhvkr7mxg"; + version = "0.3.0.0"; + sha256 = "097b25pp6pi7rq4xhk19g1i5v7v9hyx7ldyq0y3aj1cm50s2356m"; isLibrary = false; isExecutable = true; executableHaskellDepends = [ - base configurator directory filepath mtl selda selda-sqlite text + base bytestring configurator data-default directory exceptions + filepath leveldb-haskell mtl selda selda-sqlite text ]; - description = "A small tool that clears qutebrowser cookies"; + executableSystemDepends = [ snappy ]; + description = "A small tool that clears cookies (and more)"; license = lib.licenses.gpl3Only; - }) {}; + }) {inherit (pkgs) snappy;}; "bisect-binary" = callPackage ({ mkDerivation, base, bytestring, directory, filepath, hashable @@ -45238,6 +45290,7 @@ self: { libraryHaskellDepends = [ base mtl transformers ]; description = "Break from a loop"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "breakout" = callPackage @@ -52920,6 +52973,9 @@ self: { libraryHaskellDepends = [ base bytestring ]; description = "Character set detection using Mozilla's Universal Character Set Detector"; license = "LGPL"; + platforms = [ + "armv7l-linux" "i686-linux" "x86_64-darwin" "x86_64-linux" + ]; }) {}; "charsetdetect-ae" = callPackage @@ -57399,8 +57455,8 @@ self: { }: mkDerivation { pname = "code-conjure"; - version = "0.2.2"; - sha256 = "1rf9d6mwg965r4bnjxbcw2dzcf4fxqn9hnysxzyqxnyhrr8q4149"; + version = "0.2.4"; + sha256 = "1xb8c791zcbfywz4pcqx5n5iq6a2fh0fl2mzwl6cxapj2y700dbp"; libraryHaskellDepends = [ base express leancheck speculate template-haskell ]; @@ -58047,6 +58103,18 @@ self: { license = lib.licenses.bsd3; }) {}; + "collect-errors_0_1_3_0" = callPackage + ({ mkDerivation, base, containers, deepseq, QuickCheck }: + mkDerivation { + pname = "collect-errors"; + version = "0.1.3.0"; + sha256 = "03gzaqlgivlzlsqrzr8g1ijvi825p9kxzihhrrd06vib34bqswv8"; + libraryHaskellDepends = [ base containers deepseq QuickCheck ]; + description = "Error monad with a Float instance"; + license = lib.licenses.bsd3; + hydraPlatforms = lib.platforms.none; + }) {}; + "collection-json" = callPackage ({ mkDerivation, aeson, base, bytestring, hspec, hspec-discover , network-arbitrary, network-uri, network-uri-json, QuickCheck @@ -66458,8 +66526,8 @@ self: { }: mkDerivation { pname = "css-easings"; - version = "0.2.0.0"; - sha256 = "0i969cp4j154ddq7x2821p53qh8dnsr7f74rsdi4y9rbbls1fnpv"; + version = "0.2.1.0"; + sha256 = "0mn3h7fqp4bs7rqjzc05k29man8i77dg1avcajdyysf84azklyrw"; libraryHaskellDepends = [ aeson base blaze-markup data-default QuickCheck scientific shakespeare text @@ -66478,8 +66546,8 @@ self: { }: mkDerivation { pname = "css-selectors"; - version = "0.4.0.1"; - sha256 = "0wj16835xcr33kqpwlrqgsain0dv6dl9cxcxncxhp0c0z5bl4ysd"; + version = "0.4.0.2"; + sha256 = "1299xqp1ssxarz2i9wgzcyj4zmjry6cq02jb2a9n0vw61gw6z5g4"; libraryHaskellDepends = [ aeson array base binary blaze-markup bytestring data-default Decimal hashable QuickCheck shakespeare template-haskell text zlib @@ -73263,6 +73331,7 @@ self: { description = "A configuration language guaranteed to terminate"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "dhall" = callPackage @@ -73286,6 +73355,8 @@ self: { pname = "dhall"; version = "1.38.1"; sha256 = "0g70x2crdrkwf41gvwr718am25dmbn9bg4cml9f9va7i1vx5rsgk"; + revision = "1"; + editedCabalFile = "1830jbh5q7g7r4i5n1vhs1h8fj8zzig3l6qr9kbkk00dhhgywv8b"; isLibrary = true; isExecutable = true; enableSeparateDataOutput = true; @@ -73317,6 +73388,7 @@ self: { doCheck = false; description = "A configuration language guaranteed to terminate"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "dhall-bash" = callPackage @@ -73340,6 +73412,7 @@ self: { ]; description = "Compile Dhall to Bash"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "dhall-check" = callPackage @@ -73372,6 +73445,8 @@ self: { pname = "dhall-docs"; version = "1.0.5"; sha256 = "00s1vhwilnr6hvv56w98kc1md08lw6v80v8a7yhwrmg9qggwdc12"; + revision = "1"; + editedCabalFile = "0y8a02jxz5cap0q4b2106ck4av7haxqlv5vjhm0nmrsq10cl4nss"; isLibrary = true; isExecutable = true; enableSeparateDataOutput = true; @@ -73388,6 +73463,7 @@ self: { description = "Generate HTML docs from a dhall package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "dhall-fly" = callPackage @@ -73451,6 +73527,7 @@ self: { ]; description = "Convert between Dhall and JSON or YAML"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "dhall-lex" = callPackage @@ -73499,6 +73576,7 @@ self: { ]; description = "Language Server Protocol (LSP) server for Dhall"; license = lib.licenses.mit; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "dhall-nix" = callPackage @@ -73522,6 +73600,7 @@ self: { ]; description = "Dhall to Nix compiler"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "dhall-nixpkgs" = callPackage @@ -73543,6 +73622,7 @@ self: { ]; description = "Convert Dhall projects to Nix packages"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "dhall-openapi" = callPackage @@ -73567,6 +73647,7 @@ self: { ]; description = "Convert an OpenAPI specification to a Dhall package"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "dhall-recursive-adt" = callPackage @@ -73605,6 +73686,7 @@ self: { description = "Template text using Dhall"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; + maintainers = with lib.maintainers; [ Gabriel439 ]; broken = true; }) {}; @@ -73664,6 +73746,7 @@ self: { ]; description = "Convert between Dhall and YAML"; license = lib.licenses.gpl3Only; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "dhcp-lease-parser" = callPackage @@ -75649,6 +75732,7 @@ self: { ]; description = "Easily stream directory contents in constant memory"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "dirtree" = callPackage @@ -79489,8 +79573,8 @@ self: { }: mkDerivation { pname = "dual-tree"; - version = "0.2.2.1"; - sha256 = "17kdfnf0df0z5pkiifxrlmyd1xd7hjjaazd2kzyajl0gd00vbszx"; + version = "0.2.3.0"; + sha256 = "0qyn7kb42wvlcvb1wbf1qx3isc2y6k3hzp5iq6ab0r0llw9g6qlg"; libraryHaskellDepends = [ base monoid-extras newtype-generics semigroups ]; @@ -84534,6 +84618,7 @@ self: { ]; description = "Simplified error-handling"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "errors-ext" = callPackage @@ -93100,6 +93185,7 @@ self: { benchmarkHaskellDepends = [ base criterion ]; description = "Composable, streaming, and efficient left folds"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "foldl-exceptions" = callPackage @@ -93320,6 +93406,9 @@ self: { ]; 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; + platforms = [ + "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" + ]; }) {}; "follower" = callPackage @@ -96755,6 +96844,46 @@ self: { license = lib.licenses.isc; }) {}; + "futhark_0_19_5" = callPackage + ({ mkDerivation, aeson, alex, ansi-terminal, array, base, binary + , blaze-html, bmp, bytestring, bytestring-to-vector, cmark-gfm + , containers, directory, directory-tree, dlist, file-embed + , filepath, free, gitrev, happy, hashable, haskeline + , language-c-quote, mainland-pretty, megaparsec, mtl + , neat-interpolation, parallel, parser-combinators, pcg-random + , process, process-extras, QuickCheck, regex-tdfa, srcloc, tasty + , tasty-hunit, tasty-quickcheck, template-haskell, temporary + , terminal-size, text, time, transformers, unordered-containers + , utf8-string, vector, vector-binary-instances, versions + , zip-archive, zlib + }: + mkDerivation { + pname = "futhark"; + version = "0.19.5"; + sha256 = "1x922g3iq50an8jv75370qr0qslmxnrrqbwr7adca30ljaa7nfvh"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson ansi-terminal array base binary blaze-html bmp bytestring + bytestring-to-vector cmark-gfm containers directory directory-tree + dlist file-embed filepath free gitrev hashable haskeline + language-c-quote mainland-pretty megaparsec mtl neat-interpolation + parallel pcg-random process process-extras regex-tdfa srcloc + template-haskell temporary terminal-size text time transformers + unordered-containers utf8-string vector vector-binary-instances + versions zip-archive zlib + ]; + libraryToolDepends = [ alex happy ]; + executableHaskellDepends = [ base text ]; + testHaskellDepends = [ + base containers megaparsec mtl parser-combinators QuickCheck tasty + tasty-hunit tasty-quickcheck text + ]; + description = "An optimising compiler for a functional, array-oriented language"; + license = lib.licenses.isc; + hydraPlatforms = lib.platforms.none; + }) {}; + "futhask" = callPackage ({ mkDerivation, base, directory, raw-strings-qq, split }: mkDerivation { @@ -98605,8 +98734,7 @@ self: { ]; description = "Generically derive traversals, lenses and prisms"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; + maintainers = with lib.maintainers; [ maralorn ]; }) {}; "generic-optics-lite" = callPackage @@ -101636,6 +101764,8 @@ self: { pname = "ghcide"; version = "1.2.0.2"; sha256 = "0r3n23i4b51bb92q6pch9knj079a26jbz0q70qfpv66154d00wld"; + revision = "1"; + editedCabalFile = "1hv74yx0x6hh506kwg7ygkajkcczfn3l00f8rc4jnr3hkhkm5v85"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ @@ -102050,7 +102180,7 @@ self: { }) {}; "ghcup" = callPackage - ({ mkDerivation, aeson, aeson-pretty, ascii-string, async, base + ({ mkDerivation, aeson, aeson-pretty, async, base , base16-bytestring, binary, bytestring, bz2, case-insensitive , casing, concurrent-output, containers, cryptohash-sha256 , generic-arbitrary, generics-sop, haskus-utils-types @@ -102067,15 +102197,13 @@ self: { }: mkDerivation { pname = "ghcup"; - version = "0.1.14.1"; - sha256 = "1lx6ahn4mvjzs3x4qm32sdn1n8w4v7jqj2jslvan008zk664d5l2"; - revision = "1"; - editedCabalFile = "0a9c2ha61mlz9ci652djy4vmmzi4s1g8rwl1a2miymrw5b36zsmq"; + version = "0.1.14.2"; + sha256 = "1k18ira2i2ja4hd65fdxk3ab21xzh4fvd982q2rfjshzkds1a3hv"; isLibrary = true; isExecutable = true; libraryHaskellDepends = [ - aeson ascii-string async base base16-bytestring binary bytestring - bz2 case-insensitive casing concurrent-output containers + aeson async base base16-bytestring binary bytestring bz2 + case-insensitive casing concurrent-output containers cryptohash-sha256 generics-sop haskus-utils-types haskus-utils-variant hpath hpath-directory hpath-filepath hpath-io hpath-posix libarchive lzma-static megaparsec monad-logger mtl @@ -102100,7 +102228,7 @@ self: { ]; description = "ghc toolchain installer"; license = lib.licenses.lgpl3Only; - hydraPlatforms = lib.platforms.none; + maintainers = with lib.maintainers; [ maralorn ]; }) {}; "ghczdecode" = callPackage @@ -110624,24 +110752,29 @@ self: { "greenclip" = callPackage ({ mkDerivation, base, binary, bytestring, directory, exceptions - , hashable, libXau, microlens, microlens-mtl, protolude, text, unix - , vector, wordexp, X11, xcb, xdmcp, xlibsWrapper + , hashable, libXau, microlens, microlens-mtl, protolude, text + , tomland, unix, vector, wordexp, X11, xcb, xdmcp, xlibsWrapper + , xscrnsaver }: mkDerivation { pname = "greenclip"; - version = "3.4.0"; - sha256 = "0763nnh7k4blkamlswnapwxyqfn1l0g6ibpz7k1w2w2asj7a3q98"; + version = "4.1.0"; + sha256 = "1z52ffb3f0iflls3bjlwzpz4w3a904vj67c1zsdyql6j2xpln6n4"; isLibrary = false; isExecutable = true; executableHaskellDepends = [ base binary bytestring directory exceptions hashable microlens - microlens-mtl protolude text unix vector wordexp X11 + microlens-mtl protolude text tomland unix vector wordexp X11 + ]; + executablePkgconfigDepends = [ + libXau xcb xdmcp xlibsWrapper xscrnsaver ]; - executablePkgconfigDepends = [ libXau xcb xdmcp xlibsWrapper ]; description = "Simple clipboard manager to be integrated with rofi"; license = lib.licenses.bsd3; + hydraPlatforms = lib.platforms.none; + broken = true; }) {inherit (pkgs.xorg) libXau; xcb = null; xdmcp = null; - inherit (pkgs) xlibsWrapper;}; + inherit (pkgs) xlibsWrapper; xscrnsaver = null;}; "greg-client" = callPackage ({ mkDerivation, base, binary, bytestring, clock, hostname, network @@ -113417,6 +113550,26 @@ self: { maintainers = with lib.maintainers; [ peti ]; }) {}; + "hackage-db_2_1_1" = callPackage + ({ mkDerivation, aeson, base, bytestring, Cabal, containers + , directory, exceptions, filepath, tar, time, utf8-string + }: + mkDerivation { + pname = "hackage-db"; + version = "2.1.1"; + sha256 = "16y1iqb3y019hjdsq7q3zx51qy834ky3mw5vszqmzzhflqpicd31"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson base bytestring Cabal containers directory exceptions + filepath tar time utf8-string + ]; + description = "Access cabal-install's Hackage database via Data.Map"; + license = lib.licenses.bsd3; + hydraPlatforms = lib.platforms.none; + maintainers = with lib.maintainers; [ peti ]; + }) {}; + "hackage-diff" = callPackage ({ mkDerivation, ansi-terminal, async, attoparsec, base, Cabal , cpphs, directory, filepath, haskell-src-exts, HTTP, mtl, process @@ -124293,6 +124446,7 @@ self: { ]; description = "Release with confidence"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ maralorn ]; }) {}; "hedgehog-checkers" = callPackage @@ -128048,6 +128202,9 @@ self: { ]; description = "Haskell binding to inotify, using ByteString filepaths"; license = lib.licenses.bsd3; + platforms = [ + "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" + ]; }) {}; "hinquire" = callPackage @@ -130103,6 +130260,7 @@ self: { librarySystemDepends = [ openblasCompat ]; description = "Numeric Linear Algebra"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ maralorn ]; }) {inherit (pkgs) openblasCompat;}; "hmatrix-backprop" = callPackage @@ -130752,18 +130910,16 @@ self: { , http-types, lens-family, lens-family-core, lens-family-th, logict , megaparsec, monad-control, monadlist, mtl, neat-interpolation , optparse-applicative, parser-combinators, pretty-show - , prettyprinter, process, ref-tf, regex-tdfa, repline, scientific - , semialign, semialign-indexed, serialise, some, split, syb, tasty + , prettyprinter, process, ref-tf, regex-tdfa, relude, repline + , scientific, semialign, serialise, some, split, syb, tasty , tasty-hedgehog, tasty-hunit, tasty-th, template-haskell, text - , these, time, transformers, transformers-base, unix - , unordered-containers, vector, xml + , th-lift-instances, these, time, transformers, transformers-base + , unix, unordered-containers, vector, xml }: mkDerivation { pname = "hnix"; - version = "0.12.0.1"; - sha256 = "013jlmzzr5fcvl0w9rrvhsg8jikg0hbc8z57yzxgz109x7hrnjzc"; - revision = "1"; - editedCabalFile = "136lwfb5hjwdbfik5c5dw1nhsmy8v410czmjn4i242s8jv5wm9yb"; + version = "0.13.0.1"; + sha256 = "1c01ns9h7va6ri568c0hzcdkmr0jdiay5z1vwwva7cv7dlvn6wl7"; isLibrary = true; isExecutable = true; enableSeparateDataOutput = true; @@ -130775,27 +130931,24 @@ self: { lens-family lens-family-core lens-family-th logict megaparsec monad-control monadlist mtl neat-interpolation optparse-applicative parser-combinators pretty-show prettyprinter process ref-tf - regex-tdfa scientific semialign semialign-indexed serialise some - split syb template-haskell text these time transformers + regex-tdfa relude scientific semialign serialise some split syb + template-haskell text th-lift-instances these time transformers transformers-base unix unordered-containers vector xml ]; executableHaskellDepends = [ - aeson base base16-bytestring bytestring comonad containers data-fix - deepseq exceptions filepath free haskeline mtl optparse-applicative - pretty-show prettyprinter ref-tf repline serialise template-haskell - text time transformers unordered-containers + aeson base comonad containers data-fix deepseq exceptions filepath + free haskeline optparse-applicative pretty-show prettyprinter + ref-tf relude repline serialise template-haskell time ]; testHaskellDepends = [ - base base16-bytestring bytestring containers data-fix deepseq Diff - directory exceptions filepath Glob hedgehog megaparsec mtl - neat-interpolation optparse-applicative pretty-show prettyprinter - process serialise split tasty tasty-hedgehog tasty-hunit tasty-th - template-haskell text time transformers unix unordered-containers + base containers data-fix Diff directory exceptions filepath Glob + hedgehog megaparsec neat-interpolation optparse-applicative + pretty-show prettyprinter process relude serialise split tasty + tasty-hedgehog tasty-hunit tasty-th template-haskell time unix ]; benchmarkHaskellDepends = [ - base base16-bytestring bytestring containers criterion data-fix - deepseq exceptions filepath mtl optparse-applicative serialise - template-haskell text time transformers unordered-containers + base criterion data-fix exceptions filepath optparse-applicative + relude serialise template-haskell time ]; description = "Haskell implementation of the Nix language"; license = lib.licenses.bsd3; @@ -131586,6 +131739,9 @@ self: { libraryHaskellDepends = [ base ]; description = "Cross-platform interface to the PC speaker"; license = lib.licenses.asl20; + platforms = [ + "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" + ]; }) {}; "hoobuddy" = callPackage @@ -136884,6 +137040,22 @@ self: { license = lib.licenses.mit; }) {}; + "hspec_2_8_1" = callPackage + ({ mkDerivation, base, hspec-core, hspec-discover + , hspec-expectations, QuickCheck + }: + mkDerivation { + pname = "hspec"; + version = "2.8.1"; + sha256 = "1lk7xylld960wld755j1f81zaydxgxq3840np4h6xcp729cf0cq5"; + libraryHaskellDepends = [ + base hspec-core hspec-discover hspec-expectations QuickCheck + ]; + description = "A Testing Framework for Haskell"; + license = lib.licenses.mit; + hydraPlatforms = lib.platforms.none; + }) {}; + "hspec-attoparsec" = callPackage ({ mkDerivation, attoparsec, base, bytestring, hspec , hspec-expectations, text @@ -136966,6 +137138,34 @@ self: { license = lib.licenses.mit; }) {}; + "hspec-core_2_8_1" = callPackage + ({ mkDerivation, ansi-terminal, array, base, call-stack, clock + , deepseq, directory, filepath, hspec-expectations, hspec-meta + , HUnit, process, QuickCheck, quickcheck-io, random, setenv + , silently, stm, temporary, tf-random, transformers + }: + mkDerivation { + pname = "hspec-core"; + version = "2.8.1"; + sha256 = "1yha64zfc226pc4952zqwv229kbl8p5grhl7c6wxn2y948rb688a"; + libraryHaskellDepends = [ + ansi-terminal array base call-stack clock deepseq directory + filepath hspec-expectations HUnit QuickCheck quickcheck-io random + setenv stm tf-random transformers + ]; + testHaskellDepends = [ + ansi-terminal array base call-stack clock deepseq directory + filepath hspec-expectations hspec-meta HUnit process QuickCheck + quickcheck-io random setenv silently stm temporary tf-random + transformers + ]; + testToolDepends = [ hspec-meta ]; + testTarget = "--test-option=--skip --test-option='Test.Hspec.Core.Runner.hspecResult runs specs in parallel'"; + description = "A Testing Framework for Haskell"; + license = lib.licenses.mit; + hydraPlatforms = lib.platforms.none; + }) {}; + "hspec-dirstream" = callPackage ({ mkDerivation, base, dirstream, filepath, hspec, hspec-core , pipes, pipes-safe, system-filepath, text @@ -137003,6 +137203,26 @@ self: { license = lib.licenses.mit; }) {}; + "hspec-discover_2_8_1" = callPackage + ({ mkDerivation, base, directory, filepath, hspec-meta, QuickCheck + }: + mkDerivation { + pname = "hspec-discover"; + version = "2.8.1"; + sha256 = "05xzxsxpxf7hyg6zdf7mxx6xb79rxrhd3pz3pwj32a0phbjkicdn"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ base directory filepath ]; + executableHaskellDepends = [ base directory filepath ]; + testHaskellDepends = [ + base directory filepath hspec-meta QuickCheck + ]; + testToolDepends = [ hspec-meta ]; + description = "Automatically discover and run Hspec tests"; + license = lib.licenses.mit; + hydraPlatforms = lib.platforms.none; + }) {}; + "hspec-expectations" = callPackage ({ mkDerivation, base, call-stack, HUnit, nanospec }: mkDerivation { @@ -146150,6 +146370,7 @@ self: { description = "Indexed Types"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; + maintainers = with lib.maintainers; [ Gabriel439 ]; broken = true; }) {}; @@ -153160,8 +153381,8 @@ self: { }: mkDerivation { pname = "jvm-binary"; - version = "0.9.0"; - sha256 = "1ks5mbp1anrgm100sf3ycv1prwm3vj1vyag7l0ihs4cr2sqzq3a2"; + version = "0.10.0"; + sha256 = "11c3rhny06zjw8xv830khq1kdjbpzkr7wmzzymld4zcmhfmk9qda"; enableSeparateDataOutput = true; libraryHaskellDepends = [ attoparsec base binary bytestring containers data-binary-ieee754 @@ -160276,6 +160497,7 @@ self: { description = "Tutorial for the lens library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; + maintainers = with lib.maintainers; [ Gabriel439 ]; broken = true; }) {}; @@ -163082,6 +163304,9 @@ self: { libraryHaskellDepends = [ base bytestring time unix ]; description = "Bindings to Linux evdev input device interface"; license = lib.licenses.bsd3; + platforms = [ + "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" + ]; }) {}; "linux-file-extents" = callPackage @@ -163095,6 +163320,9 @@ self: { libraryHaskellDepends = [ base unix ]; description = "Retrieve file fragmentation information under Linux"; license = lib.licenses.bsd3; + platforms = [ + "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" + ]; }) {}; "linux-framebuffer" = callPackage @@ -163118,6 +163346,9 @@ self: { libraryHaskellDepends = [ base bytestring hashable unix ]; description = "Thinner binding to the Linux Kernel's inotify interface"; license = lib.licenses.bsd3; + platforms = [ + "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" + ]; }) {}; "linux-kmod" = callPackage @@ -163143,6 +163374,9 @@ self: { libraryHaskellDepends = [ base bytestring ]; description = "Mount and unmount filesystems"; license = lib.licenses.bsd3; + platforms = [ + "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" + ]; }) {}; "linux-namespaces" = callPackage @@ -163154,6 +163388,9 @@ self: { libraryHaskellDepends = [ base bytestring unix ]; description = "Work with linux namespaces: create new or enter existing ones"; license = lib.licenses.bsd3; + platforms = [ + "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" + ]; }) {}; "linux-perf" = callPackage @@ -163873,6 +164110,7 @@ self: { testHaskellDepends = [ base doctest ]; description = "List monad transformer"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "list-tries" = callPackage @@ -168550,6 +168788,7 @@ self: { libraryHaskellDepends = [ base transformers ]; description = "A monad for managed values"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "manatee" = callPackage @@ -174494,6 +174733,26 @@ self: { license = lib.licenses.bsd3; }) {}; + "mixed-types-num_0_5_1_0" = callPackage + ({ mkDerivation, base, collect-errors, hspec, hspec-smallcheck, mtl + , QuickCheck, smallcheck, template-haskell + }: + mkDerivation { + pname = "mixed-types-num"; + version = "0.5.1.0"; + sha256 = "09dkrx05mlbdvy1334q6zg3ay6k0ydl87naxhg4zr5p51i9p8lsg"; + libraryHaskellDepends = [ + base collect-errors hspec hspec-smallcheck mtl QuickCheck + smallcheck template-haskell + ]; + testHaskellDepends = [ + base collect-errors hspec hspec-smallcheck QuickCheck smallcheck + ]; + description = "Alternative Prelude with numeric and logic expressions typed bottom-up"; + license = lib.licenses.bsd3; + hydraPlatforms = lib.platforms.none; + }) {}; + "mixpanel-client" = callPackage ({ mkDerivation, aeson, base, base64-bytestring, bytestring, hspec , hspec-discover, http-client, http-client-tls, markdown-unlit @@ -174749,6 +175008,7 @@ self: { description = "Monad morphisms"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "mmorph" = callPackage @@ -174764,6 +175024,7 @@ self: { ]; description = "Monad morphisms"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "mmsyn2" = callPackage @@ -175022,16 +175283,17 @@ self: { "mnist-idx-conduit" = callPackage ({ mkDerivation, base, binary, bytestring, conduit, containers - , exceptions, resourcet, vector + , exceptions, hspec, resourcet, vector }: mkDerivation { pname = "mnist-idx-conduit"; - version = "0.2.0.0"; - sha256 = "1m6xxw59yyf60zp0s3qd2pmsps482qws2vlnfqjz2wgr4rj0cp1x"; + version = "0.3.0.0"; + sha256 = "0vqb4yhb51lykcd66kgh9dn14nf4xfr74hamg72s35aa22lhw932"; libraryHaskellDepends = [ - base binary bytestring conduit containers exceptions resourcet - vector + base binary bytestring conduit containers exceptions hspec + resourcet vector ]; + testHaskellDepends = [ base bytestring conduit hspec vector ]; description = "conduit utilities for MNIST IDX files"; license = lib.licenses.bsd3; }) {}; @@ -178189,6 +178451,7 @@ self: { description = "A bare-bones calculus of constructions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; + maintainers = with lib.maintainers; [ Gabriel439 ]; broken = true; }) {}; @@ -179773,6 +180036,21 @@ self: { license = lib.licenses.bsd3; }) {}; + "multi-except" = callPackage + ({ mkDerivation, base, dlist }: + mkDerivation { + pname = "multi-except"; + version = "0.1.0.0"; + sha256 = "0gqmj28anzl596akgkqpgk5cd4b1ic2m6dxzv3hhnvifyxxflli8"; + revision = "1"; + editedCabalFile = "1w1zzsd87qzzad8yqq28hf5amg17i94x9snxvya4pn5raibn24sm"; + libraryHaskellDepends = [ base dlist ]; + description = "Multiple Exceptions"; + license = lib.licenses.mit; + hydraPlatforms = lib.platforms.none; + broken = true; + }) {}; + "multi-instance" = callPackage ({ mkDerivation, base, doctest }: mkDerivation { @@ -181072,6 +181350,7 @@ self: { description = "Model-view-controller"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; + maintainers = with lib.maintainers; [ Gabriel439 ]; broken = true; }) {}; @@ -181085,6 +181364,7 @@ self: { description = "Concurrent and combinable updates"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "mvclient" = callPackage @@ -183488,6 +183768,9 @@ self: { executableHaskellDepends = [ base ]; description = "Netlink communication for Haskell"; license = lib.licenses.bsd3; + platforms = [ + "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" + ]; }) {}; "netlist" = callPackage @@ -185792,7 +186075,7 @@ self: { benchmarkHaskellDepends = [ attoparsec base criterion text ]; description = "Parse and render *.drv files"; license = lib.licenses.bsd3; - maintainers = with lib.maintainers; [ sorki ]; + maintainers = with lib.maintainers; [ Gabriel439 sorki ]; }) {}; "nix-diff" = callPackage @@ -185812,7 +186095,7 @@ self: { ]; description = "Explain why two Nix derivations differ"; license = lib.licenses.bsd3; - maintainers = with lib.maintainers; [ terlar ]; + maintainers = with lib.maintainers; [ Gabriel439 terlar ]; }) {}; "nix-eval" = callPackage @@ -191079,6 +191362,7 @@ self: { ]; description = "Optics as an abstract interface"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ maralorn ]; }) {}; "optics_0_4" = callPackage @@ -191108,6 +191392,7 @@ self: { description = "Optics as an abstract interface"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; + maintainers = with lib.maintainers; [ maralorn ]; }) {}; "optics-core" = callPackage @@ -191368,6 +191653,7 @@ self: { libraryHaskellDepends = [ base ]; description = "Optional function arguments"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "options" = callPackage @@ -191494,6 +191780,7 @@ self: { ]; description = "Auto-generate a command-line parser for your datatype"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "optparse-helper" = callPackage @@ -191774,11 +192061,11 @@ self: { }: mkDerivation { pname = "ordinal"; - version = "0.4.0.0"; - sha256 = "1k0hpp5p546zlvwsy1d8hypryfwqvqdifmk3cqifw3xsdrqv3d8y"; + version = "0.4.0.3"; + sha256 = "1ar7l68cx9zci7mi6qx7a6ja7vp9axxjczyzxrbnjrvd2k3zxg51"; libraryHaskellDepends = [ - base containers data-default regex template-haskell text time - vector + base containers data-default QuickCheck regex template-haskell text + time vector ]; testHaskellDepends = [ base hspec QuickCheck text ]; testToolDepends = [ hspec-discover ]; @@ -193894,6 +194181,48 @@ self: { license = lib.licenses.bsd3; }) {}; + "pantry_0_5_2" = callPackage + ({ mkDerivation, aeson, ansi-terminal, base, bytestring, Cabal + , casa-client, casa-types, conduit, conduit-extra, containers + , cryptonite, cryptonite-conduit, digest, exceptions, filelock + , generic-deriving, hackage-security, hedgehog, hpack, hspec + , http-client, http-client-tls, http-conduit, http-download + , http-types, memory, mtl, network-uri, path, path-io, persistent + , persistent-sqlite, persistent-template, primitive, QuickCheck + , raw-strings-qq, 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"; + sha256 = "0gg4fzqsh4c41vydrwr12kb8ahj0xy0vy7axwpd9j39dzxwcksnv"; + 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 + ]; + testHaskellDepends = [ + aeson ansi-terminal base bytestring Cabal casa-client casa-types + conduit conduit-extra containers cryptonite cryptonite-conduit + digest exceptions filelock generic-deriving hackage-security + hedgehog hpack hspec http-client http-client-tls http-conduit + http-download http-types memory mtl network-uri path path-io + persistent persistent-sqlite persistent-template primitive + QuickCheck raw-strings-qq resourcet rio rio-orphans rio-prettyprint + tar-conduit text text-metrics time transformers unix-compat + unliftio unordered-containers vector yaml zip-archive + ]; + description = "Content addressable Haskell package management"; + license = lib.licenses.bsd3; + hydraPlatforms = lib.platforms.none; + }) {}; + "pantry-tmp" = callPackage ({ mkDerivation, aeson, ansi-terminal, array, base, base-orphans , base64-bytestring, bytestring, Cabal, conduit, conduit-extra @@ -194754,6 +195083,9 @@ self: { libraryHaskellDepends = [ array base ]; description = "Simply interfacing the parallel port on linux"; license = "GPL"; + platforms = [ + "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" + ]; }) {}; "parquet-hs" = callPackage @@ -195640,6 +195972,8 @@ self: { ]; description = "Hashing and checking of passwords"; license = lib.licenses.bsd3; + platforms = [ "i686-linux" "x86_64-darwin" "x86_64-linux" ]; + maintainers = with lib.maintainers; [ cdepillabout ]; }) {}; "password-instances" = callPackage @@ -195663,6 +195997,8 @@ self: { ]; description = "typeclass instances for password package"; license = lib.licenses.bsd3; + platforms = [ "i686-linux" "x86_64-darwin" "x86_64-linux" ]; + maintainers = with lib.maintainers; [ cdepillabout ]; }) {}; "password-types" = callPackage @@ -197798,6 +198134,7 @@ self: { ]; description = "Serialization library with state and leb128 encoding"; license = lib.licenses.bsd3; + platforms = [ "i686-linux" "x86_64-darwin" "x86_64-linux" ]; }) {}; "persist2er" = callPackage @@ -197885,7 +198222,7 @@ self: { maintainers = with lib.maintainers; [ psibi ]; }) {}; - "persistent_2_13_0_0" = callPackage + "persistent_2_13_0_1" = callPackage ({ mkDerivation, aeson, attoparsec, base, base64-bytestring , blaze-html, bytestring, conduit, containers, criterion, deepseq , deepseq-generics, fast-logger, file-embed, hspec, http-api-data @@ -197897,10 +198234,8 @@ self: { }: mkDerivation { pname = "persistent"; - version = "2.13.0.0"; - sha256 = "1addkfiaixk076qkdlhjmx97f8bgfmxwna9dv0h7hfvnq8v35bkf"; - revision = "2"; - editedCabalFile = "12ylw4rzrjlk2m0qfgqx481k0ifhv5i8z0vy70knjrkgx8d9sfvx"; + version = "2.13.0.1"; + sha256 = "0yvipx9y33pr1vz7818w2ylr5zf9bmng8ka70mdb4f563l4ynp96"; libraryHaskellDepends = [ aeson attoparsec base base64-bytestring blaze-html bytestring conduit containers fast-logger http-api-data lift-type monad-logger @@ -200680,6 +201015,7 @@ self: { ]; description = "Compositional pipelines"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "pipes-aeson" = callPackage @@ -200845,6 +201181,7 @@ self: { ]; description = "ByteString support for pipes"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "pipes-bzip" = callPackage @@ -201013,6 +201350,7 @@ self: { testHaskellDepends = [ async base pipes stm ]; description = "Concurrency for the pipes ecosystem"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "pipes-conduit" = callPackage @@ -201075,6 +201413,7 @@ self: { ]; description = "Fast, streaming csv parser"; license = lib.licenses.mit; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "pipes-errors" = callPackage @@ -201134,6 +201473,7 @@ self: { ]; description = "Extra utilities for pipes"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "pipes-fastx" = callPackage @@ -201217,6 +201557,7 @@ self: { testHaskellDepends = [ base doctest lens-family-core ]; description = "Group streams into substreams"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "pipes-http" = callPackage @@ -201234,6 +201575,7 @@ self: { ]; description = "HTTP client with pipes interface"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "pipes-illumina" = callPackage @@ -201495,6 +201837,7 @@ self: { libraryHaskellDepends = [ base pipes transformers ]; description = "Parsing infrastructure for the pipes ecosystem"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "pipes-postgresql-simple" = callPackage @@ -201617,6 +201960,7 @@ self: { ]; description = "Safety for the pipes ecosystem"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "pipes-shell" = callPackage @@ -202621,6 +202965,25 @@ self: { license = lib.licenses.bsd3; }) {}; + "ploterific" = callPackage + ({ mkDerivation, base, bytestring, cassava, containers, hvega + , hvega-theme, lens, mtl, optparse-generic, text + }: + mkDerivation { + pname = "ploterific"; + version = "0.1.0.1"; + sha256 = "03m0zi7izlv8n5jsisym595sn7cfl2p1mhch086ajyd2g6zlxya7"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + base bytestring cassava containers hvega hvega-theme lens mtl + optparse-generic text + ]; + executableHaskellDepends = [ base mtl optparse-generic text ]; + description = "Basic plotting of tabular data for the command line"; + license = lib.licenses.gpl3Only; + }) {}; + "plotfont" = callPackage ({ mkDerivation, base, containers, tasty, tasty-hunit }: mkDerivation { @@ -209849,6 +210212,30 @@ self: { license = lib.licenses.asl20; }) {}; + "proto3-wire_1_2_2" = callPackage + ({ mkDerivation, base, bytestring, cereal, containers, deepseq + , doctest, ghc-prim, hashable, parameterized, primitive, QuickCheck + , safe, tasty, tasty-hunit, tasty-quickcheck, text, transformers + , unordered-containers, vector + }: + mkDerivation { + pname = "proto3-wire"; + version = "1.2.2"; + sha256 = "1fdzml0nsbz1bqf3lskvmfn46pgl5rnrc4b7azq8f0csm0v9ah4d"; + libraryHaskellDepends = [ + base bytestring cereal containers deepseq ghc-prim hashable + parameterized primitive QuickCheck safe text transformers + unordered-containers vector + ]; + testHaskellDepends = [ + base bytestring cereal doctest QuickCheck tasty tasty-hunit + tasty-quickcheck text transformers vector + ]; + description = "A low-level implementation of the Protocol Buffers (version 3) wire format"; + license = lib.licenses.asl20; + hydraPlatforms = lib.platforms.none; + }) {}; + "protobuf" = callPackage ({ mkDerivation, base, base-orphans, bytestring, cereal, containers , data-binary-ieee754, deepseq, hex, HUnit, mtl, QuickCheck, tagged @@ -220685,6 +221072,7 @@ self: { doCheck = false; description = "Easy-to-use, type-safe, expandable, high-level HTTP client library"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ maralorn ]; }) {}; "req-conduit" = callPackage @@ -226978,6 +227366,7 @@ self: { ]; description = "Generates unique passwords for various websites from a single password"; license = lib.licenses.bsd3; + platforms = [ "i686-linux" "x86_64-darwin" "x86_64-linux" ]; }) {}; "scc" = callPackage @@ -228137,6 +228526,7 @@ self: { ]; description = "Stronger password hashing via sequential memory-hard functions"; license = lib.licenses.bsd3; + platforms = [ "i686-linux" "x86_64-darwin" "x86_64-linux" ]; }) {}; "scrz" = callPackage @@ -233042,6 +233432,7 @@ self: { description = "Auto-generate a server for your datatype"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; + maintainers = with lib.maintainers; [ Gabriel439 ]; broken = true; }) {}; @@ -239408,6 +239799,7 @@ self: { ]; description = "Top-level package for the Snap Web Framework"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ maralorn ]; }) {}; "snap-accept" = callPackage @@ -247555,6 +247947,7 @@ self: { ]; description = "Beautiful Streaming, Concurrent and Reactive Composition"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ maralorn ]; }) {}; "streamly-archive" = callPackage @@ -248228,8 +248621,8 @@ self: { ({ mkDerivation, base, bytestring, text }: mkDerivation { pname = "string-like"; - version = "0.1.0.0"; - sha256 = "1b87532fhv2wn6pnzsaw20lzj5j399smlfn7lai0h0ph2axb2dbi"; + version = "0.1.0.1"; + sha256 = "1sadf4cdxs3ilax99w1yvkfz2v1n77rj9grck4csjbwswxw2d2dn"; libraryHaskellDepends = [ base bytestring text ]; description = "A package that aims to provide a uniform interface to string-like types"; license = lib.licenses.bsd3; @@ -256106,6 +256499,7 @@ self: { platforms = [ "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" ]; + maintainers = with lib.maintainers; [ cdepillabout ]; }) {inherit (pkgs) gtk3; inherit (pkgs) pcre2; vte_291 = pkgs.vte;}; @@ -262275,6 +262669,7 @@ self: { libraryHaskellDepends = [ base void ]; description = "Exhaustive pattern matching using lenses, traversals, and prisms"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "total-alternative" = callPackage @@ -265151,6 +265546,7 @@ self: { benchmarkHaskellDepends = [ base criterion text ]; description = "Shell programming, Haskell-style"; license = lib.licenses.bsd3; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "turtle-options" = callPackage @@ -265184,6 +265580,23 @@ self: { license = lib.licenses.bsd3; }) {}; + "twain" = callPackage + ({ mkDerivation, aeson, base, bytestring, case-insensitive, cookie + , either, http-types, text, time, transformers, wai, wai-extra + , warp + }: + mkDerivation { + pname = "twain"; + version = "1.0.0.0"; + sha256 = "0brxvqddnhxs4q5hm9g8fzkznk3xjagivy0glfiqrx24p4k8s9yb"; + libraryHaskellDepends = [ + aeson base bytestring case-insensitive cookie either http-types + text time transformers wai wai-extra warp + ]; + description = "Tiny web application framework for WAI"; + license = lib.licenses.bsd3; + }) {}; + "tweak" = callPackage ({ mkDerivation, base, containers, lens, stm, transformers }: mkDerivation { @@ -266761,6 +267174,7 @@ self: { description = "Typed and composable spreadsheets"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; + maintainers = with lib.maintainers; [ Gabriel439 ]; }) {}; "typed-streams" = callPackage @@ -284540,6 +284954,8 @@ self: { ]; description = "Testing library for Yampa"; license = lib.licenses.bsd3; + hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "yampa2048" = callPackage @@ -285511,6 +285927,29 @@ self: { license = lib.licenses.mit; }) {}; + "yesod-auth-oauth2_0_6_3_1" = callPackage + ({ mkDerivation, aeson, base, bytestring, cryptonite, errors + , hoauth2, hspec, http-client, http-conduit, http-types, memory + , microlens, mtl, safe-exceptions, text, unliftio, uri-bytestring + , yesod-auth, yesod-core + }: + mkDerivation { + pname = "yesod-auth-oauth2"; + version = "0.6.3.1"; + sha256 = "1q49a99n2h1b06zm0smqqxr9jr487b14cf8xmayvkqr0q1q5xrwa"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + 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 + ]; + testHaskellDepends = [ base hspec uri-bytestring ]; + description = "OAuth 2.0 authentication plugins"; + license = lib.licenses.mit; + hydraPlatforms = lib.platforms.none; + }) {}; + "yesod-auth-pam" = callPackage ({ mkDerivation, base, hamlet, pam, text, yesod-auth, yesod-core , yesod-form @@ -285729,6 +286168,44 @@ self: { license = lib.licenses.mit; }) {}; + "yesod-core_1_6_20" = callPackage + ({ mkDerivation, aeson, async, auto-update, base, blaze-html + , blaze-markup, bytestring, case-insensitive, cereal, clientsession + , conduit, conduit-extra, containers, cookie, deepseq, entropy + , fast-logger, gauge, hspec, hspec-expectations, http-types, HUnit + , memory, monad-logger, mtl, network, parsec, path-pieces + , primitive, random, resourcet, shakespeare, streaming-commons + , 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.20"; + sha256 = "1f3imbd22i9vl30760063p308byddwxafpl5hdric2z7vmnxayqy"; + libraryHaskellDepends = [ + aeson auto-update base blaze-html blaze-markup bytestring + case-insensitive cereal clientsession conduit conduit-extra + 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 + ]; + testHaskellDepends = [ + async base bytestring clientsession conduit conduit-extra + containers cookie hspec hspec-expectations http-types HUnit network + path-pieces random resourcet shakespeare streaming-commons + template-haskell text transformers unliftio wai wai-extra warp + ]; + benchmarkHaskellDepends = [ + base blaze-html bytestring gauge shakespeare text + ]; + description = "Creation of type-safe, RESTful web applications"; + license = lib.licenses.mit; + hydraPlatforms = lib.platforms.none; + }) {}; + "yesod-crud" = callPackage ({ mkDerivation, base, classy-prelude, containers, MissingH , monad-control, persistent, random, safe, stm, uuid, yesod-core diff --git a/pkgs/development/haskell-modules/patches/hnix-ref-tf-0.5-support.patch b/pkgs/development/haskell-modules/patches/hnix-ref-tf-0.5-support.patch deleted file mode 100644 index 5a4d0446e713..000000000000 --- a/pkgs/development/haskell-modules/patches/hnix-ref-tf-0.5-support.patch +++ /dev/null @@ -1,34 +0,0 @@ -diff '--color=auto' '--color=never' -r --unified hnix-0.12.0.1/hnix.cabal hnix-patched/hnix.cabal ---- hnix-0.12.0.1/hnix.cabal 2001-09-09 03:46:40.000000000 +0200 -+++ hnix-patched/hnix.cabal 2021-05-05 12:07:38.388267353 +0200 -@@ -430,7 +430,7 @@ - , parser-combinators >= 1.0.1 && < 1.3 - , prettyprinter >= 1.7.0 && < 1.8 - , process >= 1.6.3 && < 1.7 -- , ref-tf >= 0.4.0 && < 0.5 -+ , ref-tf >= 0.5 - , regex-tdfa >= 1.2.3 && < 1.4 - , scientific >= 0.3.6 && < 0.4 - , semialign >= 1 && < 1.2 -diff '--color=auto' '--color=never' -r --unified hnix-0.12.0.1/src/Nix/Fresh.hs hnix-patched/src/Nix/Fresh.hs ---- hnix-0.12.0.1/src/Nix/Fresh.hs 2001-09-09 03:46:40.000000000 +0200 -+++ hnix-patched/src/Nix/Fresh.hs 2021-05-05 12:07:45.841267497 +0200 -@@ -65,18 +65,3 @@ - - runFreshIdT :: Functor m => Var m i -> FreshIdT i m a -> m a - runFreshIdT i m = runReaderT (unFreshIdT m) i -- ---- Orphan instance needed by Infer.hs and Lint.hs -- ---- Since there's no forking, it's automatically atomic. --instance MonadAtomicRef (ST s) where -- atomicModifyRef r f = do -- v <- readRef r -- let (a, b) = f v -- writeRef r a -- return b -- atomicModifyRef' r f = do -- v <- readRef r -- let (a, b) = f v -- writeRef r $! a -- return b diff --git a/pkgs/development/tools/analysis/nix-linter/default.nix b/pkgs/development/tools/analysis/nix-linter/default.nix index dea2fd895f15..279a69327fa6 100644 --- a/pkgs/development/tools/analysis/nix-linter/default.nix +++ b/pkgs/development/tools/analysis/nix-linter/default.nix @@ -17,6 +17,7 @@ , containers , hnix , bytestring +, fetchpatch }: mkDerivation rec { @@ -36,10 +37,13 @@ mkDerivation rec { executableHaskellDepends = [ streamly mtl path pretty-terminal text base aeson cmdargs containers hnix bytestring path-io ]; testHaskellDepends = [ tasty tasty-hunit tasty-th ]; - # Relax upper bound on hnix https://github.com/Synthetica9/nix-linter/pull/46 - postPatch = '' - substituteInPlace nix-linter.cabal --replace "hnix >=0.8 && < 0.11" "hnix >=0.8" - ''; + patches = [ + # Fix compatibility with hnix≥0.13.0 https://github.com/Synthetica9/nix-linter/pull/51 + (fetchpatch { + url = "https://github.com/Synthetica9/nix-linter/commit/f73acacd8623dc25c9a35f8e04e4ff33cc596af8.patch"; + sha256 = "139fm21hdg3vcw8hv35kxj4awd52bjqbb76mpzx191hzi9plj8qc"; + }) + ]; description = "Linter for Nix(pkgs), based on hnix"; homepage = "https://github.com/Synthetica9/nix-linter"; diff --git a/pkgs/top-level/haskell-packages.nix b/pkgs/top-level/haskell-packages.nix index af4125d67131..8bea40efe64d 100644 --- a/pkgs/top-level/haskell-packages.nix +++ b/pkgs/top-level/haskell-packages.nix @@ -86,7 +86,7 @@ in { llvmPackages = pkgs.llvmPackages_10; }; ghcHEAD = callPackage ../development/compilers/ghc/head.nix { - bootPkgs = packages.ghc8104; # no binary yet + bootPkgs = packages.ghc901; # no binary yet inherit (buildPackages.python3Packages) sphinx; buildLlvmPackages = buildPackages.llvmPackages_10; llvmPackages = pkgs.llvmPackages_10; diff --git a/pkgs/top-level/release-haskell.nix b/pkgs/top-level/release-haskell.nix index a4ce43859ce1..38f5e2a41565 100644 --- a/pkgs/top-level/release-haskell.nix +++ b/pkgs/top-level/release-haskell.nix @@ -1,4 +1,8 @@ /* + This is the Hydra jobset for the `haskell-updates` branch in Nixpkgs. + You can see the status of this jobset at + https://hydra.nixos.org/jobset/nixpkgs/haskell-updates. + To debug this expression you can use `hydra-eval-jobs` from `pkgs.hydra-unstable` which prints the jobset description to `stdout`: @@ -144,7 +148,6 @@ let koka krank lambdabot - ldgallery madlang matterhorn mueval @@ -205,7 +208,9 @@ let cabal-install = all; Cabal_3_4_0_0 = with compilerNames; [ ghc884 ghc8104 ]; funcmp = all; - haskell-language-server = all; + # Doesn't currently work on ghc-9.0: + # https://github.com/haskell/haskell-language-server/issues/297 + haskell-language-server = with compilerNames; [ ghc884 ghc8104 ]; hoogle = all; hsdns = all; jailbreak-cabal = all; @@ -226,7 +231,10 @@ let constituents = accumulateDerivations [ # haskell specific tests jobs.tests.haskell - jobs.tests.writers # writeHaskell{,Bin} + # writeHaskell and writeHaskellBin + # TODO: writeHaskell currently fails on darwin + jobs.tests.writers.x86_64-linux + jobs.tests.writers.aarch64-linux # important top-level packages jobs.cabal-install jobs.cabal2nix