Skip to content

Commit

Permalink
Merge pull request #122719 from NixOS/haskell-updates
Browse files Browse the repository at this point in the history
haskell: update package set
  • Loading branch information
cdepillabout authored May 19, 2021
2 parents 667950d + 3522051 commit b76684a
Show file tree
Hide file tree
Showing 15 changed files with 934 additions and 209 deletions.
6 changes: 6 additions & 0 deletions maintainers/maintainer-list.nix
Original file line number Diff line number Diff line change
Expand Up @@ -3591,6 +3591,12 @@
githubId = 606000;
name = "Gabriel Adomnicai";
};
Gabriel439 = {
email = "[email protected]";
github = "Gabriel439";
githubId = 1313787;
name = "Gabriel Gonzalez";
};
gal_bolle = {
email = "[email protected]";
github = "FlorentBecker";
Expand Down
109 changes: 97 additions & 12 deletions maintainers/scripts/haskell/hydra-report.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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 #-}
Expand All @@ -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)
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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 "[email protected]"))
-- , ("bench.x86_64-linux", Maintainers (Just ""))
-- , ("conduit.x86_64-linux", Maintainers (Just "[email protected], [email protected]"))
-- , ("lens.x86_64-darwin", Maintainers (Just "[email protected]"))
-- ]
-- @@
--
-- 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
-- [ ("[email protected]", "rob22")
-- , ("[email protected]", "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
Expand Down Expand Up @@ -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 <> ")"
Expand Down
8 changes: 4 additions & 4 deletions pkgs/data/misc/hackage/pin.json
Original file line number Diff line number Diff line change
@@ -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"
}
6 changes: 5 additions & 1 deletion pkgs/development/compilers/ghc/head.nix
Original file line number Diff line number Diff line change
Expand Up @@ -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

Expand Down Expand Up @@ -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);
Expand Down
24 changes: 24 additions & 0 deletions pkgs/development/haskell-modules/configuration-arm.nix
Original file line number Diff line number Diff line change
Expand Up @@ -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;
Expand Down
61 changes: 52 additions & 9 deletions pkgs/development/haskell-modules/configuration-common.nix
Original file line number Diff line number Diff line change
Expand Up @@ -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 []);
}));

Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
Original file line number Diff line number Diff line change
Expand Up @@ -1510,7 +1510,6 @@ broken-packages:
- generic-lens-labels
- generic-lucid-scaffold
- generic-maybe
- generic-optics
- generic-override-aeson
- generic-pretty
- genericserialize
Expand Down Expand Up @@ -1676,6 +1675,7 @@ broken-packages:
- grasp
- gray-code
- greencard
- greenclip
- greg-client
- gremlin-haskell
- Grempa
Expand Down Expand Up @@ -3037,6 +3037,7 @@ broken-packages:
- multext-east-msd
- multiaddr
- multiarg
- multi-except
- multihash
- multi-instance
- multilinear
Expand Down Expand Up @@ -5155,6 +5156,7 @@ broken-packages:
- yampa-glut
- yampa-sdl2
- YampaSynth
- yampa-test
- yam-servant
- yandex-translate
- yaop
Expand Down
Loading

0 comments on commit b76684a

Please sign in to comment.