mirror of
https://github.com/ilyakooo0/nixpkgs.git
synced 2024-11-20 08:59:32 +03:00
Merge pull request #217111 from NixOS/haskell-updates
haskellPackages: update stackage and hackage
This commit is contained in:
commit
cd6d8b5973
@ -26,6 +26,7 @@ Because step 1) is quite expensive and takes roughly ~5 minutes the result is ca
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
{-# LANGUAGE ViewPatterns #-}
|
||||
{-# OPTIONS_GHC -Wall #-}
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
|
||||
import Control.Monad (forM_, (<=<))
|
||||
import Control.Monad.Trans (MonadIO (liftIO))
|
||||
@ -54,17 +55,22 @@ import Data.Time (defaultTimeLocale, formatTime, getCurrentTime)
|
||||
import Data.Time.Clock (UTCTime)
|
||||
import GHC.Generics (Generic)
|
||||
import Network.HTTP.Req (
|
||||
GET (GET),
|
||||
NoReqBody (NoReqBody),
|
||||
defaultHttpConfig,
|
||||
header,
|
||||
https,
|
||||
jsonResponse,
|
||||
req,
|
||||
responseBody,
|
||||
responseTimeout,
|
||||
runReq,
|
||||
(/:),
|
||||
GET (GET),
|
||||
HttpResponse (HttpResponseBody),
|
||||
NoReqBody (NoReqBody),
|
||||
Option,
|
||||
Req,
|
||||
Scheme (Https),
|
||||
bsResponse,
|
||||
defaultHttpConfig,
|
||||
header,
|
||||
https,
|
||||
jsonResponse,
|
||||
req,
|
||||
responseBody,
|
||||
responseTimeout,
|
||||
runReq,
|
||||
(/:),
|
||||
)
|
||||
import System.Directory (XdgDirectory (XdgCache), getXdgDirectory)
|
||||
import System.Environment (getArgs)
|
||||
@ -76,6 +82,10 @@ import Control.Exception (evaluate)
|
||||
import qualified Data.IntMap.Strict as IntMap
|
||||
import qualified Data.IntSet as IntSet
|
||||
import Data.Bifunctor (second)
|
||||
import Data.Data (Proxy)
|
||||
import Data.ByteString (ByteString)
|
||||
import qualified Data.ByteString.Char8 as ByteString
|
||||
import Distribution.Simple.Utils (safeLast, fromUTF8BS)
|
||||
|
||||
newtype JobsetEvals = JobsetEvals
|
||||
{ evals :: Seq Eval
|
||||
@ -123,17 +133,31 @@ showT = Text.pack . show
|
||||
|
||||
getBuildReports :: IO ()
|
||||
getBuildReports = runReq defaultHttpConfig do
|
||||
evalMay <- Seq.lookup 0 . evals <$> myReq (https "hydra.nixos.org" /: "jobset" /: "nixpkgs" /: "haskell-updates" /: "evals") mempty
|
||||
evalMay <- Seq.lookup 0 . evals <$> hydraJSONQuery mempty ["jobset", "nixpkgs", "haskell-updates", "evals"]
|
||||
eval@Eval{id} <- maybe (liftIO $ fail "No Evalution found") pure evalMay
|
||||
liftIO . putStrLn $ "Fetching evaluation " <> show id <> " from Hydra. This might take a few minutes..."
|
||||
buildReports :: Seq Build <- myReq (https "hydra.nixos.org" /: "eval" /: showT id /: "builds") (responseTimeout 600000000)
|
||||
buildReports :: Seq Build <- hydraJSONQuery (responseTimeout 600000000) ["eval", showT id, "builds"]
|
||||
liftIO do
|
||||
fileName <- reportFileName
|
||||
putStrLn $ "Finished fetching all builds from Hydra, saving report as " <> fileName
|
||||
now <- getCurrentTime
|
||||
encodeFile fileName (eval, now, buildReports)
|
||||
where
|
||||
myReq query option = responseBody <$> req GET query NoReqBody jsonResponse (header "User-Agent" "hydra-report.hs/v1 (nixpkgs;maintainers/scripts/haskell)" <> option)
|
||||
|
||||
hydraQuery :: HttpResponse a => Proxy a -> Option 'Https -> [Text] -> Req (HttpResponseBody a)
|
||||
hydraQuery responseType option query =
|
||||
responseBody
|
||||
<$> req
|
||||
GET
|
||||
(foldl' (/:) (https "hydra.nixos.org") query)
|
||||
NoReqBody
|
||||
responseType
|
||||
(header "User-Agent" "hydra-report.hs/v1 (nixpkgs;maintainers/scripts/haskell)" <> option)
|
||||
|
||||
hydraJSONQuery :: FromJSON a => Option 'Https -> [Text] -> Req a
|
||||
hydraJSONQuery = hydraQuery jsonResponse
|
||||
|
||||
hydraPlainQuery :: [Text] -> Req ByteString
|
||||
hydraPlainQuery = hydraQuery bsResponse mempty
|
||||
|
||||
hydraEvalCommand :: FilePath
|
||||
hydraEvalCommand = "hydra-eval-jobs"
|
||||
@ -326,23 +350,24 @@ instance Functor (Table row col) where
|
||||
instance Foldable (Table row col) where
|
||||
foldMap f (Table a) = foldMap f a
|
||||
|
||||
getBuildState :: Build -> BuildState
|
||||
getBuildState Build{finished, buildstatus} = case (finished, buildstatus) of
|
||||
(0, _) -> Unfinished
|
||||
(_, Just 0) -> Success
|
||||
(_, Just 1) -> Failed
|
||||
(_, Just 2) -> DependencyFailed
|
||||
(_, Just 3) -> HydraFailure
|
||||
(_, Just 4) -> Canceled
|
||||
(_, Just 7) -> TimedOut
|
||||
(_, Just 11) -> OutputLimitExceeded
|
||||
(_, i) -> Unknown i
|
||||
|
||||
buildSummary :: MaintainerMap -> ReverseDependencyMap -> Seq Build -> StatusSummary
|
||||
buildSummary maintainerMap reverseDependencyMap = foldl (Map.unionWith unionSummary) Map.empty . fmap toSummary
|
||||
where
|
||||
unionSummary (SummaryEntry (Table lb) lm lr lu) (SummaryEntry (Table rb) rm rr ru) = SummaryEntry (Table $ Map.union lb rb) (lm <> rm) (max lr rr) (max lu ru)
|
||||
toSummary Build{finished, buildstatus, job, id, system} = Map.singleton name (SummaryEntry (Table (Map.singleton (set, Platform system) (BuildResult state id))) maintainers reverseDeps unbrokenReverseDeps)
|
||||
toSummary build@Build{job, id, system} = Map.singleton name (SummaryEntry (Table (Map.singleton (set, Platform system) (BuildResult (getBuildState build) id))) maintainers reverseDeps unbrokenReverseDeps)
|
||||
where
|
||||
state :: BuildState
|
||||
state = case (finished, buildstatus) of
|
||||
(0, _) -> Unfinished
|
||||
(_, Just 0) -> Success
|
||||
(_, Just 1) -> Failed
|
||||
(_, Just 2) -> DependencyFailed
|
||||
(_, Just 3) -> HydraFailure
|
||||
(_, Just 4) -> Canceled
|
||||
(_, Just 7) -> TimedOut
|
||||
(_, Just 11) -> OutputLimitExceeded
|
||||
(_, i) -> Unknown i
|
||||
packageName = fromMaybe job (Text.stripSuffix ("." <> system) job)
|
||||
splitted = nonEmpty $ Text.splitOn "." packageName
|
||||
name = maybe packageName NonEmpty.last splitted
|
||||
@ -486,8 +511,23 @@ printMaintainerPing = do
|
||||
|
||||
printMarkBrokenList :: IO ()
|
||||
printMarkBrokenList = do
|
||||
(_, _, buildReport) <- readBuildReports
|
||||
forM_ buildReport \Build{buildstatus, job} ->
|
||||
case (buildstatus, Text.splitOn "." job) of
|
||||
(Just 1, ["haskellPackages", name, "x86_64-linux"]) -> putStrLn $ " - " <> Text.unpack name
|
||||
(_, fetchTime, buildReport) <- readBuildReports
|
||||
runReq defaultHttpConfig $ forM_ buildReport \build@Build{job, id} ->
|
||||
case (getBuildState build, Text.splitOn "." job) of
|
||||
(Failed, ["haskellPackages", name, "x86_64-linux"]) -> do
|
||||
-- Fetch build log from hydra to figure out the cause of the error.
|
||||
build_log <- ByteString.lines <$> hydraPlainQuery ["build", showT id, "nixlog", "1", "raw"]
|
||||
-- We use the last probable error cause found in the build log file.
|
||||
let error_message = fromMaybe " failure " $ safeLast $ mapMaybe probableErrorCause build_log
|
||||
liftIO $ putStrLn $ " - " <> Text.unpack name <> " # " <> error_message <> " in job https://hydra.nixos.org/build/" <> show id <> " at " <> formatTime defaultTimeLocale "%Y-%m-%d" fetchTime
|
||||
_ -> pure ()
|
||||
|
||||
{- | This function receives a line from a Nix Haskell builder build log and returns a possible error cause.
|
||||
| We might need to add other causes in the future if errors happen in unusual parts of the builder.
|
||||
-}
|
||||
probableErrorCause :: ByteString -> Maybe String
|
||||
probableErrorCause "Setup: Encountered missing or private dependencies:" = Just "dependency missing"
|
||||
probableErrorCause "running tests" = Just "test failure"
|
||||
probableErrorCause build_line | ByteString.isPrefixOf "Building" build_line = Just ("failure building " <> fromUTF8BS (fst $ ByteString.breakSubstring " for" $ ByteString.drop 9 build_line))
|
||||
probableErrorCause build_line | ByteString.isSuffixOf "Phase" build_line = Just ("failure in " <> fromUTF8BS build_line)
|
||||
probableErrorCause _ = Nothing
|
||||
|
@ -11,6 +11,9 @@
|
||||
# Related scripts are update-hackage.sh, for updating the snapshot of the
|
||||
# Hackage database used by hackage2nix, and update-cabal2nix-unstable.sh,
|
||||
# for updating the version of hackage2nix used to perform this task.
|
||||
#
|
||||
# Note that this script doesn't gcroot anything, so it may be broken by an
|
||||
# unfortunately timed nix-store --gc.
|
||||
|
||||
set -euo pipefail
|
||||
|
||||
@ -20,15 +23,21 @@ HACKAGE2NIX="${HACKAGE2NIX:-hackage2nix}"
|
||||
# See: https://github.com/NixOS/nixpkgs/pull/122023
|
||||
export LC_ALL=C.UTF-8
|
||||
|
||||
config_dir=pkgs/development/haskell-modules/configuration-hackage2nix
|
||||
|
||||
echo "Obtaining Hackage data"
|
||||
extraction_derivation='with import ./. {}; runCommandLocal "unpacked-cabal-hashes" { } "tar xf ${all-cabal-hashes} --strip-components=1 --one-top-level=$out"'
|
||||
unpacked_hackage="$(nix-build -E "$extraction_derivation" --no-out-link)"
|
||||
config_dir=pkgs/development/haskell-modules/configuration-hackage2nix
|
||||
|
||||
echo "Generating compiler configuration"
|
||||
compiler_config="$(nix-build -A haskellPackages.cabal2nix-unstable.compilerConfig --no-out-link)"
|
||||
|
||||
echo "Starting hackage2nix to regenerate pkgs/development/haskell-modules/hackage-packages.nix ..."
|
||||
"$HACKAGE2NIX" \
|
||||
--hackage "$unpacked_hackage" \
|
||||
--preferred-versions <(for n in "$unpacked_hackage"/*/preferred-versions; do cat "$n"; echo; done) \
|
||||
--nixpkgs "$PWD" \
|
||||
--config "$compiler_config" \
|
||||
--config "$config_dir/main.yaml" \
|
||||
--config "$config_dir/stackage.yaml" \
|
||||
--config "$config_dir/broken.yaml" \
|
||||
|
@ -1,6 +1,6 @@
|
||||
{
|
||||
"commit": "220fb2ad74640b02e543271393f21ba227bd2627",
|
||||
"url": "https://github.com/commercialhaskell/all-cabal-hashes/archive/220fb2ad74640b02e543271393f21ba227bd2627.tar.gz",
|
||||
"sha256": "1hpbqw04i8p2h5w31a7rqlmhdjpj4r4v62kdqich57hm1cj2ml7h",
|
||||
"msg": "Update from Hackage at 2023-02-13T17:53:53Z"
|
||||
"commit": "1f7cec5b787f338430007a1176f686ddbd85cbc5",
|
||||
"url": "https://github.com/commercialhaskell/all-cabal-hashes/archive/1f7cec5b787f338430007a1176f686ddbd85cbc5.tar.gz",
|
||||
"sha256": "0ddnzb8l5gbpsar1pz2dq86xa1mv4840f9ppk5viwnzgyfiqzfv8",
|
||||
"msg": "Update from Hackage at 2023-02-19T09:15:19Z"
|
||||
}
|
||||
|
383
pkgs/development/compilers/ghc/9.2.7.nix
Normal file
383
pkgs/development/compilers/ghc/9.2.7.nix
Normal file
@ -0,0 +1,383 @@
|
||||
{ lib, stdenv, pkgsBuildTarget, pkgsHostTarget, targetPackages
|
||||
|
||||
# build-tools
|
||||
, bootPkgs
|
||||
, autoconf, automake, coreutils, fetchpatch, fetchurl, perl, python3, m4, sphinx
|
||||
, xattr, autoSignDarwinBinariesHook
|
||||
, bash
|
||||
|
||||
, libiconv ? null, ncurses
|
||||
, glibcLocales ? null
|
||||
|
||||
, # GHC can be built with system libffi or a bundled one.
|
||||
libffi ? null
|
||||
|
||||
, useLLVM ? !(stdenv.targetPlatform.isx86
|
||||
|| stdenv.targetPlatform.isPower
|
||||
|| stdenv.targetPlatform.isSparc
|
||||
|| (stdenv.targetPlatform.isAarch64 && stdenv.targetPlatform.isDarwin))
|
||||
, # LLVM is conceptually a run-time-only depedendency, but for
|
||||
# non-x86, we need LLVM to bootstrap later stages, so it becomes a
|
||||
# build-time dependency too.
|
||||
buildTargetLlvmPackages, llvmPackages
|
||||
|
||||
, # If enabled, GHC will be built with the GPL-free but slightly slower native
|
||||
# bignum backend instead of the faster but GPLed gmp backend.
|
||||
enableNativeBignum ? !(lib.meta.availableOn stdenv.hostPlatform gmp
|
||||
&& lib.meta.availableOn stdenv.targetPlatform gmp)
|
||||
, gmp
|
||||
|
||||
, # If enabled, use -fPIC when compiling static libs.
|
||||
enableRelocatedStaticLibs ? stdenv.targetPlatform != stdenv.hostPlatform
|
||||
|
||||
# aarch64 outputs otherwise exceed 2GB limit
|
||||
, enableProfiledLibs ? !stdenv.targetPlatform.isAarch64
|
||||
|
||||
, # Whether to build dynamic libs for the standard library (on the target
|
||||
# platform). Static libs are always built.
|
||||
enableShared ? with stdenv.targetPlatform; !isWindows && !useiOSPrebuilt && !isStatic
|
||||
|
||||
, # Whether to build terminfo.
|
||||
enableTerminfo ? !stdenv.targetPlatform.isWindows
|
||||
|
||||
, # What flavour to build. An empty string indicates no
|
||||
# specific flavour and falls back to ghc default values.
|
||||
ghcFlavour ? lib.optionalString (stdenv.targetPlatform != stdenv.hostPlatform)
|
||||
(if useLLVM then "perf-cross" else "perf-cross-ncg")
|
||||
|
||||
, # Whether to build sphinx documentation.
|
||||
enableDocs ? (
|
||||
# Docs disabled for musl and cross because it's a large task to keep
|
||||
# all `sphinx` dependencies building in those environments.
|
||||
# `sphinx` pulls in among others:
|
||||
# Ruby, Python, Perl, Rust, OpenGL, Xorg, gtk, LLVM.
|
||||
(stdenv.targetPlatform == stdenv.hostPlatform)
|
||||
&& !stdenv.hostPlatform.isMusl
|
||||
)
|
||||
|
||||
, enableHaddockProgram ?
|
||||
# Disabled for cross; see note [HADDOCK_DOCS].
|
||||
(stdenv.targetPlatform == stdenv.hostPlatform)
|
||||
|
||||
, # Whether to disable the large address space allocator
|
||||
# necessary fix for iOS: https://www.reddit.com/r/haskell/comments/4ttdz1/building_an_osxi386_to_iosarm64_cross_compiler/d5qvd67/
|
||||
disableLargeAddressSpace ? stdenv.targetPlatform.isiOS
|
||||
}:
|
||||
|
||||
assert !enableNativeBignum -> gmp != null;
|
||||
|
||||
# Cross cannot currently build the `haddock` program for silly reasons,
|
||||
# see note [HADDOCK_DOCS].
|
||||
assert (stdenv.targetPlatform != stdenv.hostPlatform) -> !enableHaddockProgram;
|
||||
|
||||
let
|
||||
inherit (stdenv) buildPlatform hostPlatform targetPlatform;
|
||||
|
||||
inherit (bootPkgs) ghc;
|
||||
|
||||
# TODO(@Ericson2314) Make unconditional
|
||||
targetPrefix = lib.optionalString
|
||||
(targetPlatform != hostPlatform)
|
||||
"${targetPlatform.config}-";
|
||||
|
||||
buildMK = ''
|
||||
BuildFlavour = ${ghcFlavour}
|
||||
ifneq \"\$(BuildFlavour)\" \"\"
|
||||
include mk/flavours/\$(BuildFlavour).mk
|
||||
endif
|
||||
BUILD_SPHINX_HTML = ${if enableDocs then "YES" else "NO"}
|
||||
BUILD_SPHINX_PDF = NO
|
||||
'' +
|
||||
# Note [HADDOCK_DOCS]:
|
||||
# Unfortunately currently `HADDOCK_DOCS` controls both whether the `haddock`
|
||||
# program is built (which we generally always want to have a complete GHC install)
|
||||
# and whether it is run on the GHC sources to generate hyperlinked source code
|
||||
# (which is impossible for cross-compilation); see:
|
||||
# https://gitlab.haskell.org/ghc/ghc/-/issues/20077
|
||||
# This implies that currently a cross-compiled GHC will never have a `haddock`
|
||||
# program, so it can never generate haddocks for any packages.
|
||||
# If this is solved in the future, we'd like to unconditionally
|
||||
# build the haddock program (removing the `enableHaddockProgram` option).
|
||||
''
|
||||
HADDOCK_DOCS = ${if enableHaddockProgram then "YES" else "NO"}
|
||||
# Build haddocks for boot packages with hyperlinking
|
||||
EXTRA_HADDOCK_OPTS += --hyperlinked-source --quickjump
|
||||
|
||||
DYNAMIC_GHC_PROGRAMS = ${if enableShared then "YES" else "NO"}
|
||||
BIGNUM_BACKEND = ${if enableNativeBignum then "native" else "gmp"}
|
||||
'' + lib.optionalString (targetPlatform != hostPlatform) ''
|
||||
Stage1Only = ${if targetPlatform.system == hostPlatform.system then "NO" else "YES"}
|
||||
CrossCompilePrefix = ${targetPrefix}
|
||||
'' + lib.optionalString (!enableProfiledLibs) ''
|
||||
GhcLibWays = "v dyn"
|
||||
'' +
|
||||
# -fexternal-dynamic-refs apparently (because it's not clear from the documentation)
|
||||
# makes the GHC RTS able to load static libraries, which may be needed for TemplateHaskell.
|
||||
# This solution was described in https://www.tweag.io/blog/2020-09-30-bazel-static-haskell
|
||||
lib.optionalString enableRelocatedStaticLibs ''
|
||||
GhcLibHcOpts += -fPIC -fexternal-dynamic-refs
|
||||
GhcRtsHcOpts += -fPIC -fexternal-dynamic-refs
|
||||
'' + lib.optionalString targetPlatform.useAndroidPrebuilt ''
|
||||
EXTRA_CC_OPTS += -std=gnu99
|
||||
'';
|
||||
|
||||
# Splicer will pull out correct variations
|
||||
libDeps = platform: lib.optional enableTerminfo ncurses
|
||||
++ [libffi]
|
||||
++ lib.optional (!enableNativeBignum) gmp
|
||||
++ lib.optional (platform.libc != "glibc" && !targetPlatform.isWindows) libiconv;
|
||||
|
||||
# TODO(@sternenseemann): is buildTarget LLVM unnecessary?
|
||||
# GHC doesn't seem to have {LLC,OPT}_HOST
|
||||
toolsForTarget = [
|
||||
pkgsBuildTarget.targetPackages.stdenv.cc
|
||||
] ++ lib.optional useLLVM buildTargetLlvmPackages.llvm;
|
||||
|
||||
targetCC = builtins.head toolsForTarget;
|
||||
|
||||
# Sometimes we have to dispatch between the bintools wrapper and the unwrapped
|
||||
# derivation for certain tools depending on the platform.
|
||||
bintoolsFor = {
|
||||
# GHC needs install_name_tool on all darwin platforms. On aarch64-darwin it is
|
||||
# part of the bintools wrapper (due to codesigning requirements), but not on
|
||||
# x86_64-darwin.
|
||||
install_name_tool =
|
||||
if stdenv.targetPlatform.isAarch64
|
||||
then targetCC.bintools
|
||||
else targetCC.bintools.bintools;
|
||||
# Same goes for strip.
|
||||
strip =
|
||||
# TODO(@sternenseemann): also use wrapper if linker == "bfd" or "gold"
|
||||
if stdenv.targetPlatform.isAarch64 && stdenv.targetPlatform.isDarwin
|
||||
then targetCC.bintools
|
||||
else targetCC.bintools.bintools;
|
||||
};
|
||||
|
||||
# Use gold either following the default, or to avoid the BFD linker due to some bugs / perf issues.
|
||||
# But we cannot avoid BFD when using musl libc due to https://sourceware.org/bugzilla/show_bug.cgi?id=23856
|
||||
# see #84670 and #49071 for more background.
|
||||
useLdGold = targetPlatform.linker == "gold" ||
|
||||
(targetPlatform.linker == "bfd" && (targetCC.bintools.bintools.hasGold or false) && !targetPlatform.isMusl);
|
||||
|
||||
# Makes debugging easier to see which variant is at play in `nix-store -q --tree`.
|
||||
variantSuffix = lib.concatStrings [
|
||||
(lib.optionalString stdenv.hostPlatform.isMusl "-musl")
|
||||
(lib.optionalString enableNativeBignum "-native-bignum")
|
||||
];
|
||||
|
||||
in
|
||||
|
||||
# C compiler, bintools and LLVM are used at build time, but will also leak into
|
||||
# the resulting GHC's settings file and used at runtime. This means that we are
|
||||
# currently only able to build GHC if hostPlatform == buildPlatform.
|
||||
assert targetCC == pkgsHostTarget.targetPackages.stdenv.cc;
|
||||
assert buildTargetLlvmPackages.llvm == llvmPackages.llvm;
|
||||
assert stdenv.targetPlatform.isDarwin -> buildTargetLlvmPackages.clang == llvmPackages.clang;
|
||||
|
||||
stdenv.mkDerivation (rec {
|
||||
version = "9.2.7";
|
||||
pname = "${targetPrefix}ghc${variantSuffix}";
|
||||
|
||||
src = fetchurl {
|
||||
url = "https://downloads.haskell.org/ghc/${version}/ghc-${version}-src.tar.xz";
|
||||
sha256 = "a253567a17b734a4c0dd0ffa296d33c2a5b5a54a77df988806a2a1e1ca7e88b8";
|
||||
};
|
||||
|
||||
enableParallelBuilding = true;
|
||||
|
||||
outputs = [ "out" "doc" ];
|
||||
|
||||
patches = [
|
||||
# Fix docs build with sphinx >= 6.0
|
||||
# https://gitlab.haskell.org/ghc/ghc/-/issues/22766
|
||||
(fetchpatch {
|
||||
name = "ghc-docs-sphinx-6.0.patch";
|
||||
url = "https://gitlab.haskell.org/ghc/ghc/-/commit/10e94a556b4f90769b7fd718b9790d58ae566600.patch";
|
||||
sha256 = "0kmhfamr16w8gch0lgln2912r8aryjky1hfcda3jkcwa5cdzgjdv";
|
||||
})
|
||||
# fix hyperlinked haddock sources: https://github.com/haskell/haddock/pull/1482
|
||||
(fetchpatch {
|
||||
url = "https://patch-diff.githubusercontent.com/raw/haskell/haddock/pull/1482.patch";
|
||||
sha256 = "sha256-8w8QUCsODaTvknCDGgTfFNZa8ZmvIKaKS+2ZJZ9foYk=";
|
||||
extraPrefix = "utils/haddock/";
|
||||
stripLen = 1;
|
||||
})
|
||||
# Don't generate code that doesn't compile when --enable-relocatable is passed to Setup.hs
|
||||
# Can be removed if the Cabal library included with ghc backports the linked fix
|
||||
(fetchpatch {
|
||||
url = "https://github.com/haskell/cabal/commit/6c796218c92f93c95e94d5ec2d077f6956f68e98.patch";
|
||||
stripLen = 1;
|
||||
extraPrefix = "libraries/Cabal/";
|
||||
sha256 = "sha256-yRQ6YmMiwBwiYseC5BsrEtDgFbWvst+maGgDtdD0vAY=";
|
||||
})
|
||||
];
|
||||
|
||||
postPatch = "patchShebangs .";
|
||||
|
||||
# GHC needs the locale configured during the Haddock phase.
|
||||
LANG = "en_US.UTF-8";
|
||||
|
||||
# GHC is a bit confused on its cross terminology.
|
||||
# TODO(@sternenseemann): investigate coreutils dependencies and pass absolute paths
|
||||
preConfigure = ''
|
||||
for env in $(env | grep '^TARGET_' | sed -E 's|\+?=.*||'); do
|
||||
export "''${env#TARGET_}=''${!env}"
|
||||
done
|
||||
# GHC is a bit confused on its cross terminology, as these would normally be
|
||||
# the *host* tools.
|
||||
export CC="${targetCC}/bin/${targetCC.targetPrefix}cc"
|
||||
export CXX="${targetCC}/bin/${targetCC.targetPrefix}c++"
|
||||
# Use gold to work around https://sourceware.org/bugzilla/show_bug.cgi?id=16177
|
||||
export LD="${targetCC.bintools}/bin/${targetCC.bintools.targetPrefix}ld${lib.optionalString useLdGold ".gold"}"
|
||||
export AS="${targetCC.bintools.bintools}/bin/${targetCC.bintools.targetPrefix}as"
|
||||
export AR="${targetCC.bintools.bintools}/bin/${targetCC.bintools.targetPrefix}ar"
|
||||
export NM="${targetCC.bintools.bintools}/bin/${targetCC.bintools.targetPrefix}nm"
|
||||
export RANLIB="${targetCC.bintools.bintools}/bin/${targetCC.bintools.targetPrefix}ranlib"
|
||||
export READELF="${targetCC.bintools.bintools}/bin/${targetCC.bintools.targetPrefix}readelf"
|
||||
export STRIP="${bintoolsFor.strip}/bin/${bintoolsFor.strip.targetPrefix}strip"
|
||||
'' + lib.optionalString (stdenv.targetPlatform.linker == "cctools") ''
|
||||
export OTOOL="${targetCC.bintools.bintools}/bin/${targetCC.bintools.targetPrefix}otool"
|
||||
export INSTALL_NAME_TOOL="${bintoolsFor.install_name_tool}/bin/${bintoolsFor.install_name_tool.targetPrefix}install_name_tool"
|
||||
'' + lib.optionalString useLLVM ''
|
||||
export LLC="${lib.getBin buildTargetLlvmPackages.llvm}/bin/llc"
|
||||
export OPT="${lib.getBin buildTargetLlvmPackages.llvm}/bin/opt"
|
||||
'' + lib.optionalString (useLLVM && stdenv.targetPlatform.isDarwin) ''
|
||||
# LLVM backend on Darwin needs clang: https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/codegens.html#llvm-code-generator-fllvm
|
||||
export CLANG="${buildTargetLlvmPackages.clang}/bin/${buildTargetLlvmPackages.clang.targetPrefix}clang"
|
||||
'' + ''
|
||||
echo -n "${buildMK}" > mk/build.mk
|
||||
'' + lib.optionalString (stdenv.isLinux && hostPlatform.libc == "glibc") ''
|
||||
export LOCALE_ARCHIVE="${glibcLocales}/lib/locale/locale-archive"
|
||||
'' + lib.optionalString (!stdenv.isDarwin) ''
|
||||
export NIX_LDFLAGS+=" -rpath $out/lib/ghc-${version}"
|
||||
'' + lib.optionalString stdenv.isDarwin ''
|
||||
export NIX_LDFLAGS+=" -no_dtrace_dof"
|
||||
|
||||
# GHC tries the host xattr /usr/bin/xattr by default which fails since it expects python to be 2.7
|
||||
export XATTR=${lib.getBin xattr}/bin/xattr
|
||||
'' + lib.optionalString targetPlatform.useAndroidPrebuilt ''
|
||||
sed -i -e '5i ,("armv7a-unknown-linux-androideabi", ("e-m:e-p:32:32-i64:64-v128:64:128-a:0:32-n32-S64", "cortex-a8", ""))' llvm-targets
|
||||
'' + lib.optionalString targetPlatform.isMusl ''
|
||||
echo "patching llvm-targets for musl targets..."
|
||||
echo "Cloning these existing '*-linux-gnu*' targets:"
|
||||
grep linux-gnu llvm-targets | sed 's/^/ /'
|
||||
echo "(go go gadget sed)"
|
||||
sed -i 's,\(^.*linux-\)gnu\(.*\)$,\0\n\1musl\2,' llvm-targets
|
||||
echo "llvm-targets now contains these '*-linux-musl*' targets:"
|
||||
grep linux-musl llvm-targets | sed 's/^/ /'
|
||||
|
||||
echo "And now patching to preserve '-musleabi' as done with '-gnueabi'"
|
||||
# (aclocal.m4 is actual source, but patch configure as well since we don't re-gen)
|
||||
for x in configure aclocal.m4; do
|
||||
substituteInPlace $x \
|
||||
--replace '*-android*|*-gnueabi*)' \
|
||||
'*-android*|*-gnueabi*|*-musleabi*)'
|
||||
done
|
||||
'';
|
||||
|
||||
# TODO(@Ericson2314): Always pass "--target" and always prefix.
|
||||
configurePlatforms = [ "build" "host" ]
|
||||
++ lib.optional (targetPlatform != hostPlatform) "target";
|
||||
|
||||
# `--with` flags for libraries needed for RTS linker
|
||||
configureFlags = [
|
||||
"--datadir=$doc/share/doc/ghc"
|
||||
"--with-curses-includes=${ncurses.dev}/include" "--with-curses-libraries=${ncurses.out}/lib"
|
||||
] ++ lib.optionals (libffi != null) [
|
||||
"--with-system-libffi"
|
||||
"--with-ffi-includes=${targetPackages.libffi.dev}/include"
|
||||
"--with-ffi-libraries=${targetPackages.libffi.out}/lib"
|
||||
] ++ lib.optionals (targetPlatform == hostPlatform && !enableNativeBignum) [
|
||||
"--with-gmp-includes=${targetPackages.gmp.dev}/include"
|
||||
"--with-gmp-libraries=${targetPackages.gmp.out}/lib"
|
||||
] ++ lib.optionals (targetPlatform == hostPlatform && hostPlatform.libc != "glibc" && !targetPlatform.isWindows) [
|
||||
"--with-iconv-includes=${libiconv}/include"
|
||||
"--with-iconv-libraries=${libiconv}/lib"
|
||||
] ++ lib.optionals (targetPlatform != hostPlatform) [
|
||||
"--enable-bootstrap-with-devel-snapshot"
|
||||
] ++ lib.optionals useLdGold [
|
||||
"CFLAGS=-fuse-ld=gold"
|
||||
"CONF_GCC_LINKER_OPTS_STAGE1=-fuse-ld=gold"
|
||||
"CONF_GCC_LINKER_OPTS_STAGE2=-fuse-ld=gold"
|
||||
] ++ lib.optionals (disableLargeAddressSpace) [
|
||||
"--disable-large-address-space"
|
||||
];
|
||||
|
||||
# Make sure we never relax`$PATH` and hooks support for compatibility.
|
||||
strictDeps = true;
|
||||
|
||||
# Don’t add -liconv to LDFLAGS automatically so that GHC will add it itself.
|
||||
dontAddExtraLibs = true;
|
||||
|
||||
nativeBuildInputs = [
|
||||
perl autoconf automake m4 python3
|
||||
ghc bootPkgs.alex bootPkgs.happy bootPkgs.hscolour
|
||||
] ++ lib.optionals (stdenv.isDarwin && stdenv.isAarch64) [
|
||||
autoSignDarwinBinariesHook
|
||||
] ++ lib.optionals enableDocs [
|
||||
sphinx
|
||||
];
|
||||
|
||||
# For building runtime libs
|
||||
depsBuildTarget = toolsForTarget;
|
||||
|
||||
buildInputs = [ perl bash ] ++ (libDeps hostPlatform);
|
||||
|
||||
depsTargetTarget = map lib.getDev (libDeps targetPlatform);
|
||||
depsTargetTargetPropagated = map (lib.getOutput "out") (libDeps targetPlatform);
|
||||
|
||||
# required, because otherwise all symbols from HSffi.o are stripped, and
|
||||
# that in turn causes GHCi to abort
|
||||
stripDebugFlags = [ "-S" ] ++ lib.optional (!targetPlatform.isDarwin) "--keep-file-symbols";
|
||||
|
||||
checkTarget = "test";
|
||||
|
||||
hardeningDisable =
|
||||
[ "format" ]
|
||||
# In nixpkgs, musl based builds currently enable `pie` hardening by default
|
||||
# (see `defaultHardeningFlags` in `make-derivation.nix`).
|
||||
# But GHC cannot currently produce outputs that are ready for `-pie` linking.
|
||||
# Thus, disable `pie` hardening, otherwise `recompile with -fPIE` errors appear.
|
||||
# See:
|
||||
# * https://github.com/NixOS/nixpkgs/issues/129247
|
||||
# * https://gitlab.haskell.org/ghc/ghc/-/issues/19580
|
||||
++ lib.optional stdenv.targetPlatform.isMusl "pie";
|
||||
|
||||
# big-parallel allows us to build with more than 2 cores on
|
||||
# Hydra which already warrants a significant speedup
|
||||
requiredSystemFeatures = [ "big-parallel" ];
|
||||
|
||||
postInstall = ''
|
||||
# Install the bash completion file.
|
||||
install -D -m 444 utils/completion/ghc.bash $out/share/bash-completion/completions/${targetPrefix}ghc
|
||||
'';
|
||||
|
||||
passthru = {
|
||||
inherit bootPkgs targetPrefix;
|
||||
|
||||
inherit llvmPackages;
|
||||
inherit enableShared;
|
||||
|
||||
# This is used by the haskell builder to query
|
||||
# the presence of the haddock program.
|
||||
hasHaddock = enableHaddockProgram;
|
||||
|
||||
# Our Cabal compiler name
|
||||
haskellCompilerName = "ghc-${version}";
|
||||
};
|
||||
|
||||
meta = {
|
||||
homepage = "http://haskell.org/ghc";
|
||||
description = "The Glasgow Haskell Compiler";
|
||||
maintainers = with lib.maintainers; [
|
||||
guibou
|
||||
] ++ lib.teams.haskell.members;
|
||||
timeout = 24 * 3600;
|
||||
inherit (ghc.meta) license platforms;
|
||||
};
|
||||
|
||||
} // lib.optionalAttrs targetPlatform.useAndroidPrebuilt {
|
||||
dontStrip = true;
|
||||
dontPatchELF = true;
|
||||
noAuditTmpdir = true;
|
||||
})
|
@ -189,6 +189,16 @@ stdenv.mkDerivation (rec {
|
||||
|
||||
outputs = [ "out" "doc" ];
|
||||
|
||||
patches = [
|
||||
# Don't generate code that doesn't compile when --enable-relocatable is passed to Setup.hs
|
||||
# Can be removed if the Cabal library included with ghc backports the linked fix
|
||||
(fetchpatch {
|
||||
url = "https://github.com/haskell/cabal/commit/6c796218c92f93c95e94d5ec2d077f6956f68e98.patch";
|
||||
stripLen = 1;
|
||||
extraPrefix = "libraries/Cabal/";
|
||||
sha256 = "sha256-yRQ6YmMiwBwiYseC5BsrEtDgFbWvst+maGgDtdD0vAY=";
|
||||
})
|
||||
];
|
||||
|
||||
postPatch = "patchShebangs .";
|
||||
|
||||
|
@ -8,10 +8,10 @@
|
||||
}:
|
||||
mkDerivation {
|
||||
pname = "cabal2nix";
|
||||
version = "unstable-2023-02-15";
|
||||
version = "unstable-2023-02-27";
|
||||
src = fetchzip {
|
||||
url = "https://github.com/NixOS/cabal2nix/archive/5cd07f1df825084fd47cf49cf49f14569859a51c.tar.gz";
|
||||
sha256 = "1zwl5h6xqadw7fw3mkr5jljczcyrbhvi6kas19mj1wiyx6bj34yw";
|
||||
url = "https://github.com/NixOS/cabal2nix/archive/5e183d1ac819ea1beec3da6229d76d4185b026d0.tar.gz";
|
||||
sha256 = "0picq2zzr3hnwzv86p07xymrp84kdb4q5b373a07xgqqqql1wn52";
|
||||
};
|
||||
postUnpack = "sourceRoot+=/cabal2nix; echo source root reset to $sourceRoot";
|
||||
isLibrary = true;
|
||||
|
@ -31,7 +31,7 @@ self: super: {
|
||||
Cabal-syntax = cself.Cabal-syntax_3_8_1_0;
|
||||
} // lib.optionalAttrs (lib.versionOlder self.ghc.version "9.2.5") {
|
||||
# GHC 9.2.5 starts shipping 1.6.16.0
|
||||
process = cself.process_1_6_16_0;
|
||||
process = cself.process_1_6_17_0;
|
||||
} // lib.optionalAttrs (lib.versions.majorMinor self.ghc.version == "8.10") {
|
||||
# Prevent dependency on doctest which causes an inconsistent dependency
|
||||
# due to depending on ghc-8.10.7 (with bundled process) vs. process 1.6.16.0
|
||||
@ -132,7 +132,7 @@ self: super: {
|
||||
name = "git-annex-${super.git-annex.version}-src";
|
||||
url = "git://git-annex.branchable.com/";
|
||||
rev = "refs/tags/" + super.git-annex.version;
|
||||
sha256 = "0f2nnszfiqwdgfky3190prkhcndp0mva3jk7a6cl461w8kp1jspa";
|
||||
sha256 = "1g1m18l7cx2y5d43k0vy5bqn4znybq0p345399zf9nkwhwhb7s20";
|
||||
# delete android and Android directories which cause issues on
|
||||
# darwin (case insensitive directory). Since we don't need them
|
||||
# during the build process, we can delete it to prevent a hash
|
||||
@ -372,6 +372,19 @@ self: super: {
|
||||
itanium-abi = dontCheck super.itanium-abi;
|
||||
katt = dontCheck super.katt;
|
||||
language-slice = dontCheck super.language-slice;
|
||||
|
||||
# Group of libraries by same upstream maintainer for interacting with
|
||||
# Telegram messenger. Bit-rotted a bit since 2020.
|
||||
tdlib = appendPatch (fetchpatch {
|
||||
# https://github.com/poscat0x04/tdlib/pull/3
|
||||
url = "https://github.com/poscat0x04/tdlib/commit/8eb9ecbc98c65a715469fdb8b67793ab375eda31.patch";
|
||||
hash = "sha256-vEI7fTsiafNGBBl4VUXVCClW6xKLi+iK53fjcubgkpc=";
|
||||
}) (doJailbreak super.tdlib) ;
|
||||
tdlib-types = doJailbreak super.tdlib-types;
|
||||
tdlib-gen = doJailbreak super.tdlib-gen;
|
||||
# https://github.com/poscat0x04/language-tl/pull/1
|
||||
language-tl = doJailbreak super.language-tl;
|
||||
|
||||
ldap-client = dontCheck super.ldap-client;
|
||||
lensref = dontCheck super.lensref;
|
||||
lvmrun = disableHardening ["format"] (dontCheck super.lvmrun);
|
||||
@ -446,7 +459,17 @@ self: super: {
|
||||
cmdtheline = dontCheck super.cmdtheline;
|
||||
|
||||
# https://github.com/bos/snappy/issues/1
|
||||
snappy = dontCheck super.snappy;
|
||||
# https://github.com/bos/snappy/pull/10
|
||||
snappy = appendPatches [
|
||||
(pkgs.fetchpatch {
|
||||
url = "https://github.com/bos/snappy/commit/8687802c0b85ed7fbbb1b1945a75f14fb9a9c886.patch";
|
||||
sha256 = "sha256-p6rMzkjPAZVljsC1Ubj16/mNr4mq5JpxfP5xwT+Gt5M=";
|
||||
})
|
||||
(pkgs.fetchpatch {
|
||||
url = "https://github.com/bos/snappy/commit/21c3250c1f3d273cdcf597e2b7909a22aeaa710f.patch";
|
||||
sha256 = "sha256-qHEQ8FFagXGxvtblBvo7xivRARzXlaMLw8nt0068nt0=";
|
||||
})
|
||||
] (dontCheck super.snappy);
|
||||
|
||||
# https://github.com/vincenthz/hs-crypto-pubkey/issues/20
|
||||
crypto-pubkey = dontCheck super.crypto-pubkey;
|
||||
@ -1307,11 +1330,18 @@ self: super: {
|
||||
] super.svgcairo;
|
||||
|
||||
# Espial is waiting for a hackage release to be compatible with GHC 9.X.
|
||||
espial = appendPatch (fetchpatch {
|
||||
url = "https://github.com/jonschoning/espial/commit/70177f9efb9666c3616e8a474681d3eb763d0e84.patch";
|
||||
sha256 = "sha256-aJtwZGp9DUpACBV0WYRL7k32m6qWf5vq6eKBFq/G23s=";
|
||||
excludes = ["package.yaml" "stack.yaml" "stack.yaml.lock"];
|
||||
}) super.espial;
|
||||
# [This issue](https://github.com/jonschoning/espial/issues/49) can be followed
|
||||
# to track the status of the new release.
|
||||
espial =
|
||||
let ghc9-compat = fetchpatch {
|
||||
url = "https://github.com/jonschoning/espial/commit/70177f9efb9666c3616e8a474681d3eb763d0e84.patch";
|
||||
sha256 = "sha256-aJtwZGp9DUpACBV0WYRL7k32m6qWf5vq6eKBFq/G23s=";
|
||||
excludes = ["package.yaml" "stack.yaml" "stack.yaml.lock"];
|
||||
};
|
||||
in overrideCabal (drv: {
|
||||
jailbreak = assert super.espial.version == "0.0.11"; true;
|
||||
patches = [ ghc9-compat ];
|
||||
}) super.espial;
|
||||
|
||||
# Upstream PR: https://github.com/jkff/splot/pull/9
|
||||
splot = appendPatch (fetchpatch {
|
||||
@ -1440,6 +1470,13 @@ self: super: {
|
||||
haskell-language-server = (lib.pipe super.haskell-language-server [
|
||||
dontCheck
|
||||
(disableCabalFlag "stan") # Sorry stan is totally unmaintained and terrible to get to run. It only works on ghc 8.8 or 8.10 anyways …
|
||||
# Allow hls-call-hierarchy >= 1.2 which requires only a bound adjustment
|
||||
(appendPatch (fetchpatch {
|
||||
name = "hls-allow-hls-call-hierarchy-1.2.patch";
|
||||
url = "https://github.com/haskell/haskell-language-server/commit/05b248dfacc307c3397b334635cb38298aee9563.patch";
|
||||
includes = [ "haskell-language-server.cabal" ];
|
||||
sha256 = "1v0zi1lv92p6xq54yw9swzaf24dxsi9lpk10sngg3ka654ikm7j5";
|
||||
}))
|
||||
]).overrideScope (lself: lsuper: {
|
||||
# For most ghc versions, we overrideScope Cabal in the configuration-ghc-???.nix,
|
||||
# because some packages, like ormolu, need a newer Cabal version.
|
||||
@ -1802,7 +1839,38 @@ self: super: {
|
||||
database-id-class = doJailbreak super.database-id-class;
|
||||
|
||||
cabal2nix-unstable = overrideCabal {
|
||||
passthru.updateScript = ../../../maintainers/scripts/haskell/update-cabal2nix-unstable.sh;
|
||||
passthru = {
|
||||
updateScript = ../../../maintainers/scripts/haskell/update-cabal2nix-unstable.sh;
|
||||
|
||||
# This is used by regenerate-hackage-packages.nix to supply the configuration
|
||||
# values we can easily generate automatically without checking them in.
|
||||
compilerConfig =
|
||||
pkgs.runCommand
|
||||
"hackage2nix-${self.ghc.haskellCompilerName}-config.yaml"
|
||||
{
|
||||
nativeBuildInputs = [
|
||||
self.ghc
|
||||
];
|
||||
}
|
||||
''
|
||||
cat > "$out" << EOF
|
||||
# generated by haskellPackages.cabal2nix-unstable.compilerConfig
|
||||
compiler: ${self.ghc.haskellCompilerName}
|
||||
|
||||
core-packages:
|
||||
# Hack: The following package is a core package of GHCJS. If we don't declare
|
||||
# it, then hackage2nix will generate a Hackage database where all dependants
|
||||
# of this library are marked as "broken".
|
||||
- ghcjs-base-0
|
||||
|
||||
EOF
|
||||
|
||||
ghc-pkg list \
|
||||
| tail -n '+2' \
|
||||
| sed -e 's/[()]//g' -e 's/\s\+/ - /' \
|
||||
>> "$out"
|
||||
'';
|
||||
};
|
||||
} super.cabal2nix-unstable;
|
||||
|
||||
# Too strict version bounds on base
|
||||
@ -2174,6 +2242,16 @@ self: super: {
|
||||
# Too strict bounds on chell: https://github.com/fpco/haskell-filesystem/issues/24
|
||||
system-fileio = doJailbreak super.system-fileio;
|
||||
|
||||
# Temporarily upgrade haskell-gi until our hackage pin advances
|
||||
# Fixes build of gi-harfbuzz with harfbuzz >= 7.0
|
||||
# https://github.com/haskell-gi/haskell-gi/issues/396#issuecomment-1445181362
|
||||
haskell-gi =
|
||||
assert super.haskell-gi.version == "0.26.2";
|
||||
overrideCabal {
|
||||
version = "0.26.3";
|
||||
sha256 = "sha256-jsAb3JCSHCmi2dp9bpi/J3NRO/EQFB8ar4GpxAuBGOo=";
|
||||
} super.haskell-gi;
|
||||
|
||||
# Bounds too strict on base and ghc-prim: https://github.com/tibbe/ekg-core/pull/43 (merged); waiting on hackage release
|
||||
ekg-core = assert super.ekg-core.version == "0.1.1.7"; doJailbreak super.ekg-core;
|
||||
hasura-ekg-core = doJailbreak super.hasura-ekg-core;
|
||||
|
@ -318,8 +318,6 @@ self: super: ({
|
||||
# https://github.com/NixOS/nixpkgs/issues/149692
|
||||
Agda = removeConfigureFlag "-foptimise-heavily" super.Agda;
|
||||
|
||||
heystone = addBuildTool pkgs.fixDarwinDylibNames super.heystone;
|
||||
|
||||
} // lib.optionalAttrs pkgs.stdenv.isx86_64 { # x86_64-darwin
|
||||
|
||||
# tests appear to be failing to link or something:
|
||||
|
@ -195,7 +195,7 @@ in {
|
||||
};
|
||||
|
||||
# https://github.com/tweag/ormolu/issues/941
|
||||
ormolu = doDistribute self.ormolu_0_5_2_0;
|
||||
ormolu = doDistribute self.ormolu_0_5_3_0;
|
||||
fourmolu = overrideCabal (drv: {
|
||||
libraryHaskellDepends = drv.libraryHaskellDepends ++ [ self.file-embed ];
|
||||
}) (disableCabalFlag "fixity-th" super.fourmolu_0_10_1_0);
|
||||
|
@ -512,7 +512,6 @@ broken-packages:
|
||||
- byline
|
||||
- by-other-names
|
||||
- bytearray-parsing
|
||||
- bytepatch
|
||||
- bytestring-aeson-orphans
|
||||
- bytestring-arbitrary
|
||||
- bytestring-class
|
||||
@ -1386,7 +1385,6 @@ broken-packages:
|
||||
- ert
|
||||
- escape-artist
|
||||
- escoger
|
||||
- espial
|
||||
- esqueleto-pgcrypto
|
||||
- ess
|
||||
- essence-of-live-coding
|
||||
@ -1422,6 +1420,7 @@ broken-packages:
|
||||
- exinst
|
||||
- exists
|
||||
- exitcode
|
||||
- exon # dependency missing in job https://hydra.nixos.org/build/210848638 at 2023-02-28
|
||||
- exp-cache
|
||||
- exp-extended
|
||||
- explain
|
||||
@ -2423,7 +2422,6 @@ broken-packages:
|
||||
- hquantlib-time
|
||||
- hquery
|
||||
- hR
|
||||
- h-raylib
|
||||
- hreq-core
|
||||
- hRESP
|
||||
- h-reversi
|
||||
@ -2999,7 +2997,6 @@ broken-packages:
|
||||
- language-sh
|
||||
- language-sqlite
|
||||
- language-sygus
|
||||
- language-tl
|
||||
- language-typescript
|
||||
- language-webidl
|
||||
- laop
|
||||
@ -4294,6 +4291,7 @@ broken-packages:
|
||||
- quickbooks
|
||||
- quickcheck-arbitrary-template
|
||||
- quickcheck-groups
|
||||
- quickcheck-lockstep # dependency missing in job https://hydra.nixos.org/build/210845914 at 2023-02-28
|
||||
- quickcheck-monoid-subclasses
|
||||
- quickcheck-property-comb
|
||||
- quickcheck-property-monad
|
||||
@ -4917,7 +4915,8 @@ broken-packages:
|
||||
- snaplet-typed-sessions
|
||||
- snap-loader-dynamic
|
||||
- snap-predicates
|
||||
- snappy
|
||||
- snappy-conduit
|
||||
- snappy-iteratee
|
||||
- snap-routes
|
||||
- snap-stream
|
||||
- snap-testing
|
||||
@ -5256,8 +5255,6 @@ broken-packages:
|
||||
- tempus
|
||||
- ten
|
||||
- tensor
|
||||
- tensorflow
|
||||
- tensorflow-opgen
|
||||
- tensor-safe
|
||||
- termbox-bindings
|
||||
- termination-combinators
|
||||
|
@ -1,48 +1,4 @@
|
||||
# pkgs/development/haskell-modules/configuration-hackage2nix.yaml
|
||||
|
||||
compiler: ghc-9.2.4
|
||||
|
||||
core-packages:
|
||||
- Cabal-3.6.3.0
|
||||
- array-0.5.4.0
|
||||
- base-4.16.3.0
|
||||
- binary-0.8.9.0
|
||||
- bytestring-0.11.3.1
|
||||
- containers-0.6.5.1
|
||||
- deepseq-1.4.6.1
|
||||
- directory-1.3.6.2
|
||||
- exceptions-0.10.4
|
||||
- filepath-1.4.2.2
|
||||
- ghc-9.2.4
|
||||
- ghc-bignum-1.2
|
||||
- ghc-boot-9.2.4
|
||||
- ghc-boot-th-9.2.4
|
||||
- ghc-compact-0.1.0.0
|
||||
- ghc-heap-9.2.4
|
||||
- ghc-prim-0.8.0
|
||||
- ghci-9.2.4
|
||||
- haskeline-0.8.2
|
||||
- hpc-0.6.1.0
|
||||
- integer-gmp-1.1
|
||||
- libiserv-9.2.4
|
||||
- mtl-2.2.2
|
||||
- parsec-3.1.15.0
|
||||
- pretty-1.1.3.6
|
||||
- process-1.6.13.2
|
||||
- rts-1.0.2
|
||||
- stm-2.5.0.2
|
||||
- template-haskell-2.18.0.0
|
||||
- terminfo-0.4.1.5
|
||||
- text-1.2.5.0
|
||||
- time-1.11.1.1
|
||||
- transformers-0.5.6.2
|
||||
- unix-2.7.2.2
|
||||
- xhtml-3000.2.2.1
|
||||
|
||||
# Hack: The following package is a core package of GHCJS. If we don't declare
|
||||
# it, then hackage2nix will generate a Hackage database where all dependants
|
||||
# of this library are marked as "broken".
|
||||
- ghcjs-base-0
|
||||
# pkgs/development/haskell-modules/configuration-hackage2nix/main.yaml
|
||||
|
||||
# This is a list of packages with versions from the latest Stackage LTS release.
|
||||
#
|
||||
@ -191,7 +147,9 @@ package-maintainers:
|
||||
centromere:
|
||||
- nfc
|
||||
dalpd:
|
||||
- espial
|
||||
- ghc-vis
|
||||
- patat
|
||||
- svgcairo
|
||||
domenkozar:
|
||||
- cachix
|
||||
@ -619,6 +577,7 @@ supported-platforms:
|
||||
scat: [ platforms.x86 ] # uses scrypt, which requries x86
|
||||
scrypt: [ platforms.x86 ] # https://github.com/informatikr/scrypt/issues/8
|
||||
seqalign: [ platforms.x86 ] # x86 intrinsics
|
||||
swisstable: [ platforms.x86_64 ] # Needs AVX2
|
||||
tasty-papi: [ platforms.linux ] # limited by pkgs.papi
|
||||
udev: [ platforms.linux ]
|
||||
Win32-console: [ platforms.windows ]
|
||||
|
@ -865,7 +865,6 @@ dont-distribute-packages:
|
||||
- bronyradiogermany-streaming
|
||||
- btc-lsp
|
||||
- btree
|
||||
- btree-concurrent
|
||||
- buchhaltung
|
||||
- buildbox-tools
|
||||
- buildwrapper
|
||||
@ -2460,7 +2459,6 @@ dont-distribute-packages:
|
||||
- jvm
|
||||
- jvm-batching
|
||||
- jvm-streaming
|
||||
- kafka-client
|
||||
- kafka-device
|
||||
- kafka-device-glut
|
||||
- kafka-device-joystick
|
||||
@ -3228,7 +3226,6 @@ dont-distribute-packages:
|
||||
- qtah-qt5
|
||||
- quantfin
|
||||
- quantum-random
|
||||
- qudb
|
||||
- queryparser
|
||||
- queryparser-demo
|
||||
- queryparser-hive
|
||||
@ -3405,6 +3402,7 @@ dont-distribute-packages:
|
||||
- rfc-psql
|
||||
- rfc-redis
|
||||
- rfc-servant
|
||||
- rhine-bayes
|
||||
- rhine-gloss
|
||||
- rhine-terminal
|
||||
- rhythm-game-tutorial
|
||||
@ -3666,10 +3664,6 @@ dont-distribute-packages:
|
||||
- snaplet-stripe
|
||||
- snaplet-tasks
|
||||
- snaplet-wordpress
|
||||
- snappy-conduit
|
||||
- snappy-framing
|
||||
- snappy-iteratee
|
||||
- snappy-lazy
|
||||
- sndfile-enumerators
|
||||
- sneakyterm
|
||||
- sneathlane-haste
|
||||
@ -3869,20 +3863,12 @@ dont-distribute-packages:
|
||||
- tbox
|
||||
- tcache-AWS
|
||||
- tccli
|
||||
- tdlib
|
||||
- tdlib-gen
|
||||
- tdlib-types
|
||||
- techlab
|
||||
- telegram-bot
|
||||
- telegram-raw-api
|
||||
- temporal-csound
|
||||
- ten-lens
|
||||
- ten-unordered-containers
|
||||
- tensorflow-core-ops
|
||||
- tensorflow-logging
|
||||
- tensorflow-ops
|
||||
- tensorflow-records
|
||||
- tensorflow-records-conduit
|
||||
- terminal-text
|
||||
- terrahs
|
||||
- test-sandbox-compose
|
||||
|
@ -1053,12 +1053,15 @@ self: super: builtins.intersectAttrs super {
|
||||
hint = dontCheck super.hint;
|
||||
|
||||
# Make sure that Cabal 3.8.* can be built as-is
|
||||
Cabal_3_8_1_0 = doDistribute (super.Cabal_3_8_1_0.override ({
|
||||
Cabal_3_8_1_0 = doDistribute (overrideCabal (old: {
|
||||
revision = assert old.revision == "1"; "2";
|
||||
editedCabalFile = "179y365wh9zgzkcn4n6m4vfsfy6vk4apajv8jpys057z3a71s4kp";
|
||||
}) (super.Cabal_3_8_1_0.override ({
|
||||
Cabal-syntax = self.Cabal-syntax_3_8_1_0;
|
||||
} // lib.optionalAttrs (lib.versionOlder self.ghc.version "9.2.5") {
|
||||
# Use process core package when possible
|
||||
process = self.process_1_6_16_0;
|
||||
}));
|
||||
process = self.process_1_6_17_0;
|
||||
})));
|
||||
|
||||
# cabal-install switched to build type simple in 3.2.0.0
|
||||
# as a result, the cabal(1) man page is no longer installed
|
||||
|
@ -11,8 +11,8 @@ let
|
||||
tensorflow-haskell = pkgs.fetchFromGitHub {
|
||||
owner = "tensorflow";
|
||||
repo = "haskell";
|
||||
rev = "568c9b6f03e5d66a25685a776386e2ff50b61aa9";
|
||||
sha256 = "0v58zhqipa441hzdvp9pwgv6srir2fm7cp0bq2pb5jl1imwyd37h";
|
||||
rev = "555d90c43202d5a3021893013bfc8e2ffff58c97";
|
||||
sha256 = "uOuIeD4o+pcjvluTqyVU3GJUQ4e1+p3FhINJ9b6oK+k=";
|
||||
fetchSubmodules = true;
|
||||
};
|
||||
|
||||
@ -23,7 +23,9 @@ in
|
||||
{
|
||||
tensorflow-proto = doJailbreak (setTensorflowSourceRoot "tensorflow-proto" super.tensorflow-proto);
|
||||
|
||||
tensorflow = setTensorflowSourceRoot "tensorflow" super.tensorflow;
|
||||
tensorflow = overrideCabal
|
||||
(drv: { libraryHaskellDepends = drv.libraryHaskellDepends ++ [self.vector-split]; })
|
||||
(setTensorflowSourceRoot "tensorflow" super.tensorflow);
|
||||
|
||||
tensorflow-core-ops = setTensorflowSourceRoot "tensorflow-core-ops" super.tensorflow-core-ops;
|
||||
|
||||
|
808
pkgs/development/haskell-modules/hackage-packages.nix
generated
808
pkgs/development/haskell-modules/hackage-packages.nix
generated
File diff suppressed because it is too large
Load Diff
@ -19,6 +19,7 @@ let
|
||||
"ghc924"
|
||||
"ghc925"
|
||||
"ghc926"
|
||||
"ghc927"
|
||||
"ghc92"
|
||||
"ghc942"
|
||||
"ghc943"
|
||||
@ -34,6 +35,7 @@ let
|
||||
"ghc924"
|
||||
"ghc925"
|
||||
"ghc926"
|
||||
"ghc927"
|
||||
"ghc94"
|
||||
"ghc942"
|
||||
"ghc943"
|
||||
@ -206,6 +208,23 @@ in {
|
||||
buildTargetLlvmPackages = pkgsBuildTarget.llvmPackages_12;
|
||||
llvmPackages = pkgs.llvmPackages_12;
|
||||
};
|
||||
ghc927 = callPackage ../development/compilers/ghc/9.2.7.nix {
|
||||
bootPkgs =
|
||||
# aarch64 ghc8107Binary exceeds max output size on hydra
|
||||
if stdenv.hostPlatform.isAarch then
|
||||
packages.ghc8107BinaryMinimal
|
||||
else if stdenv.hostPlatform.isPower64 && stdenv.hostPlatform.isLittleEndian then
|
||||
packages.ghc810
|
||||
else
|
||||
packages.ghc8107Binary;
|
||||
inherit (buildPackages.python3Packages) sphinx;
|
||||
# Need to use apple's patched xattr until
|
||||
# https://github.com/xattr/xattr/issues/44 and
|
||||
# https://github.com/xattr/xattr/issues/55 are solved.
|
||||
inherit (buildPackages.darwin) xattr autoSignDarwinBinariesHook;
|
||||
buildTargetLlvmPackages = pkgsBuildTarget.llvmPackages_12;
|
||||
llvmPackages = pkgs.llvmPackages_12;
|
||||
};
|
||||
ghc92 = ghc926;
|
||||
ghc942 = callPackage ../development/compilers/ghc/9.4.2.nix {
|
||||
bootPkgs =
|
||||
@ -410,6 +429,11 @@ in {
|
||||
ghc = bh.compiler.ghc926;
|
||||
compilerConfig = callPackage ../development/haskell-modules/configuration-ghc-9.2.x.nix { };
|
||||
};
|
||||
ghc927 = callPackage ../development/haskell-modules {
|
||||
buildHaskellPackages = bh.packages.ghc927;
|
||||
ghc = bh.compiler.ghc927;
|
||||
compilerConfig = callPackage ../development/haskell-modules/configuration-ghc-9.2.x.nix { };
|
||||
};
|
||||
ghc92 = ghc926;
|
||||
ghc942 = callPackage ../development/haskell-modules {
|
||||
buildHaskellPackages = bh.packages.ghc942;
|
||||
|
@ -53,6 +53,7 @@ let
|
||||
ghc924
|
||||
ghc925
|
||||
ghc926
|
||||
ghc927
|
||||
ghc944
|
||||
];
|
||||
|
||||
@ -345,12 +346,23 @@ let
|
||||
};
|
||||
};
|
||||
|
||||
pkgsCross.ghcjs.haskellPackages = {
|
||||
inherit (packagePlatforms pkgs.pkgsCross.ghcjs.haskellPackages)
|
||||
ghc
|
||||
hello
|
||||
;
|
||||
};
|
||||
# TODO(@sternenseemann): when GHC 9.6 comes out we need separate jobs for
|
||||
# default GHC and ghcHEAD.
|
||||
pkgsCross.ghcjs.haskellPackages =
|
||||
removePlatforms
|
||||
[
|
||||
# Still unexplained build failure: https://github.com/NixOS/nixpkgs/issues/217127
|
||||
"x86_64-darwin"
|
||||
|
||||
# Hydra output size of 3GB is exceeded
|
||||
"aarch64-linux"
|
||||
]
|
||||
{
|
||||
inherit (packagePlatforms pkgs.pkgsCross.ghcjs.haskellPackages)
|
||||
ghc
|
||||
hello
|
||||
;
|
||||
};
|
||||
})
|
||||
(versionedCompilerJobs {
|
||||
# Packages which should be checked on more than the
|
||||
@ -392,6 +404,7 @@ let
|
||||
compilerNames.ghc924
|
||||
compilerNames.ghc925
|
||||
compilerNames.ghc926
|
||||
compilerNames.ghc927
|
||||
compilerNames.ghc944
|
||||
];
|
||||
weeder = [
|
||||
@ -400,6 +413,7 @@ let
|
||||
compilerNames.ghc924
|
||||
compilerNames.ghc925
|
||||
compilerNames.ghc926
|
||||
compilerNames.ghc927
|
||||
];
|
||||
})
|
||||
{
|
||||
@ -470,12 +484,14 @@ let
|
||||
jobs.pkgsMusl.haskell.compiler.ghc924
|
||||
jobs.pkgsMusl.haskell.compiler.ghc925
|
||||
jobs.pkgsMusl.haskell.compiler.ghc926
|
||||
jobs.pkgsMusl.haskell.compiler.ghc927
|
||||
jobs.pkgsMusl.haskell.compiler.ghcHEAD
|
||||
jobs.pkgsMusl.haskell.compiler.integer-simple.ghc8107
|
||||
jobs.pkgsMusl.haskell.compiler.native-bignum.ghc902
|
||||
jobs.pkgsMusl.haskell.compiler.native-bignum.ghc924
|
||||
jobs.pkgsMusl.haskell.compiler.native-bignum.ghc925
|
||||
jobs.pkgsMusl.haskell.compiler.native-bignum.ghc926
|
||||
jobs.pkgsMusl.haskell.compiler.native-bignum.ghc927
|
||||
jobs.pkgsMusl.haskell.compiler.native-bignum.ghcHEAD
|
||||
];
|
||||
};
|
||||
|
Loading…
Reference in New Issue
Block a user