Merge pull request #122719 from NixOS/haskell-updates

haskell: update package set
This commit is contained in:
Dennis Gosnell 2021-05-19 10:52:35 +09:00 committed by GitHub
commit b76684aff7
No known key found for this signature in database
GPG key ID: 4AEE18F83AFDEB23
15 changed files with 933 additions and 208 deletions

View file

@ -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";

View file

@ -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 <> ")"

View file

@ -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"
}

View file

@ -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);

View file

@ -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;

View file

@ -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

View file

@ -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

View file

@ -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 ]

View file

@ -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

View file

@ -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;
};
}

File diff suppressed because it is too large Load diff

View file

@ -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

View file

@ -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";

View file

@ -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;

View file

@ -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