Merge pull request #122286 from NixOS/haskell-updates
This commit is contained in:
commit
881d2af5ee
321
maintainers/scripts/haskell/hydra-report.hs
Executable file
321
maintainers/scripts/haskell/hydra-report.hs
Executable file
@ -0,0 +1,321 @@
|
|||||||
|
#! /usr/bin/env nix-shell
|
||||||
|
#! nix-shell -p "haskellPackages.ghcWithPackages (p: [p.aeson p.req])"
|
||||||
|
#! nix-shell -p hydra-unstable
|
||||||
|
#! nix-shell -i runhaskell
|
||||||
|
|
||||||
|
{-
|
||||||
|
|
||||||
|
The purpose of this script is
|
||||||
|
|
||||||
|
1) download the state of the nixpkgs/haskell-updates job from hydra (with get-report)
|
||||||
|
2) print a summary of the state suitable for pasting into a github comment (with ping-maintainers)
|
||||||
|
3) print a list of broken packages suitable for pasting into configuration-hackage2nix.yaml
|
||||||
|
|
||||||
|
Because step 1) is quite expensive and takes roughly ~5 minutes the result is cached in a json file in XDG_CACHE.
|
||||||
|
|
||||||
|
-}
|
||||||
|
{-# LANGUAGE BlockArguments #-}
|
||||||
|
{-# LANGUAGE DeriveAnyClass #-}
|
||||||
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
|
{-# LANGUAGE DuplicateRecordFields #-}
|
||||||
|
{-# LANGUAGE LambdaCase #-}
|
||||||
|
{-# LANGUAGE MultiWayIf #-}
|
||||||
|
{-# LANGUAGE NamedFieldPuns #-}
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
|
{-# LANGUAGE TupleSections #-}
|
||||||
|
{-# OPTIONS_GHC -Wall #-}
|
||||||
|
|
||||||
|
import Control.Monad (forM_, (<=<))
|
||||||
|
import Control.Monad.Trans (MonadIO (liftIO))
|
||||||
|
import Data.Aeson (
|
||||||
|
FromJSON,
|
||||||
|
ToJSON,
|
||||||
|
decodeFileStrict',
|
||||||
|
eitherDecodeStrict',
|
||||||
|
encodeFile,
|
||||||
|
)
|
||||||
|
import Data.Foldable (Foldable (toList), foldl')
|
||||||
|
import Data.Function ((&))
|
||||||
|
import Data.Functor ((<&>))
|
||||||
|
import Data.List.NonEmpty (NonEmpty, nonEmpty)
|
||||||
|
import qualified Data.List.NonEmpty as NonEmpty
|
||||||
|
import Data.Map.Strict (Map)
|
||||||
|
import qualified Data.Map.Strict as Map
|
||||||
|
import Data.Maybe (fromMaybe, mapMaybe)
|
||||||
|
import Data.Monoid (Sum (Sum, getSum))
|
||||||
|
import Data.Sequence (Seq)
|
||||||
|
import qualified Data.Sequence as Seq
|
||||||
|
import Data.Set (Set)
|
||||||
|
import qualified Data.Set as Set
|
||||||
|
import Data.Text (Text)
|
||||||
|
import qualified Data.Text as Text
|
||||||
|
import Data.Text.Encoding (encodeUtf8)
|
||||||
|
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,
|
||||||
|
(/:),
|
||||||
|
)
|
||||||
|
import System.Directory (XdgDirectory (XdgCache), getXdgDirectory)
|
||||||
|
import System.Environment (getArgs)
|
||||||
|
import System.Process (readProcess)
|
||||||
|
import Prelude hiding (id)
|
||||||
|
import qualified Prelude
|
||||||
|
|
||||||
|
newtype JobsetEvals = JobsetEvals
|
||||||
|
{ evals :: Seq Eval
|
||||||
|
}
|
||||||
|
deriving (Generic, ToJSON, FromJSON, Show)
|
||||||
|
|
||||||
|
newtype Nixpkgs = Nixpkgs {revision :: Text}
|
||||||
|
deriving (Generic, ToJSON, FromJSON, Show)
|
||||||
|
|
||||||
|
newtype JobsetEvalInputs = JobsetEvalInputs {nixpkgs :: Nixpkgs}
|
||||||
|
deriving (Generic, ToJSON, FromJSON, Show)
|
||||||
|
|
||||||
|
data Eval = Eval
|
||||||
|
{ id :: Int
|
||||||
|
, jobsetevalinputs :: JobsetEvalInputs
|
||||||
|
}
|
||||||
|
deriving (Generic, ToJSON, FromJSON, Show)
|
||||||
|
|
||||||
|
data Build = Build
|
||||||
|
{ job :: Text
|
||||||
|
, buildstatus :: Maybe Int
|
||||||
|
, finished :: Int
|
||||||
|
, id :: Int
|
||||||
|
, nixname :: Text
|
||||||
|
, system :: Text
|
||||||
|
, jobsetevals :: Seq Int
|
||||||
|
}
|
||||||
|
deriving (Generic, ToJSON, FromJSON, Show)
|
||||||
|
|
||||||
|
main :: IO ()
|
||||||
|
main = do
|
||||||
|
args <- getArgs
|
||||||
|
case args of
|
||||||
|
["get-report"] -> getBuildReports
|
||||||
|
["ping-maintainers"] -> printMaintainerPing
|
||||||
|
["mark-broken-list"] -> printMarkBrokenList
|
||||||
|
_ -> putStrLn "Usage: get-report | ping-maintainers | mark-broken-list"
|
||||||
|
|
||||||
|
reportFileName :: IO FilePath
|
||||||
|
reportFileName = getXdgDirectory XdgCache "haskell-updates-build-report.json"
|
||||||
|
|
||||||
|
showT :: Show a => a -> Text
|
||||||
|
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
|
||||||
|
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)
|
||||||
|
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)
|
||||||
|
|
||||||
|
hydraEvalCommand :: FilePath
|
||||||
|
hydraEvalCommand = "hydra-eval-jobs"
|
||||||
|
hydraEvalParams :: [String]
|
||||||
|
hydraEvalParams = ["-I", ".", "pkgs/top-level/release-haskell.nix"]
|
||||||
|
handlesCommand :: FilePath
|
||||||
|
handlesCommand = "nix-instantiate"
|
||||||
|
handlesParams :: [String]
|
||||||
|
handlesParams = ["--eval", "--strict", "--json", "-"]
|
||||||
|
handlesExpression :: String
|
||||||
|
handlesExpression = "with import ./. {}; with lib; zipAttrsWith (_: builtins.head) (mapAttrsToList (_: v: if v ? github then { \"${v.email}\" = v.github; } else {}) (import maintainers/maintainer-list.nix))"
|
||||||
|
|
||||||
|
newtype Maintainers = Maintainers {maintainers :: Maybe Text} deriving (Generic, ToJSON, FromJSON)
|
||||||
|
|
||||||
|
type HydraJobs = Map Text Maintainers
|
||||||
|
type MaintainerMap = Map Text (NonEmpty Text)
|
||||||
|
|
||||||
|
getMaintainerMap :: IO MaintainerMap
|
||||||
|
getMaintainerMap = do
|
||||||
|
hydraJobs :: HydraJobs <- get hydraEvalCommand hydraEvalParams "" "Failed to decode hydra-eval-jobs output: "
|
||||||
|
handlesMap :: Map Text Text <- get handlesCommand handlesParams handlesExpression "Failed to decode nix output for lookup of github handles: "
|
||||||
|
pure $ hydraJobs & Map.mapMaybe (nonEmpty . mapMaybe (`Map.lookup` handlesMap) . Text.splitOn ", " . fromMaybe "" . maintainers)
|
||||||
|
where
|
||||||
|
get c p i e = readProcess c p i <&> \x -> either (error . (<> " Raw:'" <> take 1000 x <> "'") . (e <>)) Prelude.id . eitherDecodeStrict' . encodeUtf8 . Text.pack $ x
|
||||||
|
|
||||||
|
-- BuildStates are sorted by subjective importance/concerningness
|
||||||
|
data BuildState = Failed | DependencyFailed | OutputLimitExceeded | Unknown (Maybe Int) | TimedOut | Canceled | Unfinished | Success deriving (Show, Eq, Ord)
|
||||||
|
|
||||||
|
icon :: BuildState -> Text
|
||||||
|
icon = \case
|
||||||
|
Failed -> ":x:"
|
||||||
|
DependencyFailed -> ":heavy_exclamation_mark:"
|
||||||
|
OutputLimitExceeded -> ":warning:"
|
||||||
|
Unknown x -> "unknown code " <> showT x
|
||||||
|
TimedOut -> ":hourglass::no_entry_sign:"
|
||||||
|
Canceled -> ":no_entry_sign:"
|
||||||
|
Unfinished -> ":hourglass_flowing_sand:"
|
||||||
|
Success -> ":heavy_check_mark:"
|
||||||
|
|
||||||
|
platformIcon :: Platform -> Text
|
||||||
|
platformIcon (Platform x) = case x of
|
||||||
|
"x86_64-linux" -> ":penguin:"
|
||||||
|
"aarch64-linux" -> ":iphone:"
|
||||||
|
"x86_64-darwin" -> ":apple:"
|
||||||
|
_ -> x
|
||||||
|
|
||||||
|
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)
|
||||||
|
|
||||||
|
instance (Ord row, Ord col, Semigroup a) => Semigroup (Table row col a) where
|
||||||
|
Table l <> Table r = Table (Map.unionWith (<>) l r)
|
||||||
|
instance (Ord row, Ord col, Semigroup a) => Monoid (Table row col a) where
|
||||||
|
mempty = Table Map.empty
|
||||||
|
instance Functor (Table row col) where
|
||||||
|
fmap f (Table a) = Table (fmap f a)
|
||||||
|
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
|
||||||
|
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)
|
||||||
|
where
|
||||||
|
state :: BuildState
|
||||||
|
state = case (finished, buildstatus) of
|
||||||
|
(0, _) -> Unfinished
|
||||||
|
(_, Just 0) -> Success
|
||||||
|
(_, Just 4) -> Canceled
|
||||||
|
(_, Just 7) -> TimedOut
|
||||||
|
(_, Just 2) -> DependencyFailed
|
||||||
|
(_, Just 1) -> Failed
|
||||||
|
(_, Just 11) -> OutputLimitExceeded
|
||||||
|
(_, i) -> Unknown i
|
||||||
|
packageName = fromMaybe job (Text.stripSuffix ("." <> system) job)
|
||||||
|
splitted = nonEmpty $ Text.splitOn "." packageName
|
||||||
|
name = maybe packageName NonEmpty.last splitted
|
||||||
|
set = maybe "" (Text.intercalate "." . NonEmpty.init) splitted
|
||||||
|
maintainers = maybe mempty (Set.fromList . toList) (Map.lookup job maintainerMap)
|
||||||
|
|
||||||
|
readBuildReports :: IO (Eval, UTCTime, Seq Build)
|
||||||
|
readBuildReports = do
|
||||||
|
file <- reportFileName
|
||||||
|
fromMaybe (error $ "Could not decode " <> file) <$> decodeFileStrict' file
|
||||||
|
|
||||||
|
sep :: Text
|
||||||
|
sep = " | "
|
||||||
|
joinTable :: [Text] -> Text
|
||||||
|
joinTable t = sep <> Text.intercalate sep t <> sep
|
||||||
|
|
||||||
|
type NumSummary = Table Platform BuildState Int
|
||||||
|
|
||||||
|
printTable :: (Ord rows, Ord cols) => Text -> (rows -> Text) -> (cols -> Text) -> (entries -> Text) -> Table rows cols entries -> [Text]
|
||||||
|
printTable name showR showC showE (Table mapping) = joinTable <$> (name : map showC cols) : replicate (length cols + sepsInName + 1) "---" : map printRow rows
|
||||||
|
where
|
||||||
|
sepsInName = Text.count "|" name
|
||||||
|
printRow row = showR row : map (\col -> maybe "" showE (Map.lookup (row, col) mapping)) cols
|
||||||
|
rows = toList $ Set.fromList (fst <$> Map.keys mapping)
|
||||||
|
cols = toList $ Set.fromList (snd <$> Map.keys mapping)
|
||||||
|
|
||||||
|
printJob :: Int -> Text -> (Table Text Platform BuildResult, Text) -> [Text]
|
||||||
|
printJob evalId name (Table mapping, maintainers) =
|
||||||
|
if length sets <= 1
|
||||||
|
then map printSingleRow sets
|
||||||
|
else ["- [ ] " <> makeJobSearchLink "" name <> " " <> maintainers] <> map printRow sets
|
||||||
|
where
|
||||||
|
printRow set = " - " <> printState set <> " " <> makeJobSearchLink set (if Text.null set then "toplevel" else set)
|
||||||
|
printSingleRow set = "- [ ] " <> printState set <> " " <> makeJobSearchLink set (makePkgName set) <> " " <> maintainers
|
||||||
|
makePkgName set = (if Text.null set then "" else set <> ".") <> name
|
||||||
|
printState set = Text.intercalate " " $ map (\pf -> maybe "" (label pf) $ Map.lookup (set, pf) mapping) platforms
|
||||||
|
makeJobSearchLink set linkLabel= makeSearchLink evalId linkLabel (makePkgName set <> ".") -- Append '.' to the search query to prevent e.g. "hspec." matching "hspec-golden.x86_64-linux"
|
||||||
|
sets = toList $ Set.fromList (fst <$> Map.keys mapping)
|
||||||
|
platforms = toList $ Set.fromList (snd <$> Map.keys mapping)
|
||||||
|
label pf (BuildResult s i) = "[[" <> platformIcon pf <> icon s <> "]](https://hydra.nixos.org/build/" <> showT i <> ")"
|
||||||
|
|
||||||
|
makeSearchLink :: Int -> Text -> Text -> Text
|
||||||
|
makeSearchLink evalId linkLabel query = "[" <> linkLabel <> "](" <> "https://hydra.nixos.org/eval/" <> showT evalId <> "?filter=" <> query <> ")"
|
||||||
|
|
||||||
|
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)
|
||||||
|
|
||||||
|
details :: Text -> [Text] -> [Text]
|
||||||
|
details summary content = ["<details><summary>" <> summary <> " </summary>", ""] <> content <> ["</details>", ""]
|
||||||
|
|
||||||
|
printBuildSummary :: Eval -> UTCTime -> StatusSummary -> Text
|
||||||
|
printBuildSummary
|
||||||
|
Eval{id, jobsetevalinputs = JobsetEvalInputs{nixpkgs = Nixpkgs{revision}}}
|
||||||
|
fetchTime
|
||||||
|
summary =
|
||||||
|
Text.unlines $
|
||||||
|
headline <> 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)
|
||||||
|
<> 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)*"]
|
||||||
|
totals =
|
||||||
|
[ "#### Build summary"
|
||||||
|
, ""
|
||||||
|
]
|
||||||
|
<> printTable "Platform" (\x -> makeSearchLink id (platform x <> " " <> platformIcon x) ("." <> platform x)) (\x -> showT x <> " " <> icon x) showT (statusToNumSummary summary)
|
||||||
|
headline =
|
||||||
|
[ "### [haskell-updates build report from hydra](https://hydra.nixos.org/jobset/nixpkgs/haskell-updates)"
|
||||||
|
, "*evaluation ["
|
||||||
|
<> showT id
|
||||||
|
<> "](https://hydra.nixos.org/eval/"
|
||||||
|
<> showT id
|
||||||
|
<> ") of nixpkgs commit ["
|
||||||
|
<> Text.take 7 revision
|
||||||
|
<> "](https://github.com/NixOS/nixpkgs/commits/"
|
||||||
|
<> revision
|
||||||
|
<> ") as of "
|
||||||
|
<> Text.pack (formatTime defaultTimeLocale "%Y-%m-%d %H:%M UTC" fetchTime)
|
||||||
|
<> "*"
|
||||||
|
]
|
||||||
|
jobsByState predicate = Map.filter (predicate . foldl' min Success . fmap state . fst) summary
|
||||||
|
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)
|
||||||
|
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, "")
|
||||||
|
showMaintainedBuild (name, (table, maintainers)) = printJob id name (table, Text.intercalate " " (fmap ("@" <>) (toList maintainers)))
|
||||||
|
|
||||||
|
printMaintainerPing :: IO ()
|
||||||
|
printMaintainerPing = do
|
||||||
|
maintainerMap <- getMaintainerMap
|
||||||
|
(eval, fetchTime, buildReport) <- readBuildReports
|
||||||
|
putStrLn (Text.unpack (printBuildSummary eval fetchTime (buildSummary maintainerMap buildReport)))
|
||||||
|
|
||||||
|
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
|
||||||
|
_ -> pure ()
|
45
maintainers/scripts/haskell/mark-broken.sh
Executable file
45
maintainers/scripts/haskell/mark-broken.sh
Executable file
@ -0,0 +1,45 @@
|
|||||||
|
#! /usr/bin/env nix-shell
|
||||||
|
#! nix-shell -i bash -p coreutils git -I nixpkgs=.
|
||||||
|
|
||||||
|
# This script uses the data pulled with
|
||||||
|
# maintainers/scripts/haskell/hydra-report.hs get-report to produce a list of
|
||||||
|
# failing builds that get written to the hackage2nix config. Then
|
||||||
|
# hackage-packages.nix gets regenerated and transitive-broken packages get
|
||||||
|
# marked as dont-distribute in the config as well.
|
||||||
|
# This should disable builds for most failing jobs in the haskell-updates jobset.
|
||||||
|
|
||||||
|
set -euo pipefail
|
||||||
|
|
||||||
|
broken_config="pkgs/development/haskell-modules/configuration-hackage2nix/broken.yaml"
|
||||||
|
|
||||||
|
tmpfile=$(mktemp)
|
||||||
|
trap "rm ${tmpfile}" 0
|
||||||
|
|
||||||
|
echo "Remember that you need to manually run 'maintainers/scripts/haskell/hydra-report.hs get-report' sometime before running this script."
|
||||||
|
echo "Generating a list of broken builds and displaying for manual confirmation ..."
|
||||||
|
maintainers/scripts/haskell/hydra-report.hs mark-broken-list | sort -i > $tmpfile
|
||||||
|
|
||||||
|
$EDITOR $tmpfile
|
||||||
|
|
||||||
|
tail -n +3 "$broken_config" >> "$tmpfile"
|
||||||
|
|
||||||
|
cat > "$broken_config" << EOF
|
||||||
|
broken-packages:
|
||||||
|
# These packages don't compile.
|
||||||
|
EOF
|
||||||
|
|
||||||
|
sort -iu "$tmpfile" >> "$broken_config"
|
||||||
|
maintainers/scripts/haskell/regenerate-hackage-packages.sh
|
||||||
|
maintainers/scripts/haskell/regenerate-transitive-broken-packages.sh
|
||||||
|
maintainers/scripts/haskell/regenerate-hackage-packages.sh
|
||||||
|
|
||||||
|
if [[ "${1:-}" == "--do-commit" ]]; then
|
||||||
|
git add $broken_config
|
||||||
|
git add pkgs/development/haskell-modules/configuration-hackage2nix/transitive-broken.yaml
|
||||||
|
git add pkgs/development/haskell-modules/hackage-packages.nix
|
||||||
|
git commit -F - << EOF
|
||||||
|
hackage2nix: Mark failing builds broken
|
||||||
|
|
||||||
|
This commit has been generated by maintainers/scripts/haskell/mark-broken.sh
|
||||||
|
EOF
|
||||||
|
fi
|
@ -1,3 +1,15 @@
|
|||||||
#! /usr/bin/env nix-shell
|
#! /usr/bin/env nix-shell
|
||||||
#! nix-shell -i bash -p coreutils nix gnused -I nixpkgs=.
|
#! nix-shell -i bash -p coreutils nix gnused -I nixpkgs=.
|
||||||
echo -e $(nix-instantiate --eval --strict maintainers/scripts/haskell/transitive-broken-packages.nix) | sed 's/\"//' > pkgs/development/haskell-modules/configuration-hackage2nix/transitive-broken.yaml
|
|
||||||
|
config_file=pkgs/development/haskell-modules/configuration-hackage2nix/transitive-broken.yaml
|
||||||
|
|
||||||
|
cat > $config_file << EOF
|
||||||
|
# This file is automatically generated by
|
||||||
|
# maintainers/scripts/haskell/regenerate-transitive-broken-packages.sh
|
||||||
|
# It is supposed to list all haskellPackages that cannot evaluate because they
|
||||||
|
# depend on a dependency marked as broken.
|
||||||
|
dont-distribute-packages:
|
||||||
|
EOF
|
||||||
|
|
||||||
|
echo "Regenerating list of transitive broken packages ..."
|
||||||
|
echo -e $(nix-instantiate --eval --strict maintainers/scripts/haskell/transitive-broken-packages.nix) | sed 's/\"//' | sort -i >> $config_file
|
||||||
|
@ -12,10 +12,5 @@ let
|
|||||||
(getEvaluating (nixpkgs { config.allowBroken = true; }).haskellPackages);
|
(getEvaluating (nixpkgs { config.allowBroken = true; }).haskellPackages);
|
||||||
in
|
in
|
||||||
''
|
''
|
||||||
# This file is automatically generated by
|
|
||||||
# maintainers/scripts/haskell/regenerate-transitive-broken-packages.sh
|
|
||||||
# It is supposed to list all haskellPackages that cannot evaluate because they
|
|
||||||
# depend on a dependency marked as broken.
|
|
||||||
dont-distribute-packages:
|
|
||||||
${lib.concatMapStringsSep "\n" (x: " - ${x}") brokenDeps}
|
${lib.concatMapStringsSep "\n" (x: " - ${x}") brokenDeps}
|
||||||
''
|
''
|
||||||
|
@ -92,4 +92,8 @@ mkDerivation (common "tamarin-prover" src // {
|
|||||||
tamarin-prover-term
|
tamarin-prover-term
|
||||||
tamarin-prover-theory
|
tamarin-prover-theory
|
||||||
];
|
];
|
||||||
|
|
||||||
|
# tamarin-prover 1.6 is incompatible with maude 3.1.
|
||||||
|
hydraPlatforms = lib.platforms.none;
|
||||||
|
broken = true;
|
||||||
})
|
})
|
||||||
|
@ -61,6 +61,7 @@ self: super: {
|
|||||||
hsakamai = dontCheck super.hsakamai;
|
hsakamai = dontCheck super.hsakamai;
|
||||||
hsemail-ns = dontCheck super.hsemail-ns;
|
hsemail-ns = dontCheck super.hsemail-ns;
|
||||||
openapi3 = dontCheck super.openapi3;
|
openapi3 = dontCheck super.openapi3;
|
||||||
|
strict-writer = dontCheck super.strict-writer;
|
||||||
|
|
||||||
# https://github.com/ekmett/half/issues/35
|
# https://github.com/ekmett/half/issues/35
|
||||||
half = dontCheck super.half;
|
half = dontCheck super.half;
|
||||||
|
@ -1037,9 +1037,6 @@ self: super: {
|
|||||||
# Has tasty < 1.2 requirement, but works just fine with 1.2
|
# Has tasty < 1.2 requirement, but works just fine with 1.2
|
||||||
temporary-resourcet = doJailbreak super.temporary-resourcet;
|
temporary-resourcet = doJailbreak super.temporary-resourcet;
|
||||||
|
|
||||||
# Requires dhall >= 1.23.0
|
|
||||||
ats-pkg = dontCheck (super.ats-pkg.override { dhall = self.dhall_1_29_0; });
|
|
||||||
|
|
||||||
# fake a home dir and capture generated man page
|
# fake a home dir and capture generated man page
|
||||||
ats-format = overrideCabal super.ats-format (old : {
|
ats-format = overrideCabal super.ats-format (old : {
|
||||||
preConfigure = "export HOME=$PWD";
|
preConfigure = "export HOME=$PWD";
|
||||||
@ -1068,18 +1065,6 @@ self: super: {
|
|||||||
# https://github.com/erikd/hjsmin/issues/32
|
# https://github.com/erikd/hjsmin/issues/32
|
||||||
hjsmin = dontCheck super.hjsmin;
|
hjsmin = dontCheck super.hjsmin;
|
||||||
|
|
||||||
nix-tools = super.nix-tools.overrideScope (self: super: {
|
|
||||||
# Needs https://github.com/peti/hackage-db/pull/9
|
|
||||||
hackage-db = super.hackage-db.overrideAttrs (old: {
|
|
||||||
src = pkgs.fetchFromGitHub {
|
|
||||||
owner = "ElvishJerricco";
|
|
||||||
repo = "hackage-db";
|
|
||||||
rev = "84ca9fc75ad45a71880e938e0d93ea4bde05f5bd";
|
|
||||||
sha256 = "0y3kw1hrxhsqmyx59sxba8npj4ya8dpgjljc21gkgdvdy9628q4c";
|
|
||||||
};
|
|
||||||
});
|
|
||||||
});
|
|
||||||
|
|
||||||
# upstream issue: https://github.com/vmchale/atspkg/issues/12
|
# upstream issue: https://github.com/vmchale/atspkg/issues/12
|
||||||
language-ats = dontCheck super.language-ats;
|
language-ats = dontCheck super.language-ats;
|
||||||
|
|
||||||
@ -1864,4 +1849,44 @@ self: super: {
|
|||||||
# 2021-05-09: Restrictive bound on hspec-golden. Dep removed in newer versions.
|
# 2021-05-09: Restrictive bound on hspec-golden. Dep removed in newer versions.
|
||||||
tomland = assert super.tomland.version == "1.3.2.0"; doJailbreak super.tomland;
|
tomland = assert super.tomland.version == "1.3.2.0"; doJailbreak super.tomland;
|
||||||
|
|
||||||
|
# 2021-05-09 haskell-ci pins ShellCheck 0.7.1
|
||||||
|
# https://github.com/haskell-CI/haskell-ci/issues/507
|
||||||
|
haskell-ci = super.haskell-ci.override {
|
||||||
|
ShellCheck = self.ShellCheck_0_7_1;
|
||||||
|
};
|
||||||
|
|
||||||
|
Frames-streamly = overrideCabal (super.Frames-streamly.override { relude = super.relude_1_0_0_1; }) (drv: {
|
||||||
|
# https://github.com/adamConnerSax/Frames-streamly/issues/1
|
||||||
|
patchPhase = ''
|
||||||
|
cat > example_data/acs100k.csv <<EOT
|
||||||
|
"YEAR","REGION","STATEFIP","DENSITY","METRO","PUMA","PERWT","SEX","AGE","RACE","RACED","HISPAN","HISPAND","CITIZEN","LANGUAGE","LANGUAGED","SPEAKENG","EDUC","EDUCD","GRADEATT","GRADEATTD","EMPSTAT","EMPSTATD","INCTOT","INCSS","POVERTY"
|
||||||
|
2006,32,1,409.6,3,2300,87.0,1,47,1,100,0,0,0,1,100,3,6,65,0,0,1,12,36000,0,347
|
||||||
|
EOT
|
||||||
|
''; });
|
||||||
|
|
||||||
|
# 2021-05-09: compilation requires patches from master,
|
||||||
|
# remove at next release (current is 0.1.0.4).
|
||||||
|
large-hashable = appendPatches super.large-hashable [
|
||||||
|
# Fix compilation of TH code for GHC >= 8.8
|
||||||
|
(pkgs.fetchpatch {
|
||||||
|
url = "https://github.com/factisresearch/large-hashable/commit/ee7afe4bd181cf15a324c7f4823f7a348e4a0e6b.patch";
|
||||||
|
sha256 = "1ha77v0bc6prxacxhpdfgcsgw8348gvhl9y81smigifgjbinphxv";
|
||||||
|
excludes = [
|
||||||
|
".travis.yml"
|
||||||
|
"stack**"
|
||||||
|
];
|
||||||
|
})
|
||||||
|
# Fix cpp invocation
|
||||||
|
(pkgs.fetchpatch {
|
||||||
|
url = "https://github.com/factisresearch/large-hashable/commit/7b7c2ed6ac6e096478e8ee00160fa9d220df853a.patch";
|
||||||
|
sha256 = "1sf9h3k8jbbgfshzrclaawlwx7k2frb09z2a64f93jhvk6ci6vgx";
|
||||||
|
})
|
||||||
|
];
|
||||||
|
|
||||||
|
# BSON defaults to requiring network instead of network-bsd which is
|
||||||
|
# required nowadays: https://github.com/mongodb-haskell/bson/issues/26
|
||||||
|
bson = appendConfigureFlag (super.bson.override {
|
||||||
|
network = self.network-bsd;
|
||||||
|
}) "-f-_old_network";
|
||||||
|
|
||||||
} // import ./configuration-tensorflow.nix {inherit pkgs haskellLib;} self super
|
} // import ./configuration-tensorflow.nix {inherit pkgs haskellLib;} self super
|
||||||
|
@ -161,4 +161,11 @@ self: super: {
|
|||||||
] ++ (drv.librarySystemDepends or []);
|
] ++ (drv.librarySystemDepends or []);
|
||||||
});
|
});
|
||||||
|
|
||||||
|
HTF = overrideCabal super.HTF (drv: {
|
||||||
|
# GNU find is not prefixed in stdenv
|
||||||
|
postPatch = ''
|
||||||
|
substituteInPlace scripts/local-htfpp --replace "find=gfind" "find=find"
|
||||||
|
'' + (drv.postPatch or "");
|
||||||
|
});
|
||||||
|
|
||||||
}
|
}
|
||||||
|
@ -11,8 +11,7 @@ with haskellLib;
|
|||||||
|
|
||||||
self: super: {
|
self: super: {
|
||||||
|
|
||||||
# This compiler version needs llvm 6.x.
|
llvmPackages = pkgs.llvmPackages_10;
|
||||||
llvmPackages = pkgs.llvmPackages_6;
|
|
||||||
|
|
||||||
# Disable GHC 8.7.x core libraries.
|
# Disable GHC 8.7.x core libraries.
|
||||||
array = null;
|
array = null;
|
||||||
|
File diff suppressed because it is too large
Load Diff
@ -104,6 +104,7 @@ extra-packages:
|
|||||||
- gi-gdk == 3.0.24 # 2021-05-07: For haskell-gi 0.25 without gtk4
|
- gi-gdk == 3.0.24 # 2021-05-07: For haskell-gi 0.25 without gtk4
|
||||||
- gi-gtk < 4.0 # 2021-05-07: For haskell-gi 0.25 without gtk4
|
- gi-gtk < 4.0 # 2021-05-07: For haskell-gi 0.25 without gtk4
|
||||||
- gi-gdkx11 == 3.0.11 # 2021-05-07: For haskell-gi 0.25 without gtk4
|
- gi-gdkx11 == 3.0.11 # 2021-05-07: For haskell-gi 0.25 without gtk4
|
||||||
|
- ShellCheck == 0.7.1 # 2021-05-09: haskell-ci 0.12.1 pins this version
|
||||||
|
|
||||||
package-maintainers:
|
package-maintainers:
|
||||||
peti:
|
peti:
|
||||||
@ -219,20 +220,22 @@ package-maintainers:
|
|||||||
- gitit
|
- gitit
|
||||||
- yarn-lock
|
- yarn-lock
|
||||||
- yarn2nix
|
- yarn2nix
|
||||||
|
- large-hashable
|
||||||
poscat:
|
poscat:
|
||||||
- hinit
|
- hinit
|
||||||
bdesham:
|
bdesham:
|
||||||
- pinboard-notes-backup
|
- pinboard-notes-backup
|
||||||
|
|
||||||
unsupported-platforms:
|
unsupported-platforms:
|
||||||
|
Allure: [ x86_64-darwin ]
|
||||||
alsa-mixer: [ x86_64-darwin ]
|
alsa-mixer: [ x86_64-darwin ]
|
||||||
alsa-pcm: [ x86_64-darwin ]
|
alsa-pcm: [ x86_64-darwin ]
|
||||||
alsa-seq: [ x86_64-darwin ]
|
alsa-seq: [ x86_64-darwin ]
|
||||||
AWin32Console: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
AWin32Console: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
||||||
barbly: [ i686-linux, x86_64-linux, aarch64-linux, armv7l-linux ]
|
barbly: [ i686-linux, x86_64-linux, aarch64-linux, armv7l-linux ]
|
||||||
bdcs-api: [ x86_64-darwin ]
|
bdcs-api: [ x86_64-darwin ]
|
||||||
bindings-sane: [ x86_64-darwin ]
|
|
||||||
bindings-directfb: [ x86_64-darwin ]
|
bindings-directfb: [ x86_64-darwin ]
|
||||||
|
bindings-sane: [ x86_64-darwin ]
|
||||||
cut-the-crap: [ x86_64-darwin ]
|
cut-the-crap: [ x86_64-darwin ]
|
||||||
d3d11binding: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
d3d11binding: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
||||||
DirectSound: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
DirectSound: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
||||||
@ -242,8 +245,9 @@ unsupported-platforms:
|
|||||||
Euterpea: [ x86_64-darwin ]
|
Euterpea: [ x86_64-darwin ]
|
||||||
freenect: [ x86_64-darwin ]
|
freenect: [ x86_64-darwin ]
|
||||||
FTGL: [ x86_64-darwin ]
|
FTGL: [ x86_64-darwin ]
|
||||||
gi-dbusmenugtk3: [ x86_64-darwin ]
|
ghcjs-dom-hello: [ x86_64-darwin ]
|
||||||
gi-dbusmenu: [ x86_64-darwin ]
|
gi-dbusmenu: [ x86_64-darwin ]
|
||||||
|
gi-dbusmenugtk3: [ x86_64-darwin ]
|
||||||
gi-ggit: [ x86_64-darwin ]
|
gi-ggit: [ x86_64-darwin ]
|
||||||
gi-ibus: [ x86_64-darwin ]
|
gi-ibus: [ x86_64-darwin ]
|
||||||
gi-ostree: [ x86_64-darwin ]
|
gi-ostree: [ x86_64-darwin ]
|
||||||
@ -256,8 +260,12 @@ unsupported-platforms:
|
|||||||
HFuse: [ x86_64-darwin ]
|
HFuse: [ x86_64-darwin ]
|
||||||
hidapi: [ x86_64-darwin ]
|
hidapi: [ x86_64-darwin ]
|
||||||
hommage-ds: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
hommage-ds: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
||||||
|
hpapi: [ x86_64-darwin ]
|
||||||
HSoM: [ x86_64-darwin ]
|
HSoM: [ x86_64-darwin ]
|
||||||
iwlib: [ x86_64-darwin ]
|
iwlib: [ x86_64-darwin ]
|
||||||
|
jsaddle-webkit2gtk: [ x86_64-darwin ]
|
||||||
|
LambdaHack: [ x86_64-darwin ]
|
||||||
|
large-hashable: [ aarch64-linux ] # https://github.com/factisresearch/large-hashable/issues/17
|
||||||
libmodbus: [ x86_64-darwin ]
|
libmodbus: [ x86_64-darwin ]
|
||||||
libsystemd-journal: [ x86_64-darwin ]
|
libsystemd-journal: [ x86_64-darwin ]
|
||||||
libtelnet: [ x86_64-darwin ]
|
libtelnet: [ x86_64-darwin ]
|
||||||
@ -266,10 +274,10 @@ unsupported-platforms:
|
|||||||
lio-fs: [ x86_64-darwin ]
|
lio-fs: [ x86_64-darwin ]
|
||||||
logging-facade-journald: [ x86_64-darwin ]
|
logging-facade-journald: [ x86_64-darwin ]
|
||||||
midi-alsa: [ x86_64-darwin ]
|
midi-alsa: [ x86_64-darwin ]
|
||||||
mpi-hs: [ aarch64-linux, x86_64-darwin ]
|
|
||||||
mpi-hs-binary: [ aarch64-linux, x86_64-darwin ]
|
mpi-hs-binary: [ aarch64-linux, x86_64-darwin ]
|
||||||
mpi-hs-cereal: [ aarch64-linux, x86_64-darwin ]
|
mpi-hs-cereal: [ aarch64-linux, x86_64-darwin ]
|
||||||
mpi-hs-store: [ aarch64-linux, x86_64-darwin ]
|
mpi-hs-store: [ aarch64-linux, x86_64-darwin ]
|
||||||
|
mpi-hs: [ aarch64-linux, x86_64-darwin ]
|
||||||
mplayer-spot: [ aarch64-linux ]
|
mplayer-spot: [ aarch64-linux ]
|
||||||
oculus: [ x86_64-darwin ]
|
oculus: [ x86_64-darwin ]
|
||||||
pam: [ x86_64-darwin ]
|
pam: [ x86_64-darwin ]
|
||||||
@ -279,7 +287,9 @@ unsupported-platforms:
|
|||||||
posix-api: [ x86_64-darwin ]
|
posix-api: [ x86_64-darwin ]
|
||||||
Raincat: [ x86_64-darwin ]
|
Raincat: [ x86_64-darwin ]
|
||||||
reactivity: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
reactivity: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
||||||
reflex-dom: [ x86_64-darwin ]
|
reflex-dom-fragment-shader-canvas: [ x86_64-darwin, aarch64-linux ]
|
||||||
|
reflex-dom: [ x86_64-darwin, aarch64-linux ]
|
||||||
|
reflex-localize-dom: [ x86_64-darwin, aarch64-linux ]
|
||||||
rtlsdr: [ x86_64-darwin ]
|
rtlsdr: [ x86_64-darwin ]
|
||||||
rubberband: [ x86_64-darwin ]
|
rubberband: [ x86_64-darwin ]
|
||||||
sbv: [ aarch64-linux ]
|
sbv: [ aarch64-linux ]
|
||||||
@ -290,21 +300,22 @@ unsupported-platforms:
|
|||||||
termonad: [ x86_64-darwin ]
|
termonad: [ x86_64-darwin ]
|
||||||
tokyotyrant-haskell: [ x86_64-darwin ]
|
tokyotyrant-haskell: [ x86_64-darwin ]
|
||||||
udev: [ x86_64-darwin ]
|
udev: [ x86_64-darwin ]
|
||||||
|
verifiable-expressions: [ aarch64-linux ]
|
||||||
vrpn: [ x86_64-darwin ]
|
vrpn: [ x86_64-darwin ]
|
||||||
|
vulkan-utils: [ x86_64-darwin ]
|
||||||
vulkan: [ i686-linux, armv7l-linux, x86_64-darwin ]
|
vulkan: [ i686-linux, armv7l-linux, x86_64-darwin ]
|
||||||
VulkanMemoryAllocator: [ i686-linux, armv7l-linux, x86_64-darwin ]
|
VulkanMemoryAllocator: [ i686-linux, armv7l-linux, x86_64-darwin ]
|
||||||
vulkan-utils: [ x86_64-darwin ]
|
|
||||||
webkit2gtk3-javascriptcore: [ x86_64-darwin ]
|
webkit2gtk3-javascriptcore: [ x86_64-darwin ]
|
||||||
Win32-console: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
Win32-console: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
||||||
Win32-dhcp-server: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
Win32-dhcp-server: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
||||||
Win32-errors: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
Win32-errors: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
||||||
Win32-extras: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
Win32-extras: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
||||||
Win32: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
|
||||||
Win32-junction-point: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
Win32-junction-point: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
||||||
Win32-notify: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
Win32-notify: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
||||||
Win32-security: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
Win32-security: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
||||||
Win32-services: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
|
||||||
Win32-services-wrapper: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
Win32-services-wrapper: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
||||||
|
Win32-services: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
||||||
|
Win32: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
||||||
xattr: [ x86_64-darwin ]
|
xattr: [ x86_64-darwin ]
|
||||||
xgboost-haskell: [ aarch64-linux, armv7l-linux ]
|
xgboost-haskell: [ aarch64-linux, armv7l-linux ]
|
||||||
XInput: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
XInput: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ]
|
||||||
@ -358,69 +369,26 @@ dont-distribute-packages:
|
|||||||
- yices-easy
|
- yices-easy
|
||||||
- yices-painless
|
- yices-painless
|
||||||
|
|
||||||
# these packages don't evaluate because they have broken (system) dependencies
|
# These packages don‘t build because they use deprecated webkit versions.
|
||||||
- XML
|
|
||||||
- comark
|
|
||||||
- couch-simple
|
|
||||||
- diagrams-hsqml
|
- diagrams-hsqml
|
||||||
- diagrams-reflex
|
|
||||||
- dialog
|
- dialog
|
||||||
- fltkhs-demos
|
|
||||||
- fltkhs-fluid-demos
|
|
||||||
- fltkhs-hello-world
|
|
||||||
- fltkhs-themes
|
|
||||||
- ghcjs-dom-hello
|
|
||||||
- ghcjs-dom-webkit
|
- ghcjs-dom-webkit
|
||||||
- gi-javascriptcore
|
|
||||||
- gi-webkit
|
- gi-webkit
|
||||||
- gi-webkit2
|
|
||||||
- gi-webkit2webextension
|
|
||||||
- gsmenu
|
|
||||||
- haste-gapi
|
|
||||||
- haste-perch
|
|
||||||
- hbro
|
|
||||||
- hplayground
|
|
||||||
- hs-mesos
|
- hs-mesos
|
||||||
- hsqml
|
- hsqml
|
||||||
- hsqml-datamodel
|
- hsqml-datamodel
|
||||||
- hsqml-datamodel-vinyl
|
|
||||||
- hsqml-datemodel-vinyl
|
|
||||||
- hsqml-demo-manic
|
- hsqml-demo-manic
|
||||||
- hsqml-demo-morris
|
|
||||||
- hsqml-demo-notes
|
|
||||||
- hsqml-demo-notes
|
- hsqml-demo-notes
|
||||||
- hsqml-demo-samples
|
- hsqml-demo-samples
|
||||||
- hsqml-morris
|
|
||||||
- hsqml-morris
|
|
||||||
- hstorchat
|
- hstorchat
|
||||||
- imprevu-happstack
|
|
||||||
- jsaddle-webkit2gtk
|
|
||||||
- jsaddle-webkitgtk
|
- jsaddle-webkitgtk
|
||||||
- jsc
|
- jsc
|
||||||
- lambdacat
|
- lambdacat
|
||||||
- leksah
|
|
||||||
- manatee-all
|
- manatee-all
|
||||||
- manatee-browser
|
- manatee-browser
|
||||||
- manatee-reader
|
- manatee-reader
|
||||||
- markup-preview
|
- markup-preview
|
||||||
- nomyx-api
|
|
||||||
- nomyx-core
|
|
||||||
- nomyx-language
|
|
||||||
- nomyx-library
|
|
||||||
- nomyx-server
|
|
||||||
- passman-cli
|
|
||||||
- passman-core
|
|
||||||
- reflex-dom-colonnade
|
|
||||||
- reflex-dom-contrib
|
|
||||||
- reflex-dom-fragment-shader-canvas
|
|
||||||
- reflex-dom-helpers
|
|
||||||
- reflex-jsx
|
|
||||||
- sneathlane-haste
|
|
||||||
- spike
|
- spike
|
||||||
- tianbar
|
|
||||||
- trasa-reflex
|
|
||||||
- treersec
|
|
||||||
- wai-middleware-brotli
|
|
||||||
- web-browser-in-haskell
|
- web-browser-in-haskell
|
||||||
- webkit
|
- webkit
|
||||||
- webkitgtk3
|
- webkitgtk3
|
||||||
|
File diff suppressed because it is too large
Load Diff
4179
pkgs/development/haskell-modules/hackage-packages.nix
generated
4179
pkgs/development/haskell-modules/hackage-packages.nix
generated
File diff suppressed because it is too large
Load Diff
Loading…
x
Reference in New Issue
Block a user