Merge pull request #138316 from NixOS/haskell-updates
haskellPackages: update stackage and hackage
This commit is contained in:
commit
f19e1cf5d9
17 changed files with 1306 additions and 881 deletions
10
maintainers/scripts/haskell/dependencies.nix
Normal file
10
maintainers/scripts/haskell/dependencies.nix
Normal file
|
@ -0,0 +1,10 @@
|
|||
# Nix script to calculate the Haskell dependencies of every haskellPackage. Used by ./hydra-report.hs.
|
||||
let
|
||||
pkgs = import ../../.. {};
|
||||
inherit (pkgs) lib;
|
||||
getDeps = _: pkg: {
|
||||
deps = builtins.filter (x: !isNull x) (map (x: x.pname or null) (pkg.propagatedBuildInputs or []));
|
||||
broken = (pkg.meta.hydraPlatforms or [null]) == [];
|
||||
};
|
||||
in
|
||||
lib.mapAttrs getDeps pkgs.haskellPackages
|
|
@ -26,6 +26,8 @@ Because step 1) is quite expensive and takes roughly ~5 minutes the result is ca
|
|||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
{-# OPTIONS_GHC -Wall #-}
|
||||
{-# LANGUAGE ViewPatterns #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
|
||||
import Control.Monad (forM_, (<=<))
|
||||
import Control.Monad.Trans (MonadIO (liftIO))
|
||||
|
@ -41,7 +43,7 @@ import Data.List.NonEmpty (NonEmpty, nonEmpty)
|
|||
import qualified Data.List.NonEmpty as NonEmpty
|
||||
import Data.Map.Strict (Map)
|
||||
import qualified Data.Map.Strict as Map
|
||||
import Data.Maybe (fromMaybe, mapMaybe)
|
||||
import Data.Maybe (fromMaybe, mapMaybe, isNothing)
|
||||
import Data.Monoid (Sum (Sum, getSum))
|
||||
import Data.Sequence (Seq)
|
||||
import qualified Data.Sequence as Seq
|
||||
|
@ -70,6 +72,12 @@ import System.Directory (XdgDirectory (XdgCache), getXdgDirectory)
|
|||
import System.Environment (getArgs)
|
||||
import System.Process (readProcess)
|
||||
import Prelude hiding (id)
|
||||
import Data.List (sortOn)
|
||||
import Control.Concurrent.Async (concurrently)
|
||||
import Control.Exception (evaluate)
|
||||
import qualified Data.IntMap.Strict as IntMap
|
||||
import qualified Data.IntSet as IntSet
|
||||
import Data.Bifunctor (second)
|
||||
|
||||
newtype JobsetEvals = JobsetEvals
|
||||
{ evals :: Seq Eval
|
||||
|
@ -134,20 +142,17 @@ hydraEvalCommand = "hydra-eval-jobs"
|
|||
hydraEvalParams :: [String]
|
||||
hydraEvalParams = ["-I", ".", "pkgs/top-level/release-haskell.nix"]
|
||||
|
||||
handlesCommand :: FilePath
|
||||
handlesCommand = "nix-instantiate"
|
||||
nixExprCommand :: FilePath
|
||||
nixExprCommand = "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))"
|
||||
nixExprParams :: [String]
|
||||
nixExprParams = ["--eval", "--strict", "--json"]
|
||||
|
||||
-- | 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
|
||||
-- Note that there are occasionally 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)
|
||||
|
@ -195,13 +200,49 @@ type EmailToGitHubHandles = Map Text Text
|
|||
-- @@
|
||||
type MaintainerMap = Map Text (NonEmpty Text)
|
||||
|
||||
-- | Generate a mapping of Hydra job names to maintainer GitHub handles.
|
||||
-- | Information about a package which lists its dependencies and whether the
|
||||
-- package is marked broken.
|
||||
data DepInfo = DepInfo {
|
||||
deps :: Set Text,
|
||||
broken :: Bool
|
||||
}
|
||||
deriving stock (Generic, Show)
|
||||
deriving anyclass (FromJSON, ToJSON)
|
||||
|
||||
-- | Map from package names to their DepInfo. This is the data we get out of a
|
||||
-- nix call.
|
||||
type DependencyMap = Map Text DepInfo
|
||||
|
||||
-- | Map from package names to its broken state, number of reverse dependencies (fst) and
|
||||
-- unbroken reverse dependencies (snd).
|
||||
type ReverseDependencyMap = Map Text (Int, Int)
|
||||
|
||||
-- | Calculate the (unbroken) reverse dependencies of a package by transitively
|
||||
-- going through all packages if it’s a dependency of them.
|
||||
calculateReverseDependencies :: DependencyMap -> ReverseDependencyMap
|
||||
calculateReverseDependencies depMap = Map.fromDistinctAscList $ zip keys (zip (rdepMap False) (rdepMap True))
|
||||
where
|
||||
-- This code tries to efficiently invert the dependency map and calculate
|
||||
-- it’s transitive closure by internally identifying every pkg with it’s index
|
||||
-- in the package list and then using memoization.
|
||||
keys = Map.keys depMap
|
||||
pkgToIndexMap = Map.fromDistinctAscList (zip keys [0..])
|
||||
intDeps = zip [0..] $ (\DepInfo{broken,deps} -> (broken,mapMaybe (`Map.lookup` pkgToIndexMap) $ Set.toList deps)) <$> Map.elems depMap
|
||||
rdepMap onlyUnbroken = IntSet.size <$> resultList
|
||||
where
|
||||
resultList = go <$> [0..]
|
||||
oneStepMap = IntMap.fromListWith IntSet.union $ (\(key,(_,deps)) -> (,IntSet.singleton key) <$> deps) <=< filter (\(_, (broken,_)) -> not (broken && onlyUnbroken)) $ intDeps
|
||||
go pkg = IntSet.unions (oneStep:((resultList !!) <$> IntSet.toList oneStep))
|
||||
where oneStep = IntMap.findWithDefault mempty pkg oneStepMap
|
||||
|
||||
-- | Generate a mapping of Hydra job names to maintainer GitHub handles. Calls
|
||||
-- hydra-eval-jobs and the nix script ./maintainer-handles.nix.
|
||||
getMaintainerMap :: IO MaintainerMap
|
||||
getMaintainerMap = do
|
||||
hydraJobs :: HydraJobs <-
|
||||
readJSONProcess hydraEvalCommand hydraEvalParams "" "Failed to decode hydra-eval-jobs output: "
|
||||
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: "
|
||||
readJSONProcess nixExprCommand ("maintainers/scripts/haskell/maintainer-handles.nix":nixExprParams) "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
|
||||
|
@ -211,6 +252,12 @@ getMaintainerMap = do
|
|||
splitMaintainersToGitHubHandles handlesMap (Maintainers maint) =
|
||||
nonEmpty . mapMaybe (`Map.lookup` handlesMap) . Text.splitOn ", " $ fromMaybe "" maint
|
||||
|
||||
-- | Get the a map of all dependencies of every package by calling the nix
|
||||
-- script ./dependencies.nix.
|
||||
getDependencyMap :: IO DependencyMap
|
||||
getDependencyMap =
|
||||
readJSONProcess nixExprCommand ("maintainers/scripts/haskell/dependencies.nix":nixExprParams) "Failed to decode nix output for lookup of dependencies: "
|
||||
|
||||
-- | Run a process that produces JSON on stdout and and decode the JSON to a
|
||||
-- data type.
|
||||
--
|
||||
|
@ -219,11 +266,10 @@ 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
|
||||
readJSONProcess exe args err = do
|
||||
output <- readProcess exe args ""
|
||||
let eitherDecodedOutput = eitherDecodeStrict' . encodeUtf8 . Text.pack $ output
|
||||
case eitherDecodedOutput of
|
||||
Left decodeErr -> error $ err <> decodeErr <> "\nRaw: '" <> take 1000 output <> "'"
|
||||
|
@ -264,7 +310,13 @@ platformIcon (Platform x) = case x of
|
|||
data BuildResult = BuildResult {state :: BuildState, id :: Int} deriving (Show, Eq, Ord)
|
||||
newtype Platform = Platform {platform :: Text} deriving (Show, Eq, Ord)
|
||||
newtype Table row col a = Table (Map (row, col) a)
|
||||
type StatusSummary = Map Text (Table Text Platform BuildResult, Set Text)
|
||||
data SummaryEntry = SummaryEntry {
|
||||
summaryBuilds :: Table Text Platform BuildResult,
|
||||
summaryMaintainers :: Set Text,
|
||||
summaryReverseDeps :: Int,
|
||||
summaryUnbrokenReverseDeps :: Int
|
||||
}
|
||||
type StatusSummary = Map Text SummaryEntry
|
||||
|
||||
instance (Ord row, Ord col, Semigroup a) => Semigroup (Table row col a) where
|
||||
Table l <> Table r = Table (Map.unionWith (<>) l r)
|
||||
|
@ -275,11 +327,11 @@ instance Functor (Table row col) where
|
|||
instance Foldable (Table row col) where
|
||||
foldMap f (Table a) = foldMap f a
|
||||
|
||||
buildSummary :: MaintainerMap -> Seq Build -> StatusSummary
|
||||
buildSummary maintainerMap = foldl (Map.unionWith unionSummary) Map.empty . fmap toSummary
|
||||
buildSummary :: MaintainerMap -> ReverseDependencyMap -> Seq Build -> StatusSummary
|
||||
buildSummary maintainerMap reverseDependencyMap = foldl (Map.unionWith unionSummary) Map.empty . fmap toSummary
|
||||
where
|
||||
unionSummary (Table l, l') (Table r, r') = (Table $ Map.union l r, l' <> r')
|
||||
toSummary Build{finished, buildstatus, job, id, system} = Map.singleton name (Table (Map.singleton (set, Platform system) (BuildResult state id)), maintainers)
|
||||
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)
|
||||
where
|
||||
state :: BuildState
|
||||
state = case (finished, buildstatus) of
|
||||
|
@ -297,6 +349,7 @@ buildSummary maintainerMap = foldl (Map.unionWith unionSummary) Map.empty . fmap
|
|||
name = maybe packageName NonEmpty.last splitted
|
||||
set = maybe "" (Text.intercalate "." . NonEmpty.init) splitted
|
||||
maintainers = maybe mempty (Set.fromList . toList) (Map.lookup job maintainerMap)
|
||||
(reverseDeps, unbrokenReverseDeps) = Map.findWithDefault (0,0) name reverseDependencyMap
|
||||
|
||||
readBuildReports :: IO (Eval, UTCTime, Seq Build)
|
||||
readBuildReports = do
|
||||
|
@ -339,25 +392,29 @@ makeSearchLink evalId linkLabel query = "[" <> linkLabel <> "](" <> "https://hyd
|
|||
statusToNumSummary :: StatusSummary -> NumSummary
|
||||
statusToNumSummary = fmap getSum . foldMap (fmap Sum . jobTotals)
|
||||
|
||||
jobTotals :: (Table Text Platform BuildResult, a) -> Table Platform BuildState Int
|
||||
jobTotals (Table mapping, _) = getSum <$> Table (Map.foldMapWithKey (\(_, platform) (BuildResult buildstate _) -> Map.singleton (platform, buildstate) (Sum 1)) mapping)
|
||||
jobTotals :: SummaryEntry -> Table Platform BuildState Int
|
||||
jobTotals (summaryBuilds -> Table mapping) = getSum <$> Table (Map.foldMapWithKey (\(_, platform) (BuildResult buildstate _) -> Map.singleton (platform, buildstate) (Sum 1)) mapping)
|
||||
|
||||
details :: Text -> [Text] -> [Text]
|
||||
details summary content = ["<details><summary>" <> summary <> " </summary>", ""] <> content <> ["</details>", ""]
|
||||
|
||||
printBuildSummary :: Eval -> UTCTime -> StatusSummary -> Text
|
||||
printBuildSummary :: Eval -> UTCTime -> StatusSummary -> [(Text, Int)] -> Text
|
||||
printBuildSummary
|
||||
Eval{id, jobsetevalinputs = JobsetEvalInputs{nixpkgs = Nixpkgs{revision}}}
|
||||
fetchTime
|
||||
summary =
|
||||
summary
|
||||
topBrokenRdeps =
|
||||
Text.unlines $
|
||||
headline <> totals
|
||||
headline <> [""] <> tldr <> ((" * "<>) <$> (errors <> warnings)) <> [""]
|
||||
<> totals
|
||||
<> optionalList "#### Maintained packages with build failure" (maintainedList fails)
|
||||
<> optionalList "#### Maintained packages with failed dependency" (maintainedList failedDeps)
|
||||
<> optionalList "#### Maintained packages with unknown error" (maintainedList unknownErr)
|
||||
<> optionalHideableList "#### Unmaintained packages with build failure" (unmaintainedList fails)
|
||||
<> optionalHideableList "#### Unmaintained packages with failed dependency" (unmaintainedList failedDeps)
|
||||
<> optionalHideableList "#### Unmaintained packages with unknown error" (unmaintainedList unknownErr)
|
||||
<> optionalHideableList "#### Top 50 broken packages, sorted by number of reverse dependencies" (brokenLine <$> topBrokenRdeps)
|
||||
<> ["","*:arrow_heading_up:: The number of packages that depend (directly or indirectly) on this package (if any). If two numbers are shown the first (lower) number considers only packages which currently have enabled hydra jobs, i.e. are not marked broken. The second (higher) number considers all packages.*",""]
|
||||
<> footer
|
||||
where
|
||||
footer = ["*Report generated with [maintainers/scripts/haskell/hydra-report.hs](https://github.com/NixOS/nixpkgs/blob/haskell-updates/maintainers/scripts/haskell/hydra-report.sh)*"]
|
||||
|
@ -365,7 +422,7 @@ printBuildSummary
|
|||
[ "#### Build summary"
|
||||
, ""
|
||||
]
|
||||
<> printTable "Platform" (\x -> makeSearchLink id (platform x <> " " <> platformIcon x) ("." <> platform x)) (\x -> showT x <> " " <> icon x) showT (statusToNumSummary summary)
|
||||
<> printTable "Platform" (\x -> makeSearchLink id (platform x <> " " <> platformIcon x) ("." <> platform x)) (\x -> showT x <> " " <> icon x) showT numSummary
|
||||
headline =
|
||||
[ "### [haskell-updates build report from hydra](https://hydra.nixos.org/jobset/nixpkgs/haskell-updates)"
|
||||
, "*evaluation ["
|
||||
|
@ -380,24 +437,49 @@ printBuildSummary
|
|||
<> Text.pack (formatTime defaultTimeLocale "%Y-%m-%d %H:%M UTC" fetchTime)
|
||||
<> "*"
|
||||
]
|
||||
jobsByState predicate = Map.filter (predicate . foldl' min Success . fmap state . fst) summary
|
||||
brokenLine (name, rdeps) = "[" <> name <> "](https://search.nixos.org/packages?channel=unstable&show=haskellPackages." <> name <> "&query=haskellPackages." <> name <> ") :arrow_heading_up: " <> Text.pack (show rdeps)
|
||||
numSummary = statusToNumSummary summary
|
||||
jobsByState predicate = Map.filter (predicate . worstState) summary
|
||||
worstState = foldl' min Success . fmap state . summaryBuilds
|
||||
fails = jobsByState (== Failed)
|
||||
failedDeps = jobsByState (== DependencyFailed)
|
||||
unknownErr = jobsByState (\x -> x > DependencyFailed && x < TimedOut)
|
||||
withMaintainer = Map.mapMaybe (\(x, m) -> (x,) <$> nonEmpty (Set.toList m))
|
||||
withoutMaintainer = Map.mapMaybe (\(x, m) -> if Set.null m then Just x else Nothing)
|
||||
withMaintainer = Map.mapMaybe (\e -> (summaryBuilds e,) <$> nonEmpty (Set.toList (summaryMaintainers e)))
|
||||
withoutMaintainer = Map.mapMaybe (\e -> if Set.null (summaryMaintainers e) then Just e else Nothing)
|
||||
optionalList heading list = if null list then mempty else [heading] <> list
|
||||
optionalHideableList heading list = if null list then mempty else [heading] <> details (showT (length list) <> " job(s)") list
|
||||
maintainedList = showMaintainedBuild <=< Map.toList . withMaintainer
|
||||
unmaintainedList = showBuild <=< Map.toList . withoutMaintainer
|
||||
showBuild (name, table) = printJob id name (table, "")
|
||||
unmaintainedList = showBuild <=< sortOn (\(snd -> x) -> (negate (summaryUnbrokenReverseDeps x), negate (summaryReverseDeps x))) . Map.toList . withoutMaintainer
|
||||
showBuild (name, entry) = printJob id name (summaryBuilds entry, Text.pack (if summaryReverseDeps entry > 0 then " :arrow_heading_up: " <> show (summaryUnbrokenReverseDeps entry) <>" | "<> show (summaryReverseDeps entry) else ""))
|
||||
showMaintainedBuild (name, (table, maintainers)) = printJob id name (table, Text.intercalate " " (fmap ("@" <>) (toList maintainers)))
|
||||
tldr = case (errors, warnings) of
|
||||
([],[]) -> [":green_circle: **Ready to merge**"]
|
||||
([],_) -> [":yellow_circle: **Potential issues**"]
|
||||
_ -> [":red_circle: **Branch not mergeable**"]
|
||||
warnings =
|
||||
if' (Unfinished > maybe Success worstState maintainedJob) "`maintained` jobset failed." <>
|
||||
if' (Unfinished == maybe Success worstState mergeableJob) "`mergeable` jobset is not finished." <>
|
||||
if' (Unfinished == maybe Success worstState maintainedJob) "`maintained` jobset is not finished."
|
||||
errors =
|
||||
if' (isNothing mergeableJob) "No `mergeable` job found." <>
|
||||
if' (isNothing maintainedJob) "No `maintained` job found." <>
|
||||
if' (Unfinished > maybe Success worstState mergeableJob) "`mergeable` jobset failed." <>
|
||||
if' (outstandingJobs (Platform "x86_64-linux") > 100) "Too much outstanding jobs on x86_64-linux." <>
|
||||
if' (outstandingJobs (Platform "aarch64-linux") > 100) "Too much outstanding jobs on aarch64-linux."
|
||||
if' p e = if p then [e] else mempty
|
||||
outstandingJobs platform | Table m <- numSummary = Map.findWithDefault 0 (platform, Unfinished) m
|
||||
maintainedJob = Map.lookup "maintained" summary
|
||||
mergeableJob = Map.lookup "mergeable" summary
|
||||
|
||||
printMaintainerPing :: IO ()
|
||||
printMaintainerPing = do
|
||||
maintainerMap <- getMaintainerMap
|
||||
(maintainerMap, (reverseDependencyMap, topBrokenRdeps)) <- concurrently getMaintainerMap do
|
||||
depMap <- getDependencyMap
|
||||
rdepMap <- evaluate . calculateReverseDependencies $ depMap
|
||||
let tops = take 50 . sortOn (negate . snd) . fmap (second fst) . filter (\x -> maybe False broken $ Map.lookup (fst x) depMap) . Map.toList $ rdepMap
|
||||
pure (rdepMap, tops)
|
||||
(eval, fetchTime, buildReport) <- readBuildReports
|
||||
putStrLn (Text.unpack (printBuildSummary eval fetchTime (buildSummary maintainerMap buildReport)))
|
||||
putStrLn (Text.unpack (printBuildSummary eval fetchTime (buildSummary maintainerMap reverseDependencyMap buildReport) topBrokenRdeps))
|
||||
|
||||
printMarkBrokenList :: IO ()
|
||||
printMarkBrokenList = do
|
||||
|
|
7
maintainers/scripts/haskell/maintainer-handles.nix
Normal file
7
maintainers/scripts/haskell/maintainer-handles.nix
Normal file
|
@ -0,0 +1,7 @@
|
|||
# Nix script to lookup maintainer github handles from their email address. Used by ./hydra-report.hs.
|
||||
let
|
||||
pkgs = import ../../.. {};
|
||||
maintainers = import ../../maintainer-list.nix;
|
||||
inherit (pkgs) lib;
|
||||
mkMailGithubPair = _: maintainer: if maintainer ? github then { "${maintainer.email}" = maintainer.github; } else {};
|
||||
in lib.zipAttrsWith (_: builtins.head) (lib.mapAttrsToList mkMailGithubPair maintainers)
|
118
maintainers/scripts/haskell/merge-and-open-pr.sh
Executable file
118
maintainers/scripts/haskell/merge-and-open-pr.sh
Executable file
|
@ -0,0 +1,118 @@
|
|||
#! /usr/bin/env nix-shell
|
||||
#! nix-shell -i bash -p git gh -I nixpkgs=.
|
||||
#
|
||||
# Script to merge the currently open haskell-updates PR into master, bump the
|
||||
# Stackage version and Hackage versions, and open the next haskell-updates PR.
|
||||
|
||||
set -eu -o pipefail
|
||||
|
||||
# exit after printing first argument to this function
|
||||
function die {
|
||||
# echo the first argument
|
||||
echo "ERROR: $1"
|
||||
echo "Aborting!"
|
||||
|
||||
exit 1
|
||||
}
|
||||
|
||||
function help {
|
||||
echo "Usage: $0 HASKELL_UPDATES_PR_NUM"
|
||||
echo "Merge the currently open haskell-updates PR into master, and open the next one."
|
||||
echo
|
||||
echo " -h, --help print this help"
|
||||
echo " HASKELL_UPDATES_PR_NUM number of the currently open PR on NixOS/nixpkgs"
|
||||
echo " for the haskell-updates branch"
|
||||
echo
|
||||
echo "Example:"
|
||||
echo " \$ $0 137340"
|
||||
|
||||
exit 1
|
||||
}
|
||||
|
||||
# Read in the current haskell-updates PR number from the command line.
|
||||
while [[ $# -gt 0 ]]; do
|
||||
key="$1"
|
||||
|
||||
case $key in
|
||||
-h|--help)
|
||||
help
|
||||
;;
|
||||
*)
|
||||
curr_haskell_updates_pr_num="$1"
|
||||
shift
|
||||
;;
|
||||
esac
|
||||
done
|
||||
|
||||
if [[ -z "${curr_haskell_updates_pr_num-}" ]] ; then
|
||||
die "You must pass the current haskell-updates PR number as the first argument to this script."
|
||||
fi
|
||||
|
||||
# Make sure you have gh authentication setup.
|
||||
if ! gh auth status 2>/dev/null ; then
|
||||
die "You must setup the \`gh\` command. Run \`gh auth login\`."
|
||||
fi
|
||||
|
||||
# Fetch nixpkgs to get an up-to-date origin/haskell-updates branch.
|
||||
echo "Fetching origin..."
|
||||
git fetch origin >/dev/null
|
||||
|
||||
# Make sure we are currently on a local haskell-updates branch.
|
||||
curr_branch="$(git rev-parse --abbrev-ref HEAD)"
|
||||
if [[ "$curr_branch" != "haskell-updates" ]]; then
|
||||
die "Current branch is not called \"haskell-updates\"."
|
||||
fi
|
||||
|
||||
# Make sure our local haskell-updates branch is on the same commit as
|
||||
# origin/haskell-updates.
|
||||
curr_branch_commit="$(git rev-parse haskell-updates)"
|
||||
origin_haskell_updates_commit="$(git rev-parse origin/haskell-updates)"
|
||||
if [[ "$curr_branch_commit" != "$origin_haskell_updates_commit" ]]; then
|
||||
die "Current branch is not at the same commit as origin/haskell-updates"
|
||||
fi
|
||||
|
||||
# Merge the current open haskell-updates PR.
|
||||
echo "Merging https://github.com/NixOS/nixpkgs/pull/${curr_haskell_updates_pr_num}..."
|
||||
gh pr merge --repo NixOS/nixpkgs --merge "$curr_haskell_updates_pr_num"
|
||||
|
||||
# Update stackage, Hackage hashes, and regenerate Haskell package set
|
||||
echo "Updating Stackage..."
|
||||
./maintainers/scripts/haskell/update-stackage.sh --do-commit
|
||||
echo "Updating Hackage hashes..."
|
||||
./maintainers/scripts/haskell/update-hackage.sh --do-commit
|
||||
echo "Regenerating Hackage packages..."
|
||||
./maintainers/scripts/haskell/regenerate-hackage-packages.sh --do-commit
|
||||
|
||||
# Push these new commits to the haskell-updates branch
|
||||
echo "Pushing commits just created to the haskell-updates branch"
|
||||
git push
|
||||
|
||||
# Open new PR
|
||||
new_pr_body=$(cat <<EOF
|
||||
### This Merge
|
||||
|
||||
This PR is the regular merge of the \`haskell-updates\` branch into \`master\`.
|
||||
|
||||
This branch is being continually built and tested by hydra at https://hydra.nixos.org/jobset/nixpkgs/haskell-updates.
|
||||
|
||||
We roughly aim to merge these \`haskell-updates\` PRs at least once every two weeks. See the @NixOS/haskell [team calendar](https://cloud.maralorn.de/apps/calendar/p/Mw5WLnzsP7fC4Zky) for who is currently in charge of this branch.
|
||||
|
||||
### haskellPackages Workflow Summary
|
||||
|
||||
Our workflow is currently described in [\`pkgs/development/haskell-modules/HACKING.md\`](https://github.com/NixOS/nixpkgs/blob/haskell-updates/pkgs/development/haskell-modules/HACKING.md).
|
||||
|
||||
The short version is this:
|
||||
* We regularly update the Stackage and Hackage pins on \`haskell-updates\` (normally at the beginning of a merge window).
|
||||
* The community fixes builds of Haskell packages on that branch.
|
||||
* We aim at at least one merge of \`haskell-updates\` into \`master\` every two weeks.
|
||||
* We only do the merge if the [\`mergeable\`](https://hydra.nixos.org/job/nixpkgs/haskell-updates/mergeable) job is succeeding on hydra.
|
||||
* If a [\`maintained\`](https://hydra.nixos.org/job/nixpkgs/haskell-updates/maintained) package is still broken at the time of merge, we will only merge if the maintainer has been pinged 7 days in advance. (If you care about a Haskell package, become a maintainer!)
|
||||
|
||||
---
|
||||
|
||||
This is the follow-up to #${curr_haskell_updates_pr_num}. Come to [#haskell:nixos.org](https://matrix.to/#/#haskell:nixos.org) if you have any questions.
|
||||
EOF
|
||||
)
|
||||
|
||||
echo "Opening a PR for the next haskell-updates merge cycle"
|
||||
gh pr create --repo NixOS/nixpkgs --base master --head haskell-updates --title "haskellPackages: update stackage and hackage" --body "$new_pr_body"
|
|
@ -1,6 +1,6 @@
|
|||
{
|
||||
"commit": "aceceb24b5b4dc95017c3509add3f935d7289cd8",
|
||||
"url": "https://github.com/commercialhaskell/all-cabal-hashes/archive/aceceb24b5b4dc95017c3509add3f935d7289cd8.tar.gz",
|
||||
"sha256": "0bc4csxmm64qq3sxj22g4i0s2q5vpgkf2fgpby6zslhpa01pdlqq",
|
||||
"msg": "Update from Hackage at 2021-09-10T22:56:58Z"
|
||||
"commit": "6b93e40198f31ac2a9d52e4f3ce90f22f1e9e6f9",
|
||||
"url": "https://github.com/commercialhaskell/all-cabal-hashes/archive/6b93e40198f31ac2a9d52e4f3ce90f22f1e9e6f9.tar.gz",
|
||||
"sha256": "1zs9d0h55q6lj3v0d0n19yxl58lhn07lmnw2j5k2y8zbx3pcqi8l",
|
||||
"msg": "Update from Hackage at 2021-09-17T18:08:40Z"
|
||||
}
|
||||
|
|
|
@ -108,7 +108,15 @@ in stdenv.mkDerivation {
|
|||
|
||||
inherit passthru;
|
||||
|
||||
# The emscripten is broken on darwin
|
||||
meta.platforms = lib.platforms.linux;
|
||||
meta.maintainers = with lib.maintainers; [ obsidian-systems-maintenance ];
|
||||
meta = {
|
||||
# The emscripten is broken on darwin
|
||||
platforms = lib.platforms.linux;
|
||||
|
||||
# Hydra limits jobs to only outputting 1 gigabyte worth of files.
|
||||
# GHCJS outputs over 3 gigabytes.
|
||||
# https://github.com/NixOS/nixpkgs/pull/137066#issuecomment-922335563
|
||||
hydraPlatforms = lib.platforms.none;
|
||||
|
||||
maintainers = with lib.maintainers; [ obsidian-systems-maintenance ];
|
||||
};
|
||||
}
|
||||
|
|
|
@ -20,6 +20,10 @@ The workflow generally proceeds in three main steps:
|
|||
|
||||
Each of these steps is described in a separate section.
|
||||
|
||||
There is a script that automates the workflow for merging the currently open
|
||||
`haskell-updates` PR into `master` and opening the next PR. It is described
|
||||
at the end of this document.
|
||||
|
||||
## Initial `haskell-updates` PR
|
||||
|
||||
In this section we create the PR for merging `haskell-updates` into `master`.
|
||||
|
@ -46,39 +50,8 @@ In this section we create the PR for merging `haskell-updates` into `master`.
|
|||
|
||||
1. Push these commits to the `haskell-updates` branch of the NixOS/nixpkgs repository.
|
||||
|
||||
1. Open a PR on Nixpkgs merging `haskell-updates` into `master`.
|
||||
|
||||
|
||||
|
||||
Use the title `haskellPackages: update stackage and hackage` and the following message body:
|
||||
|
||||
```markdown
|
||||
### This Merge
|
||||
|
||||
This PR is the regular merge of the `haskell-updates` branch into `master`.
|
||||
|
||||
This branch is being continually built and tested by hydra at https://hydra.nixos.org/jobset/nixpkgs/haskell-updates.
|
||||
|
||||
I will aim to merge this PR **by 2021-TODO-TODO**. If I can merge it earlier, there might be successor PRs in that time window. As part of our rotation @TODO will continue these merges from 2021-TODO-TODO to 2021-TODO-TODO.
|
||||
|
||||
### haskellPackages Workflow Summary
|
||||
|
||||
Our workflow is currently described in
|
||||
[`pkgs/development/haskell-modules/HACKING.md`](https://github.com/NixOS/nixpkgs/blob/haskell-updates/pkgs/development/haskell-modules/HACKING.md).
|
||||
|
||||
The short version is this:
|
||||
* We regularly update the Stackage and Hackage pins on `haskell-updates` (normally at the beginning of a merge window).
|
||||
* The community fixes builds of Haskell packages on that branch.
|
||||
* We aim at at least one merge of `haskell-updates` into `master` every two weeks.
|
||||
* We only do the merge if the [`mergeable`](https://hydra.nixos.org/job/nixpkgs/haskell-updates/mergeable) job is succeeding on hydra.
|
||||
* If a [`maintained`](https://hydra.nixos.org/job/nixpkgs/haskell-updates/maintained) package is still broken at the time of merge, we will only merge if the maintainer has been pinged 7 days in advance. (If you care about a Haskell package, become a maintainer!)
|
||||
|
||||
---
|
||||
|
||||
This is the follow-up to #TODO. Come to [#haskell:nixos.org](https://matrix.to/#/#haskell:nixos.org) if you have any questions.
|
||||
```
|
||||
|
||||
Make sure to replace all TODO with the actual values.
|
||||
1. Open a PR on Nixpkgs for merging `haskell-updates` into `master`. The recommended
|
||||
PR title and body text are described in the `merge-and-open-pr.sh` section.
|
||||
|
||||
## Notify Maintainers and Fix Broken Packages
|
||||
|
||||
|
@ -111,7 +84,7 @@ It may help contributors to try to keep the GitHub comment updated with the
|
|||
most recent build report.
|
||||
|
||||
Maintainers should be given at least 7 days to fix up their packages when they
|
||||
break. If maintainers don't fix up their packages with 7 days, then they
|
||||
break. If maintainers don't fix up their packages within 7 days, then they
|
||||
may be marked broken before merging `haskell-updates` into `master`.
|
||||
|
||||
### Fix Broken Packages
|
||||
|
@ -180,24 +153,6 @@ following will happen:
|
|||
|
||||
- All updated files will be committed.
|
||||
|
||||
### Merge `master` into `haskell-updates`
|
||||
|
||||
You should occasionally merge the `master` branch into the `haskell-updates`
|
||||
branch.
|
||||
|
||||
In an ideal world, when we merge `haskell-updates` into `master`, it would
|
||||
cause few Hydra rebuilds on `master`. Ideally, the `nixos-unstable` channel
|
||||
would never be prevented from progressing because of needing to wait for
|
||||
rebuilding Haskell packages.
|
||||
|
||||
In order to make sure that there are a minimal number of rebuilds after merging
|
||||
`haskell-updates` into `master`, `master` should occasionally be merged into
|
||||
the `haskell-updates` branch.
|
||||
|
||||
This is especially important after `staging-next` is merged into `master`,
|
||||
since there is a high chance that this will cause all the Haskell packages to
|
||||
rebuild.
|
||||
|
||||
## Merge `haskell-updates` into `master`
|
||||
|
||||
Now it is time to merge the `haskell-updates` PR you opened above.
|
||||
|
@ -241,12 +196,60 @@ When you've double-checked these points, go ahead and merge the `haskell-updates
|
|||
After merging, **make sure not to delete the `haskell-updates` branch**, since it
|
||||
causes all currently open Haskell-related pull-requests to be automatically closed on GitHub.
|
||||
|
||||
## Script for Merging `haskell-updates` and Opening a New PR
|
||||
|
||||
There is a script that automates merging the current `haskell-updates` PR and
|
||||
opening the next one. When you want to merge the currently open
|
||||
`haskell-updates` PR, you can run the script with the following steps:
|
||||
|
||||
1. Make sure you have previously authenticated with the `gh` command. The
|
||||
script uses the `gh` command to merge the current PR and open a new one.
|
||||
You should only need to do this once.
|
||||
|
||||
```console
|
||||
$ gh auth login
|
||||
```
|
||||
|
||||
1. Make sure you have correctly marked packages broken. One of the previous
|
||||
sections explains how to do this.
|
||||
|
||||
1. Merge `master` into `haskell-updates` and make sure to push to the
|
||||
`haskell-updates` branch. (This can be skipped if `master` has recently
|
||||
been merged into `haskell-updates`.)
|
||||
|
||||
1. Go to https://hydra.nixos.org/jobset/nixpkgs/haskell-updates and force an
|
||||
evaluation of the `haskell-updates` jobset. See one of the following
|
||||
sections for how to do this. Make sure there are no evaluation errors. If
|
||||
there are remaining evaluation errors, fix them before continuing with this
|
||||
merge.
|
||||
|
||||
1. Run the script to merge `haskell-updates`:
|
||||
|
||||
```console
|
||||
$ ./maintainers/scripts/haskell/merge-and-open-pr.sh PR_NUM_OF_CURRENT_HASKELL_UPDATES_PR
|
||||
```
|
||||
|
||||
This does the following things:
|
||||
|
||||
1. Fetches `origin`, makes sure you currently have the `haskell-updates`
|
||||
branch checked out, and makes sure your currently checked-out
|
||||
`haskell-updates` branch is on the same commit as
|
||||
`origin/haskell-updates`.
|
||||
|
||||
1. Merges the currently open `haskell-updates` PR.
|
||||
|
||||
1. Updates Stackage and Hackage snapshots. Regenerates the Haskell package set.
|
||||
|
||||
1. Pushes the commits updating Stackage and Hackage and opens a new
|
||||
`haskell-updates` PR on Nixpkgs. If you'd like to do this by hand,
|
||||
look in the script for the recommended PR title and body text.
|
||||
|
||||
## Update Hackage Version Information
|
||||
|
||||
After merging into `master` you can update what hackage displays as the current
|
||||
version in NixOS for every individual package.
|
||||
To do this you run `maintainers/scripts/haskell/upload-nixos-package-list-to-hackage.sh`.
|
||||
See the script for how to provide credentials. Once you have configured that
|
||||
After merging into `master` you can update what Hackage displays as the current
|
||||
version in NixOS for every individual package. To do this you run
|
||||
`maintainers/scripts/haskell/upload-nixos-package-list-to-hackage.sh`. See the
|
||||
script for how to provide credentials. Once you have configured credentials,
|
||||
running this takes only a few seconds.
|
||||
|
||||
## Additional Info
|
||||
|
|
|
@ -91,6 +91,9 @@ self: super: {
|
|||
xml-html-qq = dontCheck super.xml-html-qq;
|
||||
yaml-combinators = dontCheck super.yaml-combinators;
|
||||
yesod-paginator = dontCheck super.yesod-paginator;
|
||||
hls-pragmas-plugin = dontCheck super.hls-pragmas-plugin;
|
||||
hls-call-hierarchy-plugin = dontCheck super.hls-call-hierarchy-plugin;
|
||||
hls-module-name-plugin = dontCheck super.hls-module-name-plugin;
|
||||
|
||||
# https://github.com/ekmett/half/issues/35
|
||||
half = dontCheck super.half;
|
||||
|
|
|
@ -1936,4 +1936,7 @@ EOT
|
|||
# 2021-09-14: Tests are flaky.
|
||||
hls-splice-plugin = dontCheck super.hls-splice-plugin;
|
||||
|
||||
# 2021-09-18: https://github.com/haskell/haskell-language-server/issues/2205
|
||||
hls-stylish-haskell-plugin = doJailbreak super.hls-stylish-haskell-plugin;
|
||||
|
||||
} // import ./configuration-tensorflow.nix {inherit pkgs haskellLib;} self super
|
||||
|
|
|
@ -104,14 +104,80 @@ self: super: {
|
|||
# https://github.com/Soostone/retry/issues/71
|
||||
retry = dontCheck super.retry;
|
||||
|
||||
# hlint 3.3 needs a ghc-lib-parser newer than the one from stackage
|
||||
hlint = super.hlint_3_3_4.overrideScope (self: super: {
|
||||
ghc-lib-parser = overrideCabal self.ghc-lib-parser_9_0_1_20210324 {
|
||||
doHaddock = false;
|
||||
};
|
||||
ghc-lib-parser-ex = self.ghc-lib-parser-ex_9_0_0_4;
|
||||
# Hlint needs >= 3.3.4 for ghc 9 support.
|
||||
hlint = super.hlint_3_3_4;
|
||||
|
||||
# 2021-09-18: ghc-api-compat and ghc-lib-* need >= 9.0.x versions for hls and hlint
|
||||
ghc-api-compat = doDistribute super.ghc-api-compat_9_0_1;
|
||||
ghc-lib-parser = self.ghc-lib-parser_9_0_1_20210324;
|
||||
ghc-lib-parser-ex = self.ghc-lib-parser-ex_9_0_0_4;
|
||||
ghc-lib = self.ghc-lib_9_0_1_20210324;
|
||||
|
||||
# 2021-09-18: Need semialign >= 1.2 for correct bounds
|
||||
semialign = super.semialign_1_2;
|
||||
|
||||
# Will probably be needed for brittany support
|
||||
# https://github.com/lspitzner/czipwith/pull/2
|
||||
#czipwith = appendPatch super.czipwith
|
||||
# (pkgs.fetchpatch {
|
||||
# url = "https://github.com/lspitzner/czipwith/commit/b6245884ae83e00dd2b5261762549b37390179f8.patch";
|
||||
# sha256 = "08rpppdldsdwzb09fmn0j55l23pwyls2dyzziw3yjc1cm0j5vic5";
|
||||
# });
|
||||
|
||||
# 2021-09-18: https://github.com/mokus0/th-extras/pull/8
|
||||
# Release is missing, but asked for in the above PR.
|
||||
th-extras = overrideCabal super.th-extras (old: {
|
||||
version = assert old.version == "0.0.0.4"; "unstable-2021-09-18";
|
||||
src = pkgs.fetchFromGitHub {
|
||||
owner = "mokus0";
|
||||
repo = "th-extras";
|
||||
rev = "0d050b24ec5ef37c825b6f28ebd46787191e2a2d";
|
||||
sha256 = "045f36yagrigrggvyb96zqmw8y42qjsllhhx2h20q25sk5h44xsd";
|
||||
};
|
||||
libraryHaskellDepends = old.libraryHaskellDepends ++ [self.th-abstraction];
|
||||
});
|
||||
|
||||
# 2021-09-18: GHC 9 compat release is missing
|
||||
# Issue: https://github.com/obsidiansystems/dependent-sum/issues/65
|
||||
dependent-sum-template = dontCheck (appendPatch super.dependent-sum-template
|
||||
(pkgs.fetchpatch {
|
||||
url = "https://github.com/obsidiansystems/dependent-sum/commit/8cf4c7fbc3bfa2be475a17bb7c94a1e1e9a830b5.patch";
|
||||
sha256 = "02wyy0ciicq2x8lw4xxz3x5i4a550mxfidhm2ihh60ni6am498ff";
|
||||
stripLen = 2;
|
||||
extraPrefix = "";
|
||||
}));
|
||||
|
||||
# 2021-09-18: cabal2nix does not detect the need for ghc-api-compat.
|
||||
hiedb = overrideCabal super.hiedb (old: {
|
||||
libraryHaskellDepends = old.libraryHaskellDepends ++ [self.ghc-api-compat];
|
||||
});
|
||||
|
||||
# pick right version for compiler
|
||||
ghc-api-compat = doDistribute super.ghc-api-compat_9_0_1;
|
||||
# 2021-09-18: Need path >= 0.9.0 for ghc 9 compat
|
||||
path = self.path_0_9_0;
|
||||
# 2021-09-18: Need ormolu >= 0.3.0.0 for ghc 9 compat
|
||||
ormolu = self.ormolu_0_3_0_0;
|
||||
# 2021-09-18: https://github.com/haskell/haskell-language-server/issues/2206
|
||||
# Restrictive upper bound on ormolu
|
||||
hls-ormolu-plugin = doJailbreak super.hls-ormolu-plugin;
|
||||
|
||||
# 2021-09-18: The following plugins don‘t work yet on ghc9.
|
||||
haskell-language-server = appendConfigureFlags (super.haskell-language-server.override {
|
||||
hls-tactics-plugin = null; # No upstream support, generic-lens-core fail
|
||||
hls-splice-plugin = null; # No upstream support in hls 1.4.0, should be fixed in 1.5
|
||||
hls-refine-imports-plugin = null; # same issue es splice-plugin
|
||||
hls-class-plugin = null; # No upstream support
|
||||
|
||||
hls-fourmolu-plugin = null; # No upstream support, needs new fourmolu release
|
||||
hls-stylish-haskell-plugin = null; # No upstream support
|
||||
hls-brittany-plugin = null; # No upstream support, needs new brittany release
|
||||
}) [
|
||||
"-f-tactic"
|
||||
"-f-splice"
|
||||
"-f-refineimports"
|
||||
"-f-class"
|
||||
|
||||
"-f-fourmolu"
|
||||
"-f-brittany"
|
||||
"-f-stylishhaskell"
|
||||
];
|
||||
}
|
||||
|
|
|
@ -288,6 +288,7 @@ broken-packages:
|
|||
- barrie
|
||||
- barrier
|
||||
- barrier-monad
|
||||
- base62
|
||||
- base64-conduit
|
||||
- base-compat-migrate
|
||||
- base-encoding
|
||||
|
@ -556,6 +557,7 @@ broken-packages:
|
|||
- capri
|
||||
- caramia
|
||||
- carbonara
|
||||
- cardano-coin-selection
|
||||
- carettah
|
||||
- CarneadesDSL
|
||||
- carte
|
||||
|
@ -1102,6 +1104,7 @@ broken-packages:
|
|||
- doctest-prop
|
||||
- docusign-example
|
||||
- docvim
|
||||
- doi
|
||||
- dominion
|
||||
- domplate
|
||||
- dormouse-uri
|
||||
|
@ -5227,6 +5230,7 @@ broken-packages:
|
|||
- why3
|
||||
- WikimediaParser
|
||||
- windns
|
||||
- windowslive
|
||||
- winerror
|
||||
- Wired
|
||||
- wires
|
||||
|
|
|
@ -1,4 +1,4 @@
|
|||
# Stackage LTS 18.9
|
||||
# Stackage LTS 18.10
|
||||
# This file is auto-generated by
|
||||
# maintainers/scripts/haskell/update-stackage.sh
|
||||
default-package-overrides:
|
||||
|
@ -159,7 +159,7 @@ default-package-overrides:
|
|||
- approximate-equality ==1.1.0.2
|
||||
- app-settings ==0.2.0.12
|
||||
- arbor-lru-cache ==0.1.1.1
|
||||
- arithmoi ==0.12.0.0
|
||||
- arithmoi ==0.12.0.1
|
||||
- array-memoize ==0.6.0
|
||||
- arrow-extras ==0.1.0.1
|
||||
- arrows ==0.4.4.2
|
||||
|
@ -573,7 +573,7 @@ default-package-overrides:
|
|||
- dbus ==1.2.17
|
||||
- dbus-hslogger ==0.1.0.1
|
||||
- debian ==4.0.2
|
||||
- debian-build ==0.10.2.0
|
||||
- debian-build ==0.10.2.1
|
||||
- debug-trace-var ==0.2.0
|
||||
- dec ==0.0.4
|
||||
- Decimal ==0.5.2
|
||||
|
@ -587,7 +587,7 @@ default-package-overrides:
|
|||
- dependent-sum ==0.7.1.0
|
||||
- dependent-sum-template ==0.1.0.3
|
||||
- depq ==0.4.2
|
||||
- deque ==0.4.3
|
||||
- deque ==0.4.4
|
||||
- deriveJsonNoPrefix ==0.1.0.1
|
||||
- derive-topdown ==0.0.2.2
|
||||
- deriving-aeson ==0.2.7
|
||||
|
@ -777,7 +777,7 @@ default-package-overrides:
|
|||
- fixed-length ==0.2.3
|
||||
- fixed-vector ==1.2.0.0
|
||||
- fixed-vector-hetero ==0.6.1.0
|
||||
- fix-whitespace ==0.0.6
|
||||
- fix-whitespace ==0.0.7
|
||||
- flac ==0.2.0
|
||||
- flac-picture ==0.1.2
|
||||
- flags-applicative ==0.1.0.3
|
||||
|
@ -789,7 +789,7 @@ default-package-overrides:
|
|||
- flow ==1.0.22
|
||||
- flush-queue ==1.0.0
|
||||
- fmlist ==0.9.4
|
||||
- fmt ==0.6.2.0
|
||||
- fmt ==0.6.3.0
|
||||
- fn ==0.3.0.2
|
||||
- focus ==1.0.2
|
||||
- focuslist ==0.1.0.2
|
||||
|
@ -1003,6 +1003,7 @@ default-package-overrides:
|
|||
- haskell-src-exts-util ==0.2.5
|
||||
- haskell-src-meta ==0.8.7
|
||||
- haskey-btree ==0.3.0.1
|
||||
- hasktags ==0.72.0
|
||||
- hasql ==1.4.5.1
|
||||
- hasql-notifications ==0.2.0.0
|
||||
- hasql-optparse-applicative ==0.3.0.6
|
||||
|
@ -1135,7 +1136,7 @@ default-package-overrides:
|
|||
- hspec-wai-json ==0.11.0
|
||||
- hs-php-session ==0.0.9.3
|
||||
- hsshellscript ==3.5.0
|
||||
- hs-tags ==0.1.5.1
|
||||
- hs-tags ==0.1.5.2
|
||||
- HStringTemplate ==0.8.8
|
||||
- HSvm ==0.1.1.3.22
|
||||
- HsYAML ==0.2.1.0
|
||||
|
@ -1239,7 +1240,7 @@ default-package-overrides:
|
|||
- indexed-traversable-instances ==0.1
|
||||
- infer-license ==0.2.0
|
||||
- inflections ==0.4.0.6
|
||||
- influxdb ==1.9.1.2
|
||||
- influxdb ==1.9.2
|
||||
- ini ==0.4.1
|
||||
- inj ==1.0
|
||||
- inline-c ==0.9.1.5
|
||||
|
@ -1304,11 +1305,12 @@ default-package-overrides:
|
|||
- js-dgtable ==0.5.2
|
||||
- js-flot ==0.8.3
|
||||
- js-jquery ==3.3.1
|
||||
- json ==0.10
|
||||
- json-feed ==1.0.13
|
||||
- jsonifier ==0.1.1
|
||||
- jsonpath ==0.2.0.0
|
||||
- json-rpc ==1.0.3
|
||||
- json-rpc-generic ==0.2.1.5
|
||||
- json-rpc-generic ==0.2.1.6
|
||||
- JuicyPixels ==3.3.5
|
||||
- JuicyPixels-blurhash ==0.1.0.3
|
||||
- JuicyPixels-extra ==0.5.2
|
||||
|
@ -1766,7 +1768,7 @@ default-package-overrides:
|
|||
- persistent-mtl ==0.2.2.0
|
||||
- persistent-mysql ==2.13.0.2
|
||||
- persistent-pagination ==0.1.1.2
|
||||
- persistent-postgresql ==2.13.0.3
|
||||
- persistent-postgresql ==2.13.1.0
|
||||
- persistent-qq ==2.12.0.1
|
||||
- persistent-sqlite ==2.13.0.3
|
||||
- persistent-template ==2.12.0.0
|
||||
|
@ -2005,7 +2007,7 @@ default-package-overrides:
|
|||
- rev-state ==0.1.2
|
||||
- rfc1751 ==0.1.3
|
||||
- rfc5051 ==0.2
|
||||
- rhbzquery ==0.4.3
|
||||
- rhbzquery ==0.4.4
|
||||
- rhine ==0.7.0
|
||||
- rhine-gloss ==0.7.0
|
||||
- rigel-viz ==0.2.0.0
|
||||
|
@ -2043,9 +2045,9 @@ default-package-overrides:
|
|||
- sample-frame ==0.0.3
|
||||
- sample-frame-np ==0.0.4.1
|
||||
- sampling ==0.3.5
|
||||
- sandwich ==0.1.0.8
|
||||
- sandwich-quickcheck ==0.1.0.5
|
||||
- sandwich-slack ==0.1.0.4
|
||||
- sandwich ==0.1.0.9
|
||||
- sandwich-quickcheck ==0.1.0.6
|
||||
- sandwich-slack ==0.1.0.6
|
||||
- sandwich-webdriver ==0.1.0.6
|
||||
- say ==0.1.0.1
|
||||
- sbp ==2.6.3
|
||||
|
@ -2127,7 +2129,7 @@ default-package-overrides:
|
|||
- setlocale ==1.0.0.10
|
||||
- sexp-grammar ==2.3.1
|
||||
- SHA ==1.6.4.4
|
||||
- shake ==0.19.5
|
||||
- shake ==0.19.6
|
||||
- shake-language-c ==0.12.0
|
||||
- shake-plus ==0.3.4.0
|
||||
- shake-plus-extended ==0.4.1.0
|
||||
|
@ -2259,7 +2261,7 @@ default-package-overrides:
|
|||
- streamt ==0.5.0.0
|
||||
- strict ==0.4.0.1
|
||||
- strict-concurrency ==0.2.4.3
|
||||
- strict-list ==0.1.5
|
||||
- strict-list ==0.1.6
|
||||
- strict-tuple ==0.1.4
|
||||
- strict-tuple-lens ==0.1.0.1
|
||||
- stringbuilder ==0.5.1
|
||||
|
@ -2370,7 +2372,7 @@ default-package-overrides:
|
|||
- text-format ==0.3.2
|
||||
- text-icu ==0.7.1.0
|
||||
- text-latin1 ==0.3.1
|
||||
- text-ldap ==0.1.1.13
|
||||
- text-ldap ==0.1.1.14
|
||||
- textlocal ==0.1.0.5
|
||||
- text-manipulate ==0.3.0.0
|
||||
- text-metrics ==0.3.1
|
||||
|
@ -2408,7 +2410,7 @@ default-package-overrides:
|
|||
- thread-supervisor ==0.2.0.0
|
||||
- threepenny-gui ==0.9.1.0
|
||||
- th-reify-compat ==0.0.1.5
|
||||
- th-reify-many ==0.1.9
|
||||
- th-reify-many ==0.1.10
|
||||
- throttle-io-stream ==0.2.0.1
|
||||
- through-text ==0.1.0.0
|
||||
- throwable-exceptions ==0.1.0.9
|
||||
|
@ -2575,7 +2577,7 @@ default-package-overrides:
|
|||
- vector-circular ==0.1.3
|
||||
- vector-instances ==3.4
|
||||
- vector-mmap ==0.0.3
|
||||
- vector-rotcev ==0.1.0.0
|
||||
- vector-rotcev ==0.1.0.1
|
||||
- vector-sized ==1.4.4
|
||||
- vector-space ==0.16
|
||||
- vector-split ==1.0.0.2
|
||||
|
@ -2608,7 +2610,7 @@ default-package-overrides:
|
|||
- wai-rate-limit-redis ==0.1.0.0
|
||||
- wai-saml2 ==0.2.1.2
|
||||
- wai-session ==0.3.3
|
||||
- wai-session-redis ==0.1.0.2
|
||||
- wai-session-redis ==0.1.0.3
|
||||
- wai-slack-middleware ==0.2.0
|
||||
- wai-websockets ==3.0.1.2
|
||||
- wakame ==0.1.0.0
|
||||
|
@ -2630,6 +2632,7 @@ default-package-overrides:
|
|||
- wikicfp-scraper ==0.1.0.12
|
||||
- wild-bind ==0.1.2.7
|
||||
- wild-bind-x11 ==0.2.0.13
|
||||
- Win32 ==2.6.2.1
|
||||
- Win32-notify ==0.3.0.3
|
||||
- windns ==0.1.0.1
|
||||
- witch ==0.3.4.0
|
||||
|
@ -2689,7 +2692,7 @@ default-package-overrides:
|
|||
- yaml ==0.11.5.0
|
||||
- yamlparse-applicative ==0.2.0.0
|
||||
- yesod ==1.6.1.2
|
||||
- yesod-auth ==1.6.10.3
|
||||
- yesod-auth ==1.6.10.4
|
||||
- yesod-auth-hashdb ==1.7.1.7
|
||||
- yesod-auth-oauth2 ==0.6.3.4
|
||||
- yesod-bin ==1.6.1
|
||||
|
|
|
@ -602,9 +602,6 @@ dont-distribute-packages:
|
|||
- boots-web
|
||||
- borel
|
||||
- bowntz
|
||||
- box
|
||||
- box-csv
|
||||
- box-socket
|
||||
- breakout
|
||||
- bricks
|
||||
- bricks-internal-test
|
||||
|
@ -650,7 +647,6 @@ dont-distribute-packages:
|
|||
- call
|
||||
- camfort
|
||||
- campfire
|
||||
- candid
|
||||
- canteven-http
|
||||
- cao
|
||||
- cap
|
||||
|
@ -700,6 +696,7 @@ dont-distribute-packages:
|
|||
- chr-core
|
||||
- chr-lang
|
||||
- chromatin
|
||||
- chronos_1_1_3
|
||||
- chu2
|
||||
- chunks
|
||||
- ciphersaber2
|
||||
|
@ -3181,7 +3178,6 @@ dont-distribute-packages:
|
|||
- wavy
|
||||
- web-mongrel2
|
||||
- web-page
|
||||
- web-rep
|
||||
- web-routes-regular
|
||||
- web-routing
|
||||
- web3
|
||||
|
|
|
@ -699,7 +699,7 @@ self: super: builtins.intersectAttrs super {
|
|||
testTarget = "unit-tests";
|
||||
};
|
||||
|
||||
haskell-language-server = enableCabalFlag (enableCabalFlag (overrideCabal super.haskell-language-server (drv: {
|
||||
haskell-language-server = overrideCabal super.haskell-language-server (drv: {
|
||||
postInstall = let
|
||||
inherit (pkgs.lib) concatStringsSep take splitString;
|
||||
ghc_version = self.ghc.version;
|
||||
|
@ -714,7 +714,7 @@ self: super: builtins.intersectAttrs super {
|
|||
export PATH=$PATH:$PWD/dist/build/haskell-language-server:$PWD/dist/build/haskell-language-server-wrapper
|
||||
export HOME=$TMPDIR
|
||||
'';
|
||||
})) "all-plugins") "all-formatters";
|
||||
});
|
||||
|
||||
# tests depend on a specific version of solc
|
||||
hevm = dontCheck (doJailbreak super.hevm);
|
||||
|
|
1614
pkgs/development/haskell-modules/hackage-packages.nix
generated
1614
pkgs/development/haskell-modules/hackage-packages.nix
generated
File diff suppressed because it is too large
Load diff
|
@ -1,4 +1,4 @@
|
|||
{ lib, supportedGhcVersions ? [ "884" "8107" ], stdenv, haskellPackages
|
||||
{ lib, supportedGhcVersions ? [ "884" "8107" "901" ], stdenv, haskellPackages
|
||||
, haskell }:
|
||||
#
|
||||
# The recommended way to override this package is
|
||||
|
|
|
@ -306,9 +306,7 @@ let
|
|||
Cabal_3_6_1_0 = with compilerNames; [ ghc884 ghc8107 ghc901 ghc921 ];
|
||||
cabal2nix-unstable = all;
|
||||
funcmp = all;
|
||||
# Doesn't currently work on ghc-9.0:
|
||||
# https://github.com/haskell/haskell-language-server/issues/297
|
||||
haskell-language-server = with compilerNames; [ ghc884 ghc8107 ];
|
||||
haskell-language-server = all;
|
||||
hoogle = all;
|
||||
hsdns = all;
|
||||
jailbreak-cabal = all;
|
||||
|
|
Loading…
Reference in a new issue