diff --git a/maintainers/scripts/haskell/hydra-report.hs b/maintainers/scripts/haskell/hydra-report.hs new file mode 100755 index 00000000000..471447e60d5 --- /dev/null +++ b/maintainers/scripts/haskell/hydra-report.hs @@ -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 = ["
" <> summary <> " ", ""] <> content <> ["
", ""] + +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 () diff --git a/maintainers/scripts/haskell/mark-broken.sh b/maintainers/scripts/haskell/mark-broken.sh new file mode 100755 index 00000000000..ddf2b1243b1 --- /dev/null +++ b/maintainers/scripts/haskell/mark-broken.sh @@ -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 diff --git a/maintainers/scripts/haskell/regenerate-transitive-broken-packages.sh b/maintainers/scripts/haskell/regenerate-transitive-broken-packages.sh index ed03ef5eb6a..64ec998bf6b 100755 --- a/maintainers/scripts/haskell/regenerate-transitive-broken-packages.sh +++ b/maintainers/scripts/haskell/regenerate-transitive-broken-packages.sh @@ -1,3 +1,15 @@ #! /usr/bin/env nix-shell #! 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 diff --git a/maintainers/scripts/haskell/transitive-broken-packages.nix b/maintainers/scripts/haskell/transitive-broken-packages.nix index 3ddadea216f..d4ddaa95765 100644 --- a/maintainers/scripts/haskell/transitive-broken-packages.nix +++ b/maintainers/scripts/haskell/transitive-broken-packages.nix @@ -12,10 +12,5 @@ let (getEvaluating (nixpkgs { config.allowBroken = true; }).haskellPackages); 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} '' diff --git a/pkgs/applications/science/logic/tamarin-prover/default.nix b/pkgs/applications/science/logic/tamarin-prover/default.nix index d217e2b9b50..a77f2dbac44 100644 --- a/pkgs/applications/science/logic/tamarin-prover/default.nix +++ b/pkgs/applications/science/logic/tamarin-prover/default.nix @@ -92,4 +92,8 @@ mkDerivation (common "tamarin-prover" src // { tamarin-prover-term tamarin-prover-theory ]; + + # tamarin-prover 1.6 is incompatible with maude 3.1. + hydraPlatforms = lib.platforms.none; + broken = true; }) diff --git a/pkgs/development/haskell-modules/configuration-arm.nix b/pkgs/development/haskell-modules/configuration-arm.nix index bcbf3254053..af4893afe54 100644 --- a/pkgs/development/haskell-modules/configuration-arm.nix +++ b/pkgs/development/haskell-modules/configuration-arm.nix @@ -61,6 +61,7 @@ self: super: { hsakamai = dontCheck super.hsakamai; hsemail-ns = dontCheck super.hsemail-ns; openapi3 = dontCheck super.openapi3; + strict-writer = dontCheck super.strict-writer; # https://github.com/ekmett/half/issues/35 half = dontCheck super.half; diff --git a/pkgs/development/haskell-modules/configuration-common.nix b/pkgs/development/haskell-modules/configuration-common.nix index d8f5348f5ad..7668d854bb2 100644 --- a/pkgs/development/haskell-modules/configuration-common.nix +++ b/pkgs/development/haskell-modules/configuration-common.nix @@ -1037,9 +1037,6 @@ self: super: { # Has tasty < 1.2 requirement, but works just fine with 1.2 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 ats-format = overrideCabal super.ats-format (old : { preConfigure = "export HOME=$PWD"; @@ -1068,18 +1065,6 @@ self: super: { # https://github.com/erikd/hjsmin/issues/32 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 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. 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 <= 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 diff --git a/pkgs/development/haskell-modules/configuration-darwin.nix b/pkgs/development/haskell-modules/configuration-darwin.nix index 6768bc5d6b4..4f7a6a131d7 100644 --- a/pkgs/development/haskell-modules/configuration-darwin.nix +++ b/pkgs/development/haskell-modules/configuration-darwin.nix @@ -161,4 +161,11 @@ self: super: { ] ++ (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 ""); + }); + } diff --git a/pkgs/development/haskell-modules/configuration-ghc-head.nix b/pkgs/development/haskell-modules/configuration-ghc-head.nix index cbfd4b84b2f..2b136c6bf83 100644 --- a/pkgs/development/haskell-modules/configuration-ghc-head.nix +++ b/pkgs/development/haskell-modules/configuration-ghc-head.nix @@ -11,8 +11,7 @@ with haskellLib; self: super: { - # This compiler version needs llvm 6.x. - llvmPackages = pkgs.llvmPackages_6; + llvmPackages = pkgs.llvmPackages_10; # Disable GHC 8.7.x core libraries. array = null; diff --git a/pkgs/development/haskell-modules/configuration-hackage2nix/broken.yaml b/pkgs/development/haskell-modules/configuration-hackage2nix/broken.yaml index 52c18b3e43d..87fdeb4da2d 100644 --- a/pkgs/development/haskell-modules/configuration-hackage2nix/broken.yaml +++ b/pkgs/development/haskell-modules/configuration-hackage2nix/broken.yaml @@ -1,43 +1,28 @@ broken-packages: # These packages don't compile. - 3dmodels - - 4Blocks - - a50 - AAI - - abcBridge - abcnotation - abeson - abides - abnf - - AbortT-monadstf - - AbortT-mtl - AbortT-transformers - abstract-par-accelerate - abt - AC-BuildPlatform - - AC-EasyRaster-GTK - - AC-HalfInteger - - ac-machine - - ac-machine-conduit - - AC-MiniTest - - AC-Terminal - - AC-VanillaArray - - AC-Vector - - AC-Vector-Fancy - acc - - accelerate-arithmetic - accelerate-fftw - - accelerate-fourier - accelerate-llvm-native - accelerate-random - - accelerate-typelits - accelerate-utility - accentuateus - access-time - - access-token-provider + - AC-EasyRaster-GTK + - AC-HalfInteger - achille - acid-state-dist - acid-state-tls + - ac-machine - ACME - acme-all-monad - acme-comonad @@ -53,57 +38,38 @@ broken-packages: - acme-now - acme-numbersystem - acme-operators - - acme-php - acme-schoenfinkel - acme-strfry - acme-stringly-typed - acme-this - acme-zero - - acousticbrainz-client + - AC-MiniTest + - AC-Terminal - ActionKid - - activehs - activehs-base - activitypub - activitystreams-aeson - - actor - acts + - AC-VanillaArray + - AC-Vector - Adaptive - Adaptive-Blaisorblade - adaptive-containers - adaptive-tuple - adb - - addy - - adhoc-network - - adict - adjunction - adobe-swatch-exchange - - adp-multi - - adp-multi-monadiccp - ADPfusion - - ADPfusionForest - - ADPfusionSet + - adp-multi - adtrees - - advent-of-code-api - - Advgame - - Advise-me - - AERN-Basics - - AERN-Net - - AERN-Real - - AERN-Real-Double - - AERN-Real-Interval - - AERN-RnToRm - - AERN-RnToRm-Plot - aern2-mp - - aern2-real + - AERN-Basics - aeson-applicative - aeson-decode - aeson-diff-generic - - aeson-extra - aeson-filthy - aeson-flowtyped - - aeson-injector - aeson-match-qq - - aeson-native - aeson-options - aeson-prefix - aeson-schema @@ -117,145 +83,73 @@ broken-packages: - aeson-via - affection - affine-invariant-ensemble-mcmc - - afv - - ag-pictgen - Agata - agda-language-server - - agda-server - agda-snippets - - agda-snippets-hakyll - - agda-unused - - agentx - AGI + - ag-pictgen - AhoCorasick - aig - - aip - - air-th - airbrake - - airship - airtable-api - - aivika-distributed - - aivika-experiment-diagrams + - air-th - ajhc - AlanDeniseEricLauren - alerta - alex-prelude - alfred - alga - - algebra-checkers - algebra-dag - - algebra-driven-design - - algebra-sql - algebraic - algebraic-prelude - - algo-s - - algolia - - AlgoRhythm - AlgorithmW + - algo-s - align-text - - AlignmentAlgorithms - - Allure - ally-invest - - alms - - alpha - alphachar - alsa - - alsa-gui - alsa-midi - - alsa-pcm-tests - - alsa-seq-tests - altcomposition - alternative-extra - alternative-io - alto - alure - amazon-emailer - - amazon-emailer-client-snap - amazon-products - - amazonka-ec2 - - amazonka-s3-streaming - amby - AMI - - ampersand - amqp-conduit - - amqp-streamly - analyze - - analyze-client - anansi-pandoc - - anatomy - android - android-activity - android-lint-summary - - AndroidViewHierarchyImporter - angel - angle - Animas - animascii - animate - - animate-example - - animate-frames - - animate-preview - - animate-sdl2 - - annah - annotated-fix - - Annotations - anonymous-sums - - anonymous-sums-tests - - ansi-terminal-game - ansigraph - - antagonist - antfarm - - anticiv - antigate - antimirov - - antiope-athena - - antiope-contract - - antiope-core - - antiope-dynamodb - - antiope-es - - antiope-messages - antiope-optparse-applicative - - antiope-s3 - - antiope-shell - - antiope-sns - - antiope-sqs - antiquoter - antisplice - antlr-haskell - - antlrc - anydbm - aop-prelude - - aos-signature - aosd + - aos-signature - apart - apecs-stm - - apelsin - api-builder - api-rpc-factom - - api-rpc-pegnet - - api-tools - - api-yoti - - apiary - - apiary-authenticate - - apiary-clientsession - - apiary-cookie - - apiary-eventsource - - apiary-helics - - apiary-http-client - - apiary-logger - - apiary-memcached - - apiary-mongoDB - - apiary-persistent - - apiary-purescript - - apiary-redis - - apiary-session - - apiary-websockets - - apis - apns-http2 - - apotiki - - app-lens - appc - - ApplePush + - app-lens - AppleScript - applicative-fail - applicative-parsec @@ -265,276 +159,158 @@ broken-packages: - approveapi - approx - ApproxFun-hs - - arb-fft - arbb-vm - - arbor-datadog + - arb-fft - arbor-monad-counter - arbor-monad-logger - arbor-monad-metric - - arbor-monad-metric-datadog - arbor-postgres - - arch-hs - - arch-web - - archive-libarchive - archiver - archlinux - - archlinux-web - archnews - - arduino-copilot + - arch-web - arena - - arff - - arghwxhaskell - - argon - argon2 - argparser - arguedit - - ariadne - arion - - arithmetic-circuits - armada - - armor - arpa - arpack - - array-builder - - array-chunks - - array-forth - - array-list - - array-primops - arrayfire - - arraylist + - array-primops - ArrayRef + - arrowapply-utils - arrow-improve - arrow-list - - arrowapply-utils - arrowp - arrowp-qq - ArrowVHDL - artery - artifact - asap + - ascii85-conduit - ascii-flatten - ascii-string - - ascii-table - ascii-vector-avc - - ascii85-conduit - - asic - asil - asn - - ASN1 - asn1-codec - asn1-data - assert - assert4hs - assert4hs-core - - assert4hs-hspec - - assert4hs-tasty - assertions - asset-map - - assimp - assumpta - ast-monad - - ast-monad-json - astrds - - astview - async-combinators - async-dejafu + - asynchronous-exceptions - async-manager - async-timer - - asynchronous-exceptions - aterm-utils - - atlassian-connect-core - - atlassian-connect-descriptor - - atmos-dimensional-tf - atndapi - - atom-msp430 - atomic-modify - - atomic-primops-foreign - atomic-primops-vector + - atom-msp430 - atomo - - atp - atp-haskell - ats-pkg - ats-setup - ats-storable - attempt - attic-schedule - - atto-lisp - AttoBencode - - AttoJson + - atto-lisp - attomail - - attoparsec-enumerator - - attoparsec-ip - - attoparsec-iteratee - attoparsec-text - - attoparsec-text-enumerator - attoparsec-trans - - attoparsec-uri - attosplit - Attrac - - atuin - - audiovisual - augeas - augur - aur - aur-api - - aura - Aurochs - authenticate-ldap - authinfo-hs - - authoring - - AutoForms - autom - automata - autonix-deps - - autonix-deps-kf5 - autopack - avatar-generator - - avers - - avers-api - - avers-api-docs - - avers-server - avl-static - - AvlTree - avr-shake - - avro-piper - awesome-prelude - - awesomium - - awesomium-glut - awesomium-raw - aws-cloudfront-signer - - aws-configuration-tools - - aws-dynamodb-conduit - - aws-dynamodb-streams - aws-easy - aws-ec2 - aws-ec2-knownhosts - - aws-elastic-transcoder - aws-general - - aws-kinesis - - aws-kinesis-client - - aws-kinesis-reshard - - aws-lambda - - aws-lambda-haskell-runtime-wai - - aws-lambda-runtime - aws-larpi - - aws-mfa-credentials - aws-performance-tests - aws-route53 - - aws-sdk - aws-sdk-text-converter - - aws-sdk-xml-unordered - - aws-ses-easy - - aws-sign4 - aws-simple - - aws-sns - axel - - axiom - - azimuth-hs - azubi - azure-acs - azure-email - - azure-functions-worker - - azure-service-api - - azure-servicebus - azurify - - b-tree - b9 - - babylon - - backblaze-b2-hs - - backdropper - backstop - backtracking-exceptions - backward-state - bag - Baggins - bake - - ballast - - bamboo - - bamboo-launcher - - bamboo-plugin-highlight - - bamboo-plugin-photo - - bamboo-theme-blueprint - - bamboo-theme-mini-html5 - - bamse - - bamstats - - ban-instance - Bang + - ban-instance - bank-holiday-usa - banwords - barchart - barcodes-code128 - barecheck - - Barracuda - barrie - barrier - barrier-monad + - base16 + - base64-conduit - base-compat-migrate - base-encoding - base-feature-macros - base-generics - base-io-access - - base16 - - base16-lens - - base32-bytestring - - base62 - - base64-bytes - - base64-conduit - - baserock-schema - basex-client - - BASIC - basic - basic-sop - baskell - - batchd - battlenet - - battlenet-yesod - - battleplace - - battleplace-api - battleship-combinatorics - - battleships - - bayes-stack - bazel-coverage-report-renderer - - bbi - BCMtools - - bcp47 - - bcp47-orphans - - bdcs - - bdcs-api - bdd - bdo - beam - - beam-automigrate - - beam-core - - beam-migrate - - beam-mysql - - beam-newtype-field - - beam-postgres - - beam-sqlite - - beam-th - beamable - - beautifHOL + - beam-core - bech32 - - bech32-th - bed-and-breakfast - beeminder-api - Befunge93 - - bein - - belka - - bench-graph - - bench-show - BenchmarkHistory + - bench-show - bencodex - berkeleydb - BerkeleyDBXML - - BerlekampAlgorithm - - berp - bert - besout - bet - betacode - betris - - bff - - bglib - bgmax - bgzf - bhoogle @@ -545,29 +321,17 @@ broken-packages: - bidispec - bidispec-extras - BiGUL - - billboard-parser - - billeksah-forms - - billeksah-main - - billeksah-pane - billeksah-services - binary-bits - binary-communicator - binary-derive - binary-ext - - binary-file - binary-indexed-tree - binary-protocol - - binary-protocol-zmq - - binary-streams - - binary-tagged - binary-typed - - bind-marshal - BinderAnn - - binding-core - binding-gtk - - binding-wx - bindings-apr - - bindings-apr-util - bindings-bfd - bindings-cctools - bindings-common @@ -581,6 +345,7 @@ broken-packages: - bindings-hamlib - bindings-hdf5 - bindings-K8055 + - bindings-levmar - bindings-libftdi - bindings-libg15 - bindings-libpci @@ -588,189 +353,88 @@ broken-packages: - bindings-libstemmer - bindings-libusb - bindings-libv4l2 - - bindings-linux-videodev2 - bindings-monetdb-mapi - bindings-mpdecimal - - bindings-ppdev - bindings-sc3 - bindings-sipc - bindings-wlc + - bind-marshal - bindynamic - binembed - - binembed-example - bio - - bio-sequence - - bioace - - bioalign - - Biobase - - BiobaseBlast - - BiobaseDotP - - BiobaseENA - - BiobaseEnsembl - - BiobaseFasta - - BiobaseFR3D - - BiobaseHTTP - - BiobaseHTTPTools - - BiobaseInfernal - - BiobaseMAF - BiobaseNewick - - BiobaseTrainingData - - BiobaseTurner - - BiobaseTypes - - BiobaseVienna - - BiobaseXNA - biocore - - biofasta - - biofastq - biohazard - - BioHMM - - bioinformatics-toolkit - - biophd - - biopsl - - biosff - - biostockholm - - bip32 - - birch-beer - - bird - - BirdPP + - bio-sequence - birds-of-paradise - bisect-binary - bishbosh - - bit-array - - bit-stream - - bitcoin-address - - bitcoin-api - - bitcoin-api-extra - - bitcoin-block - - bitcoin-compact-filters - bitcoin-hs - - bitcoin-keys - - bitcoin-rpc - bitcoin-script - - bitcoin-scripting - - bitcoin-tx - - bitcoin-types - - bitcoind-regtest - - bitcoind-rpc - - Bitly - - bitly-cli - - bitmaps - bits-atomic - bits-conduit - - bits-extras - bitset + - bits-extras - bitspeak + - bit-stream - BitStringRandomMonad - - BitSyntax - - bittorrent - - bitwise-enum - bitx-bitcoin - - bizzlelude - bizzlelude-js - bkr - - bla - blakesum - - blakesum-demo - blas - - BlastHTTP - - blastxml - - blatex - - blaze-builder-enumerator - - blaze-colonnade - blaze-html-contrib - blaze-html-hexpat - blaze-html-truncate - blaze-json - - blaze-textual-native - blazeT - - ble - - blink1 - - blip + - blaze-textual-native - bliplib - - Blobs - blockchain - blockhash - Blogdown - - blogination - - BlogLiterately - - BlogLiterately-diagrams - bloodhound - - bloodhound-amazonka-auth - bloomfilter-redis - blosum - - bloxorz - - blubber - blubber-server - Blueprint - - bluetile - bluetileutils - blunk-hask-tests - - blunt - - bno055-haskell - bogocopy - - bogre-banana - boilerplate - bolt - boltzmann-brain - bond - - bond-haskell - - bond-haskell-compiler - bookkeeper - - bookkeeper-permissions - - Bookshelf - boolean-normal-forms - boolexpr - boombox - - boomslang - - boopadoop - boots-app - - boots-cloud - - boots-web - - borel - boring-window-switcher - bot - botpp - bottom - - bound-extras - bounded-array - - bowntz - - box - - box-csv - - box-socket + - bound-extras - braid - brain-bleep - Bravo - - breakout - - breve - brians-brain - brick-dropdownmenu - - bricks - bricks-internal - - bricks-internal-test - - bricks-parsec - - bricks-rendering - - bricks-syntax - brillig - broccoli - brok - broker-haskell - bronyradiogermany-common - - bronyradiogermany-streaming - brotli - - brotli-conduit - - brotli-streams - browscap - bsd-sysctl - - bson - bson-generic - bson-generics - - bson-lens - bsparse - - btree - btree-concurrent - - buchhaltung - buffer - - buffer-builder - buffer-builder-aeson - BufferedSocket - buffet @@ -780,61 +444,39 @@ broken-packages: - build - buildable - buildbox - - buildbox-tools - builder - - buildwrapper - bullet - - bulletproofs - - bulmex - bumper - bunz - - burnt-explorer - burst-detection - - bus-pirate - - Buster - buster - - buster-gtk - - buster-network + - Buster - butter - - butterflies - bv-sized - - byline - bytable - bytearray-parsing - - bytebuild - - bytehash - - bytelog - - byteslice - - bytesmith - bytestring-arbitrary - bytestring-builder-varword - bytestring-class - bytestring-csv + - bytestringparser + - bytestringparser-temporary - bytestring-plain - - bytestring-read + - bytestringreadp - bytestring-rematch - bytestring-show - bytestring-substring - bytestring-time - bytestring-trie - bytestring-typenats - - bytestringparser - - bytestringparser-temporary - - bytestringreadp - - c-dsl - - c-io - - c-mosquitto - - c0check - c0parser - c10k - c2ats - - cab - - cabal-appimage + - cabal2doap + - cabal2ebuild + - cabal2ghci - cabal-audit - - cabal-bounds - cabal-bundle-clib - - cabal-cache - - cabal-cargs - cabal-constraints - cabal-db - cabal-dependency-licenses @@ -844,416 +486,247 @@ broken-packages: - cabal-file-th - cabal-ghc-dynflags - cabal-ghci + - cabalgraph - cabal-graphdeps - Cabal-ide-backend - cabal-info - cabal-install-bundle - cabal-install-ghc72 - cabal-install-ghc74 + - cabalish - cabal-lenses - cabal-meta - cabal-mon - cabal-nirvana - cabal-progdeps - - cabal-query + - cabalQuery + - CabalSearch - cabal-setup - cabal-sort - cabal-src - - cabal-test - cabal-test-quickcheck - cabal-upload - - cabal2arch - - cabal2doap - - cabal2ebuild - - cabal2ghci - - cabalgraph - - cabalish - - cabalmdvrpm - - cabalQuery - - cabalrpmdeps - - CabalSearch - cabalvchk - cabin - cabocha - - cache-polysemy - cached + - cache-polysemy - caching - - caching-vault - cacophony - cafeteria-prelude - caffegraph - cairo-core - - cake - cake3 - - cakyrespa - - cal-layout - cal3d - - cal3d-examples - - cal3d-opengl - calamity - - calc - - calculator - - caldims - caledon - calenderweek - - call - call-alloy + - cal-layout - call-haskell-from-anything - - camfort - - campfire - - candid - canon - canonical-filepath - canonical-json - - canteven-http - canteven-listen-http - canteven-log - canteven-parsedate - cantor - - cao - - cap - Capabilities - capnp - capped-list - capri - - car-pool - caramia - carbonara - - carboncopy - - cardano-coin-selection - carettah - CarneadesDSL - - CarneadesIntoDung - carte - - cartel - Cartesian - casa-abbreviations-and-acronyms - - casadi-bindings - - casadi-bindings-control - - casadi-bindings-core - casadi-bindings-internal - - casadi-bindings-ipopt-interface - - casadi-bindings-snopt-interface - Cascade - cascading - caseof - - cases - - cash - - cassandra-cql - Cassava - cassava-conduit - cassava-records - cassette - - cassy - castle - - casui - catamorphism - Catana - catch-fd - - categorical-algebra - - category-extras - category-traced - catnplus - cautious-file - cautious-gen - cayene-lpp - cayley-client - - CBOR - - CC-delcont-alt + - CCA - CC-delcont-cxe - CC-delcont-exc - CC-delcont-ref - CC-delcont-ref-tf - - CCA - cci - ccnx - - cctools-workqueue + - c-dsl - cedict - cef - cef3-raw - - cef3-simple - - ceilometer-common - cellrenderer-cairo - - celtchar - cerberus - cereal-derive - - cereal-enumerator - cereal-ieee754 - - cereal-io-streams - cereal-plus - - cereal-streams - - certificate - cf - cfenv - - cfipu - - cflp - - cfopu - cg - cgen - cgi-utils - - cgrep - - chainweb-mining-client - - chakra - chalkboard - - chalkboard-viewer - character-cases - - charade - - chart-cli - - Chart-fltkhs + - charter - chart-histogram - Chart-simple - - chart-svg - - chart-svg-various - - chart-unit - - charter - chatty-text - chatwork - - cheapskate-terminal - - check-pvp - - Checked - checked + - Checked - checkmate - chell-quickcheck - - chessIO - - chevalier-common - - chiasma - - chiphunk - - chitauri - Chitra - choose - - choose-exe - chorale - - chorale-geo - chp - - chp-mtl - - chp-plus - chp-spec - - chp-transformers - - chr-core - - chr-lang - - chr-parse - ChristmasTree - - chromatin - chronograph - - chronos-bench - - chu2 - - chunks + - chr-parse - chunky - church - church-maybe - - churros - cielo - cil - cinvoke + - c-io - cio - cipher-blowfish - - ciphersaber2 - circlehs - circular - - citation-resolve - citeproc-hs - - citeproc-hs-pandoc-filter - - cj-token - cjk - - cl3 - - cl3-hmatrix-interface - - cl3-linear-interface - - clac - - clafer - - claferIG - - claferwiki + - cj-token - clang-compilation-database - clang-pure - clanki - clarifai - CLASE - - clash - - clash-ghc - - clash-lib - - clash-multisignal - clash-prelude - Clash-Royale-Hack-Cheats - - clash-systemverilog - - clash-verilog - - clash-vhdl - - classify-frog - ClassLaws - classy-influxdb-simple - - classy-miso - classy-parallel - classyplate - ClassyPrelude - - clckwrks - - clckwrks-cli - - clckwrks-dot-com - - clckwrks-plugin-bugs - - clckwrks-plugin-ircbot - - clckwrks-plugin-mailinglist - - clckwrks-plugin-media - - clckwrks-plugin-page - - clckwrks-plugin-redirect - - clckwrks-theme-bootstrap - - clckwrks-theme-clckwrks - - clckwrks-theme-geo-bootstrap - cld2 - Clean - clean-unions - - cless - clevercss - clexer - CLI - cli-builder - - cli-extras - - cli-git - - cli-nix - clickhouse-haskell - clif - - clifford - clifm - clingo - clippard - clipper - - clippings - clisparkline - clit - - clocked - clogparse - clone-all - closure - - cloud-haskell - - cloud-seeder - cloudfront-signer - clr-inline - - clua - cluss - - ClustalParser - clustering - - clustertools - - clutterhs - cmark-highlight - cmark-patterns - cmark-sections - cmath - - cmathml3 - - CMCompare - cmd-item - cmdlib - cmdtheline - cmf - cmonad + - c-mosquitto - cmph - - cmptype - CMQ - cmt - - cmv - - cnc-spec-compiler - - co-log-polysemy - - co-log-polysemy-formatting - - co-log-sys - - Coadjute - coalpit - cobot-io - cobot-tools - code-builder - - codec - codec-beam - codec-libevent - - codec-rpm - codecov-haskell - - codemonitor - codepad - codeworld-api - codex - codo-notation - - coercible-utils - coin - - coinbase-exchange - coinbase-pro - coincident-root-loci - - colada - colchis - collada-output - - collapse-duplication - collapse-util - - collection-json - collections - collections-api - - collections-base-instances + - co-log-polysemy + - co-log-sys - colonnade - - color-counter - colorless - - colorless-http-client - - colorless-scotty - - colour-space - coltrane - - columbia - - columnar - com - comark-syntax - - combinat - combinat-diagrams - - combinator-interactive - combinatorial-problems - - Combinatorrent + - combinator-interactive - combobuffer - - comic - Command - commander - Commando - commodities - commsec - - commsec-keyexchange - - ComonadSheet + - compactable + - Compactable - compact-list - compact-map - - compact-mutable - compact-mutable-vector - compact-socket - compact-string - compact-string-fix - - compact-word-vectors - - Compactable - - compactable - - compdata - - compdata-automata - compdata-dags - compdata-param - - compendium-client - competition - compilation - complex-generic - - complexity - compose-trans - composite-opaleye - - composite-swagger - composition-tree - comprehensions-ghc - compressed - compstrat - comptrans - - computational-algebra - computational-geometry - computations - ConClusion - - concraft - - concraft-hr - - concraft-pl - - concrete-haskell - - concrete-haskell-autogen - concrete-relaxng-parser - concrete-typerep - - concurrency-benchmarks - concurrent-buffer - Concurrent-Cache - - concurrent-machines - - concurrent-state - Concurrential - - Condor - - condor + - concurrent-state - condorcet - conductive-base - - conductive-hsc3 - - conductive-song - conduit-audio-lame - conduit-audio-samplerate - conduit-find @@ -1263,309 +736,190 @@ broken-packages: - conduit-throttle - conduit-tokenize-attoparsec - conduit-vfs - - conduit-vfs-zip - conf - - confcrypt - - conferer-dhall - - conferer-provider-dhall - conferer-provider-json - - conferer-provider-yaml - conferer-snap - - conferer-source-dhall - conferer-source-json - - conferer-source-yaml - - conffmt - confide - - config-parser - - config-select - - config-value-getopt - ConfigFileTH - - Configger - - configifier + - config-parser - Configurable - configuration - - configurator-ng + - config-value-getopt - confsolve - congruence-relation - conjure - conkin - conlogger - connection-string - - connections - Conscript - consistent - console-program - const-math-ghc-plugin - - constr-eq - constrained-categories - constrained-category - constrained-dynamic - constrained-monads - - constraint-manip - ConstraintKinds - constraints-emerge - - constructible + - constr-eq - constructive-algebra - consul-haskell - Consumer - - consumers - - container - containers-benchmark - containers-verified - ContArrow - content-store + - ContextAlgebra - context-free-grammar - context-stack - - ContextAlgebra - - contiguous - contiguous-checked - - contiguous-fft - continue - - continuum - - continuum-client - Contract - - control - control-iso - - control-monad-attempt - - control-monad-exception-monadsfd - control-monad-failure - control-monad-failure-mtl - - Control-Monad-MultiPass - Control-Monad-ST2 - contstuff-monads-tf - contstuff-transformers - - conversions - - convert - convert-annotation - - convertible-ascii - - convertible-text - - cookies - - coordinate - - copilot - - copilot-c99 - - copilot-cbmc - - copilot-language - - copilot-libraries - copilot-sbv - - copilot-theorem - copr - COrdering - core - - core-haskell - corebot-bliki - CoreDump - CoreErlang - - CoreFoundation - - corenlp-parser + - core-haskell - Coroutine - - coroutine-enumerator - - coroutine-iteratee - coroutine-object - - couch-hs - CouchDB - couchdb-conduit - - couchdb-enumerator - - countable-inflections + - couch-hs - counter - - country-codes - courier - court - coverage - cparsing - - CPBrainfuck - cpio-conduit - - cpkg - - CPL - cplusplus-th - - cprng-aes-effect - cpuperf - cpython - cql-io - - cql-io-tinylog - cqrs-core - - cqrs-example - - cqrs-memory - - cqrs-postgresql - - cqrs-sqlite3 - - cqrs-test - - cqrs-testkit - cr - crack - - craft - Craft3e - craftwerk - - craftwerk-cairo - - craftwerk-gtk - crawlchain - - craze - crc - crc16 - - crdt - crdt-event-fold - creatur - credential-store - - crf-chain1 - - crf-chain1-constrained - - crf-chain2-generic - - crf-chain2-tiers - critbit - - criterion-cmp - criterion-compare - criterion-plus - criterion-to-html - - criu-rpc - criu-rpc-types - crjdt-haskell - - crockford - crocodile - - cron-compat - cruncher-types - crunghc - - crypt-sha512 - crypto-cipher-benchmarks - crypto-classical - - crypto-conduit + - cryptocompare + - cryptoconditions + - cryptoids-types - crypto-keys-ssh - crypto-multihash - crypto-pubkey-openssh - crypto-random-effect - crypto-simple - - cryptocipher - - cryptocompare - - cryptoconditions - - cryptoids - - cryptoids-class - - cryptoids-types - - cryptol - cryptsy-api - - crystalfontz - cse-ghc-plugin - - csg - - CSPM-cspm - CSPM-FiringRules - CSPM-Frontend - - CSPM-Interpreter - - CSPM-ToProlog - - cspmchecker - cspretty - css - css-easings - css-selectors - - csv-enumerator - csv-nptools - ctemplate - ctkl - - ctpl - - cube - cubical - cuboid - cuckoo - curl-runnings - - currency-codes - currency-convert - - curry-frontend - CurryDB - curryer-rpc - - cursedcsv - - cursor-fuzzy-time-gen + - curry-frontend - curves - custom-prelude - CV - - cv-combinators - - cypher - - d-bus - d3js - dag - DAG-Tournament - damnpacket - - Dangerous - danibot - - Dao - dao - - dapi - - darcs-benchmark - - darcs-beta + - Dao + - darcs2dot - darcs-buildpackage - darcs-cabalized - - darcs-fastconvert - darcs-graph - darcs-monitor - - darcs2dot - - darcsden - - DarcsHelpers - - darcswatch - - darkplaces-demo - darkplaces-rcon - - darkplaces-rcon-util - darkplaces-text - - dash-haskell - - data-accessor-monads-fd - data-accessor-monads-tf - data-aviary - data-base - - data-basic + - database-id-groundhog + - database-study - data-check - data-combinator-gen - data-concurrent-queue - data-construction - - data-cycle - data-dispersal - data-diverse-lens + - datadog - data-easy - - data-elf - data-embed - data-emoticons - data-filepath - data-fin - data-fin-simple + - datafix - data-flagset - - data-interval - data-ivar - data-kiln - - data-layer - data-lens - - data-lens-fd - - data-lens-ixset - - data-lens-template + - datalog - data-map-multikey - data-nat - data-object - - data-object-json - - data-object-yaml + - datapacker - data-pprint - data-quotientref - - data-r-tree - data-reify-cse - data-repr - - data-result - data-rev - - Data-Rope - data-rope - - data-rtuple + - Data-Rope + - data-r-tree - data-size - data-spacepart - data-standards - data-store - data-stringmap - - data-structure-inferrer - data-sword + - DataTreeView - data-type - data-util - data-validation - data-variant - - database-id-groundhog - - database-study - - datadog - - datadog-tracing - - datafix - - dataflow - - datalog - - datapacker - - datasets - - DataTreeView - - dataurl - DataVersion - - date-conversions - dates - datetime - datetime-sb @@ -1574,137 +928,77 @@ broken-packages: - dbcleaner - dbf - DBFunctor - - dbjava - DBlimited - dbm - dbmigrations-mysql - dbmigrations-postgresql - dbmigrations-sqlite + - d-bus - DBus - - dbus-client - dbus-core - dbus-qq - dclabel - dclabel-eci11 - dcpu16 - - ddate - ddc-base - - ddc-build - ddc-code - - ddc-core - - ddc-core-babel - - ddc-core-eval - - ddc-core-flow - - ddc-core-llvm - - ddc-core-salt - - ddc-core-simpl - - ddc-core-tetra - - ddc-driver - - ddc-interface - - ddc-source-tetra - - ddc-tools - - ddc-war - - ddci-core - dead-code-detection - - dead-simple-json - Deadpan-DDP - - debug + - dead-simple-json - debug-me - - debug-trace-var - debug-tracy - decepticons - - decidable - - decimal-arithmetic - decimal-literals - DecisionTree - decoder-conduit - - dedukti - - deep-transformations - - DeepArrow - deepcontrol - DeepDarkFantasy - - deeplearning-hs - deepseq-bounded - deepseq-magic - deepseq-th - - deepzoom - - defargs - - DefendTheKing + - deep-transformations - deka - - deka-tests - - delaunay - - delicious - - delimited-text - - delimiter-separated - - delta - - delta-h - Delta-Lambda - delude - demarcate - denominate - - dense - dense-int-set - - dep-t - - dep-t-advice - dependent-hashmap - dependent-monoidal-map - - dependent-state - depends - - dephd + - dep-t - deptrack-core - - deptrack-devops - - deptrack-dot - - dequeue - derangement - derivation-trees - derive - derive-enumerable - derive-gadt - - derive-IG - derive-monoid - derive-trie - derp-lib - describe - descript-lang - deterministic-game-engine - - detour-via-uom - deunicode - devil - - devtools - - dewdrop - - dfinity-radix-tree - Dflow - dfsbuild - dgim - dgs - dhall-check - - dhall-docs - dhall-fly - - dhall-nix - - dhall-nixpkgs - - dhall-recursive-adt - dhall-text - dhall-to-cabal - - dhcp-lease-parser - dhrun - dia-base - - dia-functions - diagrams-boolean - - diagrams-braille - - diagrams-builder - diagrams-canvas - diagrams-graphviz - diagrams-gtk - - diagrams-haddock - - diagrams-html5 - - diagrams-pandoc - diagrams-pdf - - diagrams-pgf - diagrams-qrcode - diagrams-rasterific - - diagrams-rubiks-cube - diagrams-tikz - - diagrams-wx - dib - dice2tex - dicom @@ -1713,8 +1007,6 @@ broken-packages: - diet - diff - diffcabal - - difference-monoid - - DifferenceLogic - differential - DifferentialEvolution - diffmap @@ -1723,36 +1015,24 @@ broken-packages: - digestive-foundation-lucid - digestive-functors-aeson - digestive-functors-happstack - - digestive-functors-hsp + - digest-pure - DigitalOcean - digitalocean-kzs - digits - - dimensional-codata - - dimensional-tf - DimensionalHash - - dingo-core - - dingo-example - - dingo-widgets + - dimensional-tf - diohsc - diophantine - - diplomacy - - diplomacy-server - direct-binary-files + - directed-cubical - direct-fastcgi - direct-http + - directory-contents - direct-plugins - direct-rocksdb - - directed-cubical - - directory-contents - direm - - dirfiles - - discogs-haskell - - discord-gateway - - discord-hs - - discord-register - - discord-rest - - discord-types - discordian-calendar + - discord-types - discrete - DiscussionSupportSystem - Dish @@ -1760,48 +1040,19 @@ broken-packages: - disjoint-set - disjoint-set-stateful - Dist - - dist-upload - distance - - DisTract - distributed-fork-aws-lambda - distributed-process - - distributed-process-async - - distributed-process-azure - - distributed-process-client-server - - distributed-process-ekg - - distributed-process-execution - - distributed-process-extras - - distributed-process-fsm - - distributed-process-lifted - - distributed-process-monad-control - - distributed-process-p2p - - distributed-process-platform - - distributed-process-registry - - distributed-process-simplelocalnet - - distributed-process-supervisor - - distributed-process-systest - - distributed-process-task - - distributed-process-tests - - distributed-process-zookeeper - distribution - - distribution-plot - - diversity - - dixi + - dist-upload - djembe - djinn-th - - dl-fedora - dmcc - dmenu - - dmenu-pkill - - dmenu-pmount - - dmenu-search - - DMuCheck - - DnaProteinAlignment - dnscache - dnsrbl - dnssd - dobutok - - doc-review - doccheck - docidx - docker @@ -1810,37 +1061,18 @@ broken-packages: - dockerfile-creator - docopt - docrecords - - DocTest - doctest-discover-configurator - doctest-prop - - docusign-base - - docusign-base-minimal - - docusign-client - docusign-example - docvim - - doi - - DOM - - domain - - domain-core - - domain-optics - domplate - - dot-linker - dotfs + - dot-linker - doublify-toolkit - - dow - - download-media-content - downloader - dozenal - dozens - - DP - dph-base - - dph-examples - - dph-lifted-base - - dph-lifted-copy - - dph-lifted-vseg - - dph-prim-interface - - dph-prim-par - - dph-prim-seq - dpkg - DPM - dpor @@ -1848,65 +1080,44 @@ broken-packages: - drawille - drClickOn - dresdner-verkehrsbetriebe - - DrHylo - DrIFT - DrIFT-cabalized - - drifter - drifter-postgresql - - drifter-sqlite - drmaa - drone - - dropbox - - dropbox-sdk - - dropsolve - - ds-kanren - DSA - dsc - - DSH - - dsh-sql + - ds-kanren - dsmc - - dsmc-tools - dson - dson-parsec - - DSTM - dstring - DTC - - dtd - dtd-text - dtw - dualizer - duet - - dumb-cas - dump-core - dunai-core - Dung - duplo - dura - - Dust - Dust-crypto - - Dust-tools - - Dust-tools-pcap - dvault - - dvda - dvdread - dvi-processing - dwarf - dwarfadt - dyckword - dyepack - - dynamic-cabal - dynamic-graphs - dynamic-mvector - dynamic-object - - dynamic-plot - dynamic-pp - DynamicTimeWarp - dynamodb-simple - dynloader - - dynobud - DysFRP - - DysFRP-Cairo - - DysFRP-Craftwerk - dywapitchtrack - dzen-dhall - dzen-utils @@ -1917,78 +1128,50 @@ broken-packages: - easy-bitcoin - easyjson - easyplot - - easytensor - - easytensor-vulkan - easytest - ebeats - ebnf-bff - - ec2-unikernel - eccrypto - - eccrypto-ed25519-bindings - ecma262 - ecu - eddie - ede - edenmodules - - edenskel - - edentv - - edge - - edges - edis - edit - edit-lenses - - editable - editline - - EditTimeReport - effect-handlers - effect-monad - effect-stack - effin - - egison - egison-pattern-src - - egison-pattern-src-haskell-mode - - egison-pattern-src-th-mode - - egison-quote - - egison-tutorial - ehaskell - ehs - eibd-client-simple - eigen - Eight-Ball-Pool-Hack-Cheats - eio - - either-list-functions - - either-unwrap - EitherT + - either-unwrap - ejdb2-binding - ekg-bosun - ekg-carbon - - ekg-cloudwatch - ekg-elastic - ekg-elasticsearch - ekg-log - ekg-push - ekg-rrd - ekg-wai - - elerea-examples - elevator - elision - - elliptic-curve - elm-street - elm-websocket - - elsa - - elynx - - elynx-tree - - emacs-keys - emacs-module - - email + - emailaddress - email-header - email-postmark - - emailaddress - - emailparse - - embeddock - - embeddock-example - embla - - embroidery - emgm - Emping - Empty @@ -1997,33 +1180,20 @@ broken-packages: - encoding - encoding-io - encryptable - - engine-io - - engine-io-growler - engine-io-snap - engine-io-wai - engine-io-yesod - - entangle - - EntrezHTTP - entwine - - enum-text - - enum-text-rio - - enum-utf8 - EnumContainers - - enumerate - - enumerate-function - enumerator - - enumerator-fd - - enumerator-tf - enumfun - EnumMap - enummapmap - - env-extra + - enum-utf8 - env-parser - envstatus - epanet-haskell - epass - - ephemeral - - epi-sim - epic - epoll - eprocess @@ -2032,77 +1202,47 @@ broken-packages: - EqualitySolver - equational-reasoning-induction - equeue - - erf-native - erlang - erlang-ffi - eros - - eros-client - - eros-http - - error-codes + - errata - error-context - error-continuations - error-list - error-loc - - error-message - error-util - - errors-ext - ersaconcat - ersatz - - ersatz-toysat - ert - escape-artist - escoger - - esotericbot - - EsounD - espial - ess - estimators - EstProgress - - estreps - Etage - - Etage-Graph - - EtaMOO - eternal - - Eternal10Seconds - - eternity - - eternity-timestamped - - ether - - Etherbunny - - ethereum-analyzer - - ethereum-analyzer-cli - - ethereum-analyzer-webui - - ethereum-client-haskell - - ethereum-merkle-patricia-db - ethereum-rlp - euphoria - eurofxref - evdev - - evdev-streamly - eve-cli - event - event-driven - - event-monad - eventful-dynamodb - - eventful-postgresql - eventful-sql-common - - eventful-sqlite - eventlog2html - eventloop - - EventSocket - - eventsource-geteventstore-store - eventstore - - every-bit-counts - ewe - exact-cover - exact-real-positional - except-exceptions - - exception-monads-fd - exceptional - exceptionfree-readfile - exchangerates - execs - executor - - exference - exh - exherbo-cabal - exif @@ -2112,172 +1252,98 @@ broken-packages: - exists - exitcode - exp-extended - - expand - - expat-enumerator - - expiring-containers - explain - explicit-constraint-lens - explicit-determinant - explicit-iomodes - - explicit-iomodes-bytestring - - explicit-iomodes-text - - explicit-sharing - - explore - exposed-containers - expression-parser - expressions - - expressions-z3 - expresso - extcore - - extemp - extended-categories - - extensible-data - extensible-effects-concurrent - extensible-skeleton - external-sort - Extra - - extract-dependencies - extractelf - extralife - - ez-couch - ez3 - - f-algebra-gen - - f-ree-hack-cheats-free-v-bucks-generator + - ez-couch - Facebook-Password-Hacker-Online-Latest-Version - faceted - - factory - - Facts - facts - - factual-api - - fadno - - fadno-braids - - fadno-xml - failable-list - failure-detector - - FailureT - - fake - fake-type - faktory - - falling-turnip - - fallingblocks - - family-tree - - fast-arithmetic - - fast-combinatorics - - fast-digits - - fast-nats - - fasta + - f-algebra-gen - fastbayes + - fast-combinatorics - fastedit - - fastirc - fastly + - fast-nats - fastpbkdf2 - FastPush - - fastsum - FastxPipe - fathead-util - - fault-tree - fay-builder - fay-hsx - fay-simplejson - - fb-persistent - fbmessenger-api - - fbrnch + - fb-persistent - fca - fcache - - fcd - - fcf-containers - fcg - fckeditor - fclabels-monadlib - fcm-client - - FComp - fdo-trash - feature-flipper - - feature-flipper-postgres - - fedora-img-dl - fedora-packages - feed-cli - feed-collect - feed-crawl - - feed-gipeda - - feed-translator - - feed2lj - - feed2twitter - - fei-base - - fei-cocoapi - - fei-dataiter - - fei-datasets - - fei-examples - - fei-modelzoo - - fei-nn - - feldspar-compiler - - feldspar-language - fenfire - - FermatsLastMargin - fernet - FerryCore - - festung - Feval - fez-conf - ffeed - fficxx - - ffmpeg-tutorials - ffunctor - fgl-extras-decompositions - fibon - - ficketed - - fields - - FieldTrip - fieldwise - fig - file-collection - file-command-qq + - filediff - file-embed-poly - file-location - - filecache - - filediff - FileManip - FileManipCompat - fileneglect - - filepath-crypto - - filepath-io-access - - FilePather - - filepather - - fileplow - Files - FileSystem - filesystem-abstractions - filesystem-conduit - - filesystem-enumerator - filesystem-trees - fillit - - Fin - final-pretty-printer - Finance-Quote-Yahoo - - Finance-Treasury - - find-clumpiness - find-conduit - find-source-files - - findhttp - fingertree-psqueue - fingertree-tf - finitary-derive - - FiniteMap - firefly-example - first-and-last - first-class-instances - - firstify - - FirstOrderTheory - - fishfood - fit - - fits-parse - fitsio - - fix-imports - - fix-parser-simple - - fix-symbols-gitit + - fits-parse - fixed-point - - fixed-point-vector - - fixed-point-vector-space - fixed-precision - fixed-storable-array - fixed-timestep @@ -2287,124 +1353,75 @@ broken-packages: - fixed-width - fixer - fixfile - - fixhs - fixie + - fix-symbols-gitit - fizzbuzz - fizzbuzz-as-a-service - flac - - flac-picture - flaccuraterip - flamethrower - flamingra - - flashblast - flat-maybe - - flatbuffers - flay - flexible-time - - flexiwrap - - flexiwrap-smallcheck - flickr + - flight-kml - flink-statefulfun - - Flippi - - flite - float-binstring - floating-bits - - flow-er - flowdock - - flowdock-api - flowdock-rest - - flower + - flow-er - flowlocks-framework - - flowsim - flp - fltkhs - - fltkhs-fluid-examples - - fluent-logger - fluffy-parser - fluidsynth - flux-monoid - - FM-SBLEX - fmark - FModExRaw - - fmt-for-rio - - fmt-terminal-colors - fn-extra - foldl-incremental - foldl-statistics - foldl-transduce - - foldl-transduce-attoparsec - folds-common - follow - - follower - - foma - font-opengl-basic4x6 - - foo - - for-free - forbidden-fruit - fordo - forecast-io - foreign-var - forest - forest-fire - - Forestry - forex2ledger + - for-free - forger - ForkableT - - formal - - FormalGrammars - - format - - format-status - formatn - formattable - - forml - - formlets - - formlets-hsp - formura - ForSyDe - forsyde-deep - - forth-hll - Fortnite-Hack-Cheats-Free-V-Bucks-Generator - fortran-src - - fortran-src-extras - fortytwo - - foscam-directory - foscam-filename - - foscam-sort - - Foster - - fp-ieee - fpco-api - - fplll - - fpnla-examples - FPretty - fptest - Fractaler - fractals - fraction - frag - - frame-markdown - - Frames-beam - - Frames-dsv - Frames-map-reduce - franchise - - Frank - fraxl - freddy - - free-algebras - - free-category - free-concurrent - free-game + - f-ree-hack-cheats-free-v-bucks-generator - free-http - free-operational - - free-theorems - - free-theorems-counterexamples - - free-theorems-seq - - free-theorems-seq-webui - - free-theorems-webui - - free-v-bucks-generator-no-survey - - free-v-bucks-generator-ps4-no-survey - - freekick2 - - freelude - - freer-converse - freer-effects - freer-simple-catching - freer-simple-http @@ -2413,21 +1430,19 @@ broken-packages: - freer-simple-time - freesect - freesound - - freetype-simple + - free-theorems - FreeTypeGL + - freetype-simple + - free-v-bucks-generator-no-survey + - free-v-bucks-generator-ps4-no-survey - freq - fresh - friday-devil - friday-scale-dct - friendly - - front - frown - frp-arduino - frpnow - - frpnow-gloss - - frpnow-gtk - - frpnow-gtk3 - - frpnow-vty - fs-events - fsh-csv - fsmActions @@ -2436,99 +1451,52 @@ broken-packages: - fswait - fswatch - ft-generator - - ftdi - FTGL-bytestring - ftp-client - - ftp-client-conduit - ftp-conduit - ftphs - - FTPLine - - ftree - - ftshell - full-sessions - - funbot - funbot-client - - funbot-git-hook - - funcons-lambda-cbv-mp - - funcons-simple - - funcons-tools - funcons-values - - function-combine - function-instances-algebra - - functional-arrow - functor - functor-combinators - - functor-combo - functor-friends - functor-infix + - functorm - functor-products - functor-utils - - functorm - funflow - - funflow-nix - Fungi - - funion - - funnyprint - funpat - - funsat - funspection - fused-effects-exceptions - fused-effects-resumable - - fused-effects-squeal - - fused-effects-th - fusion - futun - future - - fuzzy-time-gen - fuzzy-timings - fwgl - - fwgl-glfw - - fwgl-javascript - - fxpak - - g-npm - - g2 - - g2q - g4ip - - gact - - galois-fft - galois-field - - game-probability - gameclock + - game-probability - gamgee - - Gamgine - gamma - Ganymede - garepinoh - - gargoyle-postgresql-connect - gargoyle-postgresql-nix - gas - gather - - gbu - gc-monitoring-wai - gconf - - gdax - - gdiff-ig - gdiff-th - - GeBoP - - gedcom - - geek - - geek-server - gegl - gelatin - - gelatin-freetype2 - - gelatin-fruity - - gelatin-gl - - gelatin-sdl2 - - gelatin-shaders - - gemini-textboard - gemstone - - gen-imports - - gen-passwd - - Genbank - gencheck - gender - genders - - Gene-CluEDO - general-prelude - GeneralTicTacToe - generator @@ -2545,63 +1513,57 @@ broken-packages: - generic-optics - generic-override-aeson - generic-pretty + - genericserialize - generic-server + - generics-mrsop - generic-storable - generic-tree - generic-trie - generic-xml - generic-xmlpickler - - generics-mrsop - - generics-mrsop-gdiff - - genericserialize - - genesis - - genesis-test - genetics - - GenI - - geni-gui - - geni-util - - geniconvert + - gen-imports - geniplate - - geniserver + - gen-passwd - genprog - - GenSmsPdu - gentlemark - - GenussFold - genvalidity-persistent - - geo-resolver - GeocoderOpenCage - - geodetic - geodetic-types - geojson-types - - geolite-csv - geom2d - GeomPredicates-SSE + - geo-resolver - geos - Get - - getemx - getflag - GGg - ggtsTC - - gh-labeler - ghc-clippy-plugin - ghc-core-smallstep - ghc-datasize - - ghc-dump-core - ghc-dump-tree - - ghc-dump-util - ghc-dup - ghc-events-analyze - ghc-events-parallel - ghc-generic-instances - - ghc-imported-from - - ghc-instances + - ghci-diagrams + - ghci-haskeline + - ghci-history-parser + - ghci-lib + - ghci-ng + - ghcjs-dom-jsffi + - ghcjs-fetch + - ghcjs-promise + - ghcjs-xhr - ghc-justdoit + - ghclive - ghc-man-completion - - ghc-mod - ghc-parmake - ghc-pkg-autofix - ghc-pkg-lib - ghc-plugs-out + - ghcprofview - ghc-proofs - ghc-session - ghc-simple @@ -2609,390 +1571,192 @@ broken-packages: - ghc-syb - ghc-syb-utils - ghc-tags-core - - ghc-tags-plugin - ghc-time-alloc-prof - ghc-usage - - ghc-vis - - ghci-dap - - ghci-diagrams - - ghci-haskeline - - ghci-history-parser - - ghci-lib - - ghci-ng - - ghci-pretty - - ghcjs-dom-jsffi - - ghcjs-fetch - - ghcjs-hplay - - ghcjs-promise - - ghcjs-xhr - - ghclive - - ghcprofview - - ghcup - - ght - - gi-cairo-again + - gh-labeler + - giak + - Gifcurry - gi-graphene - - gi-gsk - - gi-gstaudio - - gi-gstpbutils - gi-gsttag - gi-gtkosxapplication - gi-gtksheet - gi-handy - - gi-poppler - - gi-vips - - gi-wnck - - giak - - Gifcurry - ginsu - gipeda - giphy-api - - GiST - gist + - GiST - git - git-all - git-checklist - git-config - git-cuk - git-date - - git-fmt - - git-gpush - - git-jump - - git-monitor - - git-object - - git-remote-ipfs - - git-repair - - git-sanity - - git-vogue - gitdo - github-backup - github-data - github-tools - github-utils - github-webhook-handler - - github-webhook-handler-snap - githud - gitignore + - git-jump - gitlab-api - - gitlib - gitlib-cmdline - - gitlib-cross - - gitlib-libgit2 - - gitlib-s3 - - gitlib-sample - - gitlib-test - gitlib-utils + - git-repair + - git-sanity - gitson - gitter - - givegif + - git-vogue + - gi-vips + - gi-wnck - glade - - gladexml-accessor - glapp - - glazier - - glazier-pipes - - glazier-react - - glazier-react-examples - - glazier-react-widget - Gleam - GLFW - GLFW-b-demo - - GLFW-OGL - - GLFW-task - gli - glider-nlp - GLMatrix - - glob-posix - - global - - global-config - global-variables - - glome-hs + - glob-posix - GlomeTrace - - GlomeView - - gloss-banana - - gloss-devil - - gloss-examples - gloss-export - gloss-game - - gloss-sodium - glpk-headers - - glpk-hs - gltf-codec - glue - - gmap - - gmndl - - gnome-desktop - - gnomevfs - - gnss-converters - - gnuidn + - g-npm - goa - goal-core - - goal-geometry - - goal-probability - - goal-simulation - - goatee - - goatee-gtk - gochan - godot-haskell - gofer-prelude - - goldplate - gooey - google-cloud - - google-drive + - GoogleCodeJam - google-html5-slide - - google-mail-filters - - google-maps-geocoding - google-oauth2 - google-oauth2-easy - - google-oauth2-jwt - - google-search - - google-server-api - - google-static-maps - - google-translate - - GoogleCodeJam - - GoogleDirections - - googleplus - googlepolyline - - GoogleSB - - GoogleTranslate + - google-search + - google-translate - gopherbot - gopro-plus - gore-and-ash - - gore-and-ash-actor - - gore-and-ash-async - - gore-and-ash-demo - - gore-and-ash-glfw - - gore-and-ash-lambdacube - - gore-and-ash-logging - - gore-and-ash-network - - gore-and-ash-sdl - - gore-and-ash-sync - GotoT-transformers - gpah - GPipe - - GPipe-Collada - GPipe-Core - - GPipe-Examples - - GPipe-GLFW - - GPipe-GLFW4 - - GPipe-TextureLoad - - gps - - gps2htmlReport - - GPX - gpx-conduit - grab - - grab-form - graceful - grafana - - graflog - Grafos - grakn - - grammar-combinators - - GrammarProducts - - grammatical-parsers - - grapefruit-examples - grapefruit-frp - - grapefruit-records - - grapefruit-ui - - grapefruit-ui-gtk - - graph-core - - graph-matchings - - graph-rewriting - - graph-rewriting-cl - - graph-rewriting-gl - - graph-rewriting-lambdascope - - graph-rewriting-layout - - graph-rewriting-ski - - graph-rewriting-strategies - - graph-rewriting-trs - - graph-rewriting-ww - - graph-serialize - - graph-utils - - graph-visit - Graph500 + - Graphalyze - graphbuilder - graphene - - GraphHammer - - GraphHammer-examples - graphics-drawingcombinators - graphics-formats-collada - - graphicsFormats - - graphicstools + - graph-matchings - graphmod-plugin - - graphql - graphql-api - - graphql-client - graphql-utils - graphql-w-persistent + - graph-rewriting + - graph-serialize - graphted - - graphtype - - graphula - graphula-core + - graph-utils - graql - grasp - gray-code - greencard - - greencard-lib - greg-client - gremlin-haskell - Grempa - grenade - - grid-proto - - gridbounds - - gridland - grm - groot - gross - GroteTrap - groundhog-converters - groundhog-mysql + - grouped-list - group-theory - group-with - - grouped-list - - groups-generic - growler - - GrowlNotify - grpc-api-etcd - - grpc-etcd-client - - grpc-haskell - - grpc-haskell-core - - gruff - - gruff-examples - - gscholar-rss - gsl-random - - gsl-random-fu - - gstorable - gstreamer - GTALib - - gtfs - gtfs-realtime - - gtk-serialized-event - - gtk-toy - gtk2hs-hello - gtk2hs-rpn - - Gtk2hsGenerics - gtk3-mac-integration - gtkglext - - GtkGLTV - - gtkimageview - - gtkrsync + - gtk-sni-tray - gtksourceview2 - gtksourceview3 - - GtkTV - - guarded-rewriting - - guess-combinator - - GuiHaskell - - GuiTV + - gtk-toy - gulcii - gw - gyah-bin - gym-http-api - - h-booru - - h-gpgme - - h-reversi - h2048 - h2c - haar - - habit - - hablo - - hablog - HABQT - - Hach - - hack-contrib - - hack-contrib-press - - hack-frontend-happstack - - hack-handler-cgi - - hack-handler-epoll - - hack-handler-evhttp - - hack-handler-fastcgi - - hack-handler-happstack - - hack-handler-hyena - - hack-handler-kibro - - hack-handler-simpleserver - - hack-middleware-cleanpath - - hack-middleware-clientsession - - hack-middleware-jsonp - - hack2-handler-happstack-server - - hack2-handler-mongrel2-http - - hack2-handler-snap-server - hack2-handler-warp + - hackage2hwn - hackage-api - hackage-diff - hackage-mirror - hackage-processing - hackage-proxy - - hackage-repo-tool - - hackage-server - - hackage-whatsnew - - hackage2hwn - - hackage2twitter - hackager + - hackage-repo-tool + - hackage-whatsnew - hackernews + - hack-frontend-happstack + - hack-handler-cgi + - hack-handler-happstack + - hack-handler-kibro - HackMail - - hackmanager - hackport - hactor - hactors - - haddock - haddock-api - haddock-cheatsheet - haddock-leksah - haddock-test - - haddocset - hadoop-formats - hadoop-rpc - - hadoop-tools - hafar - - haggis - Haggressive - hahp - haiji - hailgun-send - - hails-bin - hairy - hakaru - hakismet - hakka - hako - hakyll - - hakyll-agda - - hakyll-alectryon - - hakyll-blaze-templates - - hakyll-contrib - - hakyll-contrib-csv - - hakyll-contrib-elm - - hakyll-contrib-hyphenation - - hakyll-contrib-links - - hakyll-dhall - - hakyll-dir-list - - hakyll-elm - - hakyll-favicon - - hakyll-filestore - - hakyll-images - - hakyll-ogmarkup - - hakyll-process - - hakyll-R - - hakyll-sass - - hakyll-series - - hakyll-shakespeare - hakyll-shortcode - - hakyll-shortcut-links - - hakyll-typescript - - hal - - halberd - HaLeX - halfs - halipeto - halive - - hall-symbols - halma - - halma-gui - - halma-telegram-bot - halves - - ham - - HaMinitel - hampp - hamsql - hamtmap - - hamusic - hanabi-dealer - handa-gdata - handle-like @@ -3001,98 +1765,59 @@ broken-packages: - Hangman - hannahci - hans - - hans-pcap - hanspell - haphviz - happindicator - happindicator3 - happlets - - happlets-lib-gtk - happraise - - HAppS-Data - - happs-hsp - - happs-hsp-template - - HAppS-IxSet - - HAppS-Server - - HAppS-State - - happs-tutorial - - HAppS-Util - happstack - - happstack-auth - - happstack-authenticate - - happstack-contrib - - happstack-data - - happstack-dlg - - happstack-facebook - - happstack-fay - happstack-fay-ajax - happstack-foundation - happstack-hamlet - happstack-heist - - happstack-helpers - happstack-hstringtemplate - - happstack-ixset - - happstack-jmacro - happstack-lite - happstack-monad-peel - - happstack-plugins - happstack-server-tls-cryptonite - - happstack-state - happstack-util - - happstack-yui - - happy-hour + - HAppS-Util - happybara - - happybara-webkit - happybara-webkit-server + - happy-hour - HappyTree - hapstone - HaPy - haquery - - haquil - harchive - - hArduino - - hardware-edsl - - HaRe - - harg - - hark - - harmony - - HarmTrace - haroonga - - haroonga-httpd - harpy - harvest-api - has - - has-th - - hasbolt - hasbolt-extras - HasCacBDD - hascard - hascas - Haschoo - - HasGP - hash - hashable-extras - hashable-generics - hashable-orphans - hashabler - hashed-storage - - Hashell - - hashflare - hashring - hashtables-plus - hasim - hask - - hask-home - - haskarrow - haskbot-core - - haskdeep - - haskeem - haskeline-class - haskelisp - - haskell-abci - - haskell-aliyun + - haskell2010 + - haskell2020 + - haskell98 + - haskell98libraries + - HaskellAnalysisProgram - haskell-awk - - haskell-bitmex-client - haskell-bitmex-rest - haskell-brainfuck - haskell-ci @@ -3101,209 +1826,99 @@ broken-packages: - haskell-compression - haskell-conll - haskell-course-preludes - - haskell-debug-adapter + - haskelldb + - haskelldb-wx - haskell-disque - - haskell-docs - - haskell-eigen-util - haskell-formatter - - haskell-ftp - haskell-generate - haskell-go-checkers - haskell-holes-th - haskell-igraph - haskell-in-space - haskell-kubernetes + - HaskellLM - haskell-lsp-client - haskell-ml - haskell-mpfr - haskell-mpi - haskell-names - haskell-neo4j-client + - HaskellNet-SSL + - HaskellNN + - Haskelloids - haskell-openflow - haskell-overridez - haskell-packages - - haskell-pdf-presenter - - haskell-platform-test - haskell-player - haskell-plot - haskell-postal - haskell-read-editor - - haskell-reflect - haskell-rules + - haskellscrabble + - haskellscript - haskell-spacegoo - - haskell-src-exts-observe - haskell-src-exts-prisms - haskell-src-exts-qq - haskell-src-exts-sc - haskell-src-match - haskell-src-meta-mwotton - haskell-stack-trace-plugin - - haskell-token-utils - - haskell-tools-ast - - haskell-tools-ast-fromghc - - haskell-tools-ast-gen - - haskell-tools-ast-trf - - haskell-tools-backend-ghc - - haskell-tools-builtin-refactorings - - haskell-tools-cli - - haskell-tools-daemon - - haskell-tools-debug - - haskell-tools-demo - - haskell-tools-experimental-refactorings - - haskell-tools-prettyprint - - haskell-tools-refactor - - haskell-tools-rewrite - - haskell-tor + - HaskellTorrent + - HaskellTutorials - haskell-type-exts - haskell-typescript - haskell-tyrant - - haskell2010 - - haskell2020 - - haskell98 - - haskell98libraries - - HaskellAnalysisProgram - - haskelldb - - haskelldb-connect-hdbc - - haskelldb-connect-hdbc-catchio-mtl - - haskelldb-connect-hdbc-catchio-tf - - haskelldb-connect-hdbc-catchio-transformers - - haskelldb-connect-hdbc-lifted - - haskelldb-dynamic - - haskelldb-flat - - haskelldb-hdbc - - haskelldb-hdbc-mysql - - haskelldb-hdbc-odbc - - haskelldb-hdbc-postgresql - - haskelldb-hdbc-sqlite3 - - haskelldb-hsql - - haskelldb-hsql-mysql - - haskelldb-hsql-odbc - - haskelldb-hsql-postgresql - - haskelldb-hsql-sqlite3 - - haskelldb-th - - haskelldb-wx - - haskellish - - HaskellLM - - HaskellNet - - HaskellNet-SSL - - HaskellNN - - Haskelloids - - haskellscrabble - - haskellscript - - HaskellTorrent - - HaskellTutorials - - haskelm - haskelzinc - haskeme - haskey - - haskey-mtl - - haskgame - haskheap - haskhol-core - haskmon - haskoin - - haskoin-bitcoind - - haskoin-core - - haskoin-crypto - - haskoin-node - - haskoin-protocol - - haskoin-script - - haskoin-store - - haskoin-store-data - haskoin-util - - haskoin-wallet - - haskoon - - haskoon-httpspec - - haskoon-salvia - haskore - - haskore-realtime - - haskore-supercollider - - haskore-synthesizer - - HaskRel - - hasktorch - hasktorch-codegen - hasktorch-ffi-th - - hasktorch-ffi-thc - - hasktorch-indef - - hasktorch-signatures - hasktorch-signatures-partial - hasktorch-signatures-support - - hasktorch-zoo - haskus-binary - - haskus-system-build - - haskus-utils - - haskus-utils-compat - - haskus-utils-data - - haskus-utils-types - - haskus-utils-variant - - haskus-web - haskyapi - - haslo - - hasloGUI - hasmin - - hasparql-client - hasql-backend - hasql-class - - hasql-cursor-query - hasql-cursor-transaction - hasql-dynamic-statements - hasql-generic - - hasql-postgres - - hasql-postgres-options - - hasql-queue - hasql-simple - - hasql-th - - hasql-url - hastache - - hastache-aeson - haste - - haste-app - - haste-lib - - haste-markup - haste-prim - - Hate - hatex-guide - - HaTeX-meta - - HaTeX-qq - hats - hatt - haven - haverer - - HaVSA - - hawitter - - Hawk - hax - haxl-amazonka - haxl-facebook - haxparse - haxr-th - - haxy - hayland - - Hayoo - hayoo-cli - - hback - - hbayes - - hbb - - hbcd - hBDD-CMUBDD - hBDD-CUDD - hbeanstalk - hbeat - - hbf - hblas - hblock + - h-booru - hburg - hcad - HCard - hcc - hcg-minus - - hcg-minus-cairo - - hcheat - - hcheckers - hchesslib - - HCL - hcltest - - hCM - hcoap - hcom - hcount @@ -3313,119 +1928,66 @@ broken-packages: - hdaemonize-buildfix - hdbc-aeson - HDBC-mysql - - HDBC-postgresql-hstore - hdbc-postgresql-hstore - - hdbi - - hdbi-conduit - - hdbi-postgresql - - hdbi-sqlite - - hdbi-tests + - HDBC-postgresql-hstore - hdevtools - - hdf - hDFA - - hdiff - hdigest - - hdirect - hdis86 - hdiscount - hdm - hdo - - hdocs - - hdph - hdph-closure - hdr-histogram - HDRUtils - headergen - heap-console - heapsort - - heart-app - heart-core - - heartbeat-streams - - heatitup - - heatitup-complete - - heavy-log-shortcuts - - heavy-logger - - heavy-logger-amazon - - heavy-logger-instances - hebrew-time - - hecc - heckle - hedgehog-checkers - - hedgehog-checkers-lens - - hedgehog-fakedata - - hedgehog-gen-json - hedgehog-generic - hedgehog-golden - hedgehog-servant - - Hedi - hedis-config - hedis-namespace - - hedis-pile - hedis-simple - hedis-tags - - hedn-functor - hedra - - heidi - hein - - heist-aeson - heist-async - - helics - - helics-wai - helisp - - helium - helix - hell - - hellage - - hellnet - help-esb - hemkay - - hemokit - - hen - - henet - - hepevt - - her-lexer - - her-lexer-parsec - HERA - herbalizer - HerbiePlugin - heredocs + - her-lexer - Hermes - - hermit - - hermit-syb - herms - - herringbone - - herringbone-embed - - herringbone-wai - - hesh - - hesql - hetero-dict - heterogeneous-list-literals - - heterolist - hetris - heukarya - hevm - - hevolisa - - hevolisa-dph - - hex-text - HExcel - hexchat - hexif - hexmino - hexml-lens - - hexpat-iteratee - hexpat-pickle-generic - hexpr - hexpress - hexquote - hexstring - hext - - hextream - heyefi - - heyting-algebras - hF2 - hfann - - hfd - - hfiar - HFitUI - hfmt - hfoil @@ -3434,106 +1996,65 @@ broken-packages: - HFrequencyQueue - hfusion - hg-buildpackage - - hgalib - hgdbmi - HGE2D - hgearman - hGelf - - hgen - hgeometric - hgeometry-ipe - - hgeometry-svg - - hgeos - hgettext - hgis - - hgithub - - hgmp - hgom - hgopher + - h-gpgme - HGraphStorage - hgrep - hgrib - hharp - HHDL - - hhp - hhwloc - hi - hi3status - - hiccup - hichi - - hid-examples - hidden-char + - hid-examples - hie-core - hieraclus + - hierarchical-env - hierarchical-exceptions - - hierarchical-spectral-clustering - hierarchy - hiernotify - - Hieroglyph - higgledy - - HiggsSet - higherorder - highjson - - highjson-swagger - - highjson-th - highlight-versions - highWaterMark - himg - - himpy - - hindent - hindley-milner - - hinduce-classifier - - hinduce-classifier-decisiontree - - hinduce-examples - hinquire - hinstaller - - hint-server - hinter - hinterface - - hinvaders - - hinze-streams - - hip - - hipbot - hipchat-hs - hipe - - Hipmunk-Utils + - Hipmunk - hipsql-api - - hipsql-client - - hipsql-server - hircules - - hirt - Hish - hissmetrics - - hist-pl - - hist-pl-dawg - - hist-pl-fusion - - hist-pl-lexicon - - hist-pl-lmf - - hist-pl-types - historian - - hit - - hit-graph + - hist-pl-types - hit-on - HJavaScript - hjcase - hjs - - HJScript - - hjson-query - hjsonpointer - - hjsonschema - - hjugement-cli + - hjson-query - HJVM - hkd-delta - hkd-lens - hkt - hlbfgsb - - hlcm - - HLearn-algebra - - HLearn-approximation - - HLearn-classification - - HLearn-datastructures - - HLearn-distributions - - hledger-api - hledger-chart - hledger-irr - hledger-vty @@ -3542,98 +2063,62 @@ broken-packages: - hlibfam - HList - hlivy - - HLogger - hlogger + - HLogger - hlongurl - - hlrdb - - hlrdb-core - - hls - hls-exactprint-utils - hlwm - - hly - - hmark - hmarkup - hmatrix-banded - hmatrix-mmap - hmatrix-nipals - hmatrix-sparse - hmatrix-static - - hmatrix-sundials - hmatrix-svdlibc - hmatrix-syntax - hmatrix-tests - - hmeap - - hmeap-utils - hmenu - - hmep - hmk - - HMM - hmm + - HMM - hmm-hmatrix - - hmm-lapack - hMollom - hmp3 - Hmpf - - hmt - - hmt-diagrams - hmumps - hnetcdf - - HNM - - hnormalise - - ho-rewriting - hoauth - - hob - hobbes - - hobbits - hocilib - hocker - hodatime - HODE - hoe - - Hoed - - hOff-display - hog - hogg - - hoggl - - hogre - - hogre-examples - hois - hol - hold-em - hole - holmes - - Holumbus-Searchengine - - holy-project - homeomorphic - - hommage - homoiconic - homplexity - - HongoDB - honi - hoobuddy - - hood - - hood-off - hood2 - - hoodie - - hoodle - - hoodle-builder - - hoodle-core - - hoodle-extra - - hoodle-parser - - hoodle-publish - - hoodle-render - hoodle-types + - hood-off - hoogle-index - hooks-dir - hoop - hoopl - - hoovie - hopencc - hopencl - HOpenCV - hopfield - hops - - hoq + - ho-rewriting - horizon - horname - hosc-json @@ -3643,158 +2128,72 @@ broken-packages: - hourglass-fuzzy-parsing - houseman - hp2any-core - - hp2any-graph - - hp2any-manager - hpack-convert - - hpack-dhall - - hpaco - - hpaco-lib - - hpage - hpapi - - hpaste - hpasteit - HPath - hpc-coveralls - - hpc-tracer - - hPDB - - hPDB-examples - - HPDF - hpg - HPi - hpio - hplaylist - - HPlot - hpodder - - HPong - hpqtypes - - hpqtypes-extras - hprotoc - - hprotoc-fork - - hps - - hps-cairo - hps-kmeans - hPushover - hpygments - hpylos - hpyrg - - hpython - - hquantlib - hquantlib-time - hR - - hranker - - HRay - - hreader - - hreader-lens - - hreq-client - - hreq-conduit - hreq-core - - Hricket + - h-reversi - hricket - - hriemann - - HROOT - - HROOT-core - - HROOT-graf - - HROOT-hist - - HROOT-io - - HROOT-math - - HROOT-tree - - hs-blake2 - - hs-brotli - - hs-carbon-examples - - hs-cdb - - hs-conllu - - hs-di - - hs-dotnet - - hs-excelx - - hs-ffmpeg - - hs-fltk - - hs-gen-iface - - hs-gizapp - - hs-inspector - - hs-java - - hs-json-rpc - - hs-logo - - hs-nombre-generator - - hs-pattrans - - hs-pgms - - hs-pkg-config - - hs-pkpass - - hs-re - - hs-rqlite - - hs-rs-notify - - hs-scrape - - hs-snowtify - - hs-speedscope - - hs-tags - - hs-twitter - - hs-twitterarchiver - - hs-vcard - - hs-watchman + - Hricket - hs2bf - - Hs2lib - hs2ps - hsaml2 - - hsautogui - hsay - - hsbackup - hsbc - hsbencher - - hsbencher-codespeed - - hsbencher-fusion - hsc3 - - hsc3-auditor - - hsc3-cairo - - hsc3-data - - hsc3-db - - hsc3-dot - - hsc3-forth - - hsc3-graphs - - hsc3-lang - - hsc3-lisp - - hsc3-plot - - hsc3-process - - hsc3-rec - hsc3-rw - - hsc3-server - hsc3-sf - - hsc3-sf-hsndfile - - hsc3-unsafe - - hsc3-utils - hscaffold - hscamwire - - hscassandra + - hs-carbon-examples - hscd + - hs-cdb - hsclock - - hscope - hScraper - hscuid - - hsdev + - hs-di - hsdif - hsdip - hsdns-cache - - Hsed - - hsendxmpp + - hs-dotnet - hsenv - HSet - - hset - - hsfacter + - hs-excelx - hsfcsh - HSFFIG - hsfilt + - hs-fltk - hsforce - - HSGEP + - hs-gizapp - hsgnutls - hsgnutls-yj - hsgsom - HsHaruPDF - - HSHHelpers - HsHTSLib - HsHyperEstraier - hsI2C - hSimpleDB - hsimport - - hsinspect - hsinspect-lsp + - hs-java + - hs-json-rpc - HsJudy - hskeleton - hslackbuilder @@ -3802,80 +2201,64 @@ broken-packages: - hslinks - hslogger-reader - hslogger-template - - hslogstash + - hs-logo - hsluv-haskell - hsmagick - - HSmarty - hsmodetweaks - Hsmtlib - hsmtpclient - - hsnock + - hs-nombre-generator - hsns - hsnsq - hsntp - hsoptions - - HSoundFile - hsoz - - hsp-cgi - hsparql - - HsParrot + - hs-pattrans + - hsp-cgi - hspear - - hspec-expectations-json + - hspec2 - hspec-expectations-match - - hspec-expectations-pretty - hspec-experimental - - hspec-hashable - hspec-jenkins - hspec-monad-control - - hspec-pg-transact - - hspec-setup - - hspec-shouldbe - hspec-snap - hspec-structured-formatter - - hspec-test-sandbox - hspec-webdriver - - hspec2 - - hspecVariant - HsPerl5 + - hs-pgms - hspkcs11 + - hs-pkg-config - hspread - hspresent - - hsprocess - hsql - - hsql-mysql - - hsql-odbc - - hsql-postgresql - - hsql-sqlite3 - - hsreadability + - hs-re - hsrelp + - hs-rqlite + - hs-rs-notify + - hs-scrape - hsseccomp + - hs-snowtify + - hs-speedscope - hsSqlite3 - hssqlppp - - hssqlppp-th - HsSVN - - hstar + - hs-tags - hstats - hstatsd - hstest - hstidy - - hstox - - hstradeking - - HStringTemplateHelpers + - hs-twitter + - hs-twitterarchiver - hstyle - - hstzaar - - hsubconvert - hsudoku - - HsWebots - - hswip + - hs-vcard + - hs-watchman - hsx - - hsx-jmacro - - hsx-xhtml - hsXenCtrl - hsyscall - hsyslog-tcp - hszephyr - - HTab - - htags - hTalos - htar - htdp-image @@ -3888,12 +2271,12 @@ broken-packages: - html-kure - html-rules - html-tokenizer - - hts - htsn - htsn-import - htssets + - http2-client + - http2-grpc-proto-lens - http-attoparsec - - http-client-auth - http-client-lens - http-client-request-modifiers - http-client-session @@ -3903,9 +2286,7 @@ broken-packages: - http-conduit-downloader - http-directory - http-dispatch - - http-enumerator - http-grammar - - http-io-streams - http-kinder - http-listen - http-monad @@ -3914,18 +2295,9 @@ broken-packages: - http-proxy - http-querystring - http-response-decoder - - http-rfc7807 - http-server - http-shed - http-wget - - http2-client - - http2-client-exe - - http2-client-grpc - - http2-grpc-proto-lens - - http2-grpc-proto3-wire - - https-everywhere-rules - - https-everywhere-rules-raw - - httpspec - htune - htvm - htzaar @@ -3933,8 +2305,6 @@ broken-packages: - HueAPI - huff - huffman - - hugs2yc - - hulk - HulkImport - human-parse - human-text @@ -3942,101 +2312,49 @@ broken-packages: - hums - hunch - HUnit-Diff - - hunit-gui - hunit-rematch - - hunp - hunspell-hs - - hunt-searchengine - - hunt-server - hup - - hurdle - - hurl - hurriyet - - husk-scheme - - husk-scheme-libs - - husky - hutton - huttons-razor - - huzzy - hVOIDP - - hw-all - - hw-aws-sqs-conduit - - hw-ci-assist - - hw-dsv - - hw-json - - hw-json-lens - - hw-json-simd - - hw-json-simple-cursor - - hw-json-standard-cursor - - hw-kafka-avro - - hw-prim-bits - - hw-simd - - hw-simd-cli - - hw-uri - hwall-auth-iitk + - hw-ci-assist - hweblib - hwhile + - hw-json-simd - hworker - - hworker-ses - - hwormhole - - hws + - hw-simd - hwsl2 - - hwsl2-bytevector - - hwsl2-reducers - hx - - HXMPP - - hxmppc - - hxournal - HXQ + - hxt-cache - hxt-pickle-utils - - hxthelper - - hxweb - hyakko - - hybrid - hydra-hs - hydra-print - - Hydrogen - hydrogen - - hydrogen-cli - - hydrogen-cli-args - - hydrogen-data - hydrogen-multimap - - hydrogen-parsing - - hydrogen-prelude - - hydrogen-prelude-parsec - - hydrogen-syntax - - hydrogen-util - - hyena - hylide - hylolib - - hylotab - - hyloutils - hyperdrive - hyperfunctions - hyperion - hyperloglogplus - - hyperpublic - hypher - - hzk - hzulip - i18n - I1M - i3ipc - iap-verifier - - ib-api - iban + - ib-api - ical - - ice40-prim - icepeak - IcoGrid - iconv-typed - - ide-backend - - ide-backend-common - - ide-backend-server - ideas - - ideas-math - - ideas-math-types - - ideas-statistics - idempotent - identifiers - idiii @@ -4048,84 +2366,44 @@ broken-packages: - IFS - ig - ige - - ige-mac-integration - ignore - igraph - ihaskell-parsec - - ihaskell-rlangqq - ihaskell-widgets - - ihttp - illuminate - imagepaste - - imap - imapget - - imbib - imgur - - imgurder - - imj-animation - - imj-base - - imj-game-hamazed - - imj-measure-stdout - imj-prelude - - imm - immortal-worker - - imparse - imperative-edsl - - imperative-edsl-vhdl - ImperativeHaskell - impl - implicit-logging - implicit-params - - importify - imports - impossible - imprint - - improve - - INblobs - - inch - inchworm - - incremental-computing - - incremental-maps - - increments - - indentation - indentation-core - - indentation-parsec - - indentation-trifecta - - indents - index-core - - indexation - - IndexedList - indextype - indices - - indieweb-algorithms - - inf-interval - infer-upstream - - infernal - - infernu - infinity + - inf-interval - infix - - InfixApplicative - inflist - informative - - ini-qq - inilist + - ini-qq - initialize - inject-function - - inline-asm - - inline-java - inserts - - inspector-wrecker - instana-haskell-trace-sdk - instance-map - - instant-aeson - - instant-bytes - - instant-deepseq - instant-generics - - instant-hashable - - instant-zipper - - instapaper-sender - instinct - - int-multimap - intcode - integer-pure - integreat @@ -4135,117 +2413,65 @@ broken-packages: - internetmarke - intero - interpol - - interpolatedstring-qq - - interpolatedstring-qq-mwotton - interpolatedstring-qq2 - interruptible - interval - IntFormats + - int-multimap - intricacy - - intro-prelude - introduction - - introduction-test - - intset + - intro-prelude - invert - - invertible-hlist - invertible-syntax - io-capture - io-choice - - io-reactive - ioctl - - ion - IOR - - IORefCAS + - io-reactive - iostring - iothread - iotransaction - - ip - - ip-quoter - ip2location - ip2proxy - - ipatch - - ipc - ipfs - - ipfs-api - - ipld-cid - ipopt-hs - - ipprint + - ip-quoter - iptables-helpers - - iptadmin - IPv6DB - Irc - irc-dcc - - irc-fun-bot - - irc-fun-client - - irc-fun-color - - irc-fun-messages - irc-fun-types - - iri - iridium - iron-mq - - ironforge - irt - isdicom - - isevaluated - - ismtp - IsNull - iso8601-duration - isobmff - - isobmff-builder - - isohunt - isotope - - it-has - itcli - itemfield - - iter-stats - iteratee - - iteratee-compress - - iteratee-mtl - - iteratee-parsec - - iteratee-stm - iterIO - - iterio-server - - iterm-show - - iterm-show-diagrams - - iterm-show-JuicyPixels - - ivor + - it-has - ivory - - ivory-avr-atmega328p-registers - - ivory-backend-c - - ivory-bitdata - - ivory-eval - - ivory-examples - - ivory-hw - - ivory-opts - - ivory-quickcheck - - ivory-serialize - - ivory-stdlib - - ivy-web - ixdopp - ixmonad - ixshader - - iyql - j - - j2hs - jack-bindings - - JackMiniMix - jackminimix + - JackMiniMix - jacobi-roots - jaeger-flamegraph - - jail - jalla - jarfind - jarify - jason - java-bridge - - java-bridge-extras - - java-character - - java-reflect - javascript-bridge - - Javasf - - javasf - - Javav - javav + - Javav - jbi - jcdecaux-vls - Jdh @@ -4254,328 +2480,171 @@ broken-packages: - jenkinsPlugins2nix - jespresso - jinquantities - - jmacro - - jmacro-rpc - - jmacro-rpc-happstack - - jmacro-rpc-snap - jml-web-service - - jmonkey - jni - jobqueue - - jobs-ui - - join - join-api - joinlist - jonathanscard - - jot - jpeg - - js-good-parts - jsaddle-hello - jsaddle-wkwebview - - JsContracts - - jsmw + - js-good-parts + - json2 - json-alt - json-assertions - - json-ast-json-encoder - json-ast-quickcheck - - json-autotype - - json-b - json-builder - - JSON-Combinator - - JSON-Combinator-Examples - json-encoder - - json-enumerator + - jsonextfilter - json-extra - json-fu - - json-incremental-decoder - json-litobj + - jsonnet - json-pointer-hasql - json-pointy - json-python - - json-query + - jsonresume - json-rpc-client - json-schema - - json-sop - - json-syntax - - json-to-haskell - - json-togo - - json-tokens - - json-tools - - json-tracer - - json2 - - json2-hdbc - - JSONb - - jsonextfilter - - JsonGrammar - - jsonifier - - jsonnet - - jsonresume - - jsonrpc-conduit - - jsons-to-schema - jsonschema-gen - jsonsql + - json-tools + - json-tracer - jsontsv - jsonxlsx - - jspath - - juandelacosa - judge - judy - JuicyPixels-blp - JuicyPixels-canvas - JunkDB - - JunkDB-driver-gdbm - - JunkDB-driver-hashtables - jupyter - - JuPyTer-notebook - JustParse - - jvm - - jvm-batching - jvm-binary - jvm-parser - - jvm-streaming - JYU-Utils - kademlia - kafka-client - kafka-client-sync - - kafka-device - - kafka-device-glut - - kafka-device-joystick - - kafka-device-leap - - kafka-device-spacenav - - kafka-device-vrpn - - kaleidoscope - - Kalman - kalman + - Kalman - kangaroo - - kansas-lava - - kansas-lava-cores - - kansas-lava-papilio - - kansas-lava-shake - - karakuri - karps - - katip-elasticsearch - katip-kafka - katip-raven - - katip-rollbar - katip-scalyr-scribe - katip-syslog - katt - katydid - - kawaii - kawhi - - kd-tree - kdesrc-build-extra + - kd-tree - keccak - - keera-hails-i18n - - keera-hails-mvc-environment-gtk - - keera-hails-mvc-model-lightmodel - - keera-hails-mvc-model-protectedmodel - - keera-hails-mvc-solutions-gtk - - keera-hails-reactive-cbmvar - - keera-hails-reactive-fs - - keera-hails-reactive-gtk - - keera-hails-reactive-htmldom - - keera-hails-reactive-network - - keera-hails-reactive-polling - - keera-hails-reactive-wx - - keera-hails-reactive-yampa - - keera-hails-reactivelenses - keera-hails-reactivevalues - kempe - kerry - Ketchup - keter - - kevin - keyed - keyring - - keysafe - - keystore - - keyvaluehash - - keyword-args - khph - - kicad-data - kickass-torrents-dump-parser - kickchan - - kif-parser - - kit - - kleene - - kmeans-par - - kmeans-vector - kmonad - kmp-dfa - - knead - - knead-arithmetic - - knit-haskell - - knots - koellner-phonetic - kontra-config - - korfu - kparams - kqueue - kraken - krapsh - Kriens - krpc - - ks-test - KSP - ktx - ktx-codec - - kubernetes-client - - kubernetes-client-core - kuifje - - kure - kure-your-boilerplate - - kurita - KyotoCabinet - - l-bfgs-b - - L-seed - labeled-graph - - laborantin-hs - - labsat - - labyrinth - - labyrinth-server - - lackey - lagrangian - - laika - - lambda-bridge - - lambda-calculator - - lambda-canvas - - lambda-devs - - lambda-options - - lambda-toolbox - lambda2js - lambdaBase - lambdabot-utils - - lambdabot-zulip + - lambda-bridge + - lambda-canvas - lambdacms-core - - lambdacms-media - - lambdacube - - lambdacube-bullet - - lambdacube-compiler - - lambdacube-core - - lambdacube-edsl - - lambdacube-engine - - lambdacube-examples - - lambdacube-gl - lambdacube-ir - - lambdacube-samples - - LambdaDesigner - - lambdaFeed - - LambdaHack - - LambdaINet - Lambdajudge - - lambdaLit - LambdaNet - - LambdaPrettyQuote - - LambdaShell - lambdatex + - lambda-toolbox - lambdatwit - Lambdaya - - lambdaya-bus - - lambdiff - lame - lame-tester - - lang - language-asn - - language-boogie - language-c-comments - language-c-inline - language-conf - language-csharp - language-dart - - language-dickinson - language-dockerfile - - language-eiffel - language-elm - - language-fortran - language-gcl - language-go - language-guess - language-hcl - language-java-classfile - - language-kort - - language-lua-qq - language-lua2 + - language-lua-qq - language-mixal - - language-Modula2 - - language-ninja - - language-oberon - language-objc - language-ocaml - language-openscad - language-pig - language-puppet - - language-python-colour - - language-qux - language-rust - language-sh - - language-spelling - language-sqlite - language-sygus - - language-thrift - language-tl - language-typescript - language-vhdl - language-webidl - - lapack - - lapack-carray - - lapack-comfort-array - lapack-ffi - - large-hashable - Lastik - - lat - latest-npm-version - - latex-formulae-hakyll - latex-formulae-image - - latex-formulae-pandoc - - latex-svg-hakyll - latex-svg-image - - latex-svg-pandoc - LATS - - launchdarkly-server-sdk - launchpad-control - lawless-concurrent-machines - - layered-state - layers - - layers-game - layout - layout-bootstrap - - layout-rules - - layouting - - lazy-hash - - lazy-hash-cache - - lazy-io-streams - - lazy-priority-queue - - lazy-search - lazyarray - lazyboy + - lazy-priority-queue - lazyset - LazyVault - - ld-intervals + - l-bfgs-b - lda - - ldapply - - LDAPv3 - ldif + - ld-intervals - leaf - - leaky - - lean - - leanpub-wreq - leapseconds - learn - - learn-physics-examples - Learning + - learn-physics-examples - leb128 - leetify - - legion - - legion-discovery - - legion-discovery-client - - legion-extra - - leksah-server - lendingclub - lens-filesystem - lens-labels - lens-prelude - lens-process + - lensref - lens-simple - lens-text-encoding - lens-th-rewrite @@ -4583,26 +2652,13 @@ broken-packages: - lens-toml-parser - lens-tutorial - lens-typelevel - - lens-utils - - lensref - - lentil - - level-monad - Level0 - - levmar - - levmar-chart - - lex-applicative + - level-monad - lfst - - lgtk - - lha - - lhae - lhc - - lhe - lhs2TeX-hl - lhslatex - - libarchive - LibClang - - libconfig - - libcspm - libexpect - libfuse3 - libGenI @@ -4610,447 +2666,258 @@ broken-packages: - libinfluxdb - libjenkins - libjwt-typed - - liblastfm - - liblawless - - liblinear-enumerator - libltdl - - libmolude - libnix - liboath-hs - liboleg - libpafe - libpq - - libraft - librandomorg - - librato - libssh2 - - libssh2-conduit - libsystemd-daemon - libtagc - libxls - - libxml-enumerator - libxslt - lie - life-sync - - lifetimes - - lifted-base-tf - lifted-protolude - lifter - ligature - - lightning-haskell - - lightstep-haskell - - lighttpd-conf - - lighttpd-conf-qq - lilypond - Limit - limp-cbc - linda - linden - - line-bot-sdk - - line-drawing - linear-algebra-cblas - linear-base - - linear-circuit - linear-code - linear-maps - linear-opengl - - linear-vect - - linearmap-category - linearscan - - linearscan-hoopl - - LinearSplit + - linear-vect + - line-drawing - lines-of-action - - LinkChecker - - linkchk - - linkcore - - linked-list-with-iterator - linkedhashmap + - linked-list-with-iterator - linklater - - linnet - - linnet-aeson - - linnet-conduit - linode - linode-v4 - linux-blkid - linux-cgroup - linux-kmod - linux-perf - - linux-ptrace - linx-gateway - - lio-eci11 - lio-simple - - lion - lipsum-gen - liquid - - liquid-base - - liquid-bytestring - - liquid-containers - - liquid-ghc-prim - - liquid-parallel - - liquid-platform - - liquid-prelude - - liquid-vector - liquidhaskell - liquidhaskell-cabal - Liquorice - list-fusion-probe + - listlike-instances - list-mux - list-prompt - list-remote-forwards - - list-t-attoparsec - - list-t-html-parser + - ListT - list-t-http-client - list-t-text - - list-witnesses - list-zip-def - list-zipper - - listenbrainz-client - - listlike-instances - - ListT - liszt - lit - literals - LiterateMarkdown - - little-logger - - live-sequencer - ll-picosat - llsd - - llvm - - llvm-analysis - llvm-base - - llvm-base-types - - llvm-base-util - - llvm-data-interop - - llvm-dsl - - llvm-extension - - llvm-extra - llvm-ffi - llvm-ffi-tools - - llvm-general - llvm-general-pure - - llvm-general-quote - llvm-ht - llvm-pkg-config - llvm-pretty - - llvm-pretty-bc-parser - - llvm-tf - - llvm-tools - lmonad - - lmonad-yesod - load-balancing - load-font - local-address - - local-search - - localize - located - located-monad-logger - loch - - locked-poll - - log - - log-postgres - - log-utils - - log-warper - log2json - log4hs - logentries - logger - - logging-effect-extra - logging-effect-extra-file - logging-effect-extra-handler - Logic - - logic-classes - - LogicGrowsOnTrees - - LogicGrowsOnTrees-MPI - - LogicGrowsOnTrees-network - - LogicGrowsOnTrees-processes - logicst - logict-state - logplex-parse - - lojban + - log-warper - lojbanParser - lojbanXiragan - - lojysamban - lol - - lol-apps - - lol-benches - lol-calculus - - lol-cpp - - lol-repa - - lol-tests - - lol-typing - - loli - longboi - - longshot - lookup-tables - - loop-effin - - loop-while - loopbreaker - looper - loops + - loop-while - loopy - lord - lorem - - lorentz - loris - loshadka - - lostcities - - loup - lowgl - lp-diagrams-svg - LRU - - ls-usb - lscabal + - L-seed - lsfrom - - LslPlus - - lsystem - - lti13 + - ltext - ltk - LTS - lua-bc - - luachunk - luautils - - lucid-colonnade - - lucienne - - Lucu - - luhn - - lui - luis-client - luka - luminance - - luminance-samples - lushtags - luthor - - lvish - lvmlib - lxc - lxd-client - lye - - Lykah - - lz4-bytes - - lz4-conduit - lz4-frame-conduit - lzip - - lzma-enumerator - lzma-streams - lzo - maam - mac - macaroon-shop - - macbeth-lib - machinecell - - machines-amazonka - - machines-attoparsec - - machines-binary - machines-bytestring - machines-directory - machines-encoding - - machines-io - - machines-process - machines-zlib - macho - maclight - macos-corelibs - - macosx-make-standalone - macrm - madlang - mage - - magic-tyfams - - magic-wormhole - - magicbane - MagicHaskeller - - magico + - magic-tyfams - magma - - mahoro - - maid - - mail-pool - - mail-reports - mailchimp - - mailchimp-subscribe - MailchimpSimple - - mailgun - - majordomo - - majority + - mailchimp-subscribe + - makedo + - makefile - make-hard-links - make-monofoldable-foldable - make-package - - makedo - - makefile - mallard - - manatee - - manatee-anything - - manatee-core - - manatee-curl - - manatee-editor - - manatee-filemanager - - manatee-imageviewer - - manatee-ircclient - - manatee-mplayer - - manatee-pdfviewer - - manatee-processmanager - - manatee-template - - manatee-terminal - - manatee-welcome - mandrill - mandulia - mangopay - - manifold-random - - manifolds - Map - - map-exts - mapalgebra + - map-exts - Mapping - mappy - - marionetta - markdown-kate - - markdown-pap - - markdown2svg - marked-pretty - - markov-processes - - markov-realization - - markup - - marmalade-upload - - marquise - mars - - marvin - marvin-interpolate - - masakazu-bot - MASMGen - massiv-persist - massiv-serialise - - master-plan - - matchers + - mathflow - math-grads - math-interpolate - math-metric - math-programming - - math-programming-glpk - - math-programming-tests - - mathblog - - mathflow - - mathlink - matrix-as-xyz - matrix-market - matrix-sized - - matsuri - maude - - maxent - maxent-learner-hw - - maxent-learner-hw-gui - - maxsharing - maybench - MaybeT - MaybeT-monads-tf - - MaybeT-transformers - MazesOfMonad - MBot - mbox-tools - mbug - - MC-Fold-DP - mcl - mcm - mcmaster-gloss-examples - - mcmc - - mcmc-samplers - mcmc-synthesis - mcpi - mdapi - mdcat - - mDNSResponder-client - mdp - mealstrom - - mealy - MeanShift - Measure - mecab - mech - Mecha - - Mechs - mechs + - Mechs - mediabus - - mediabus-fdk-aac - - mediabus-rtp - mediawiki - medium-sdk-haskell - - mega-sdist - megalisp + - mega-sdist - mellon-core - - mellon-gpio - - mellon-web - melody - - memcache - - memcache-conduit - - memcache-haskell - memcached-binary + - memcache-haskell - memis - - memo-ptr - memoization-utils + - memo-ptr - memorypool - menoh - menshen - - mergeful-persistent - - mergeless-persistent - - merkle-patricia-db - merkle-tree - messagepack-rpc - messente - - meta-misc - - meta-par - - meta-par-accelerate - metadata - MetaHDBC - metaheuristics - - MetaObject - - metaplug - - metar - - metar-http + - meta-misc + - meta-par - metric - - Metrics - metricsd-client - - metronome - mezzo - mezzolens - - MFlow - mgeneric - - Mhailist - MHask - mi - - Michelangelo - miconix-test - - micro-gateway - - micro-recursion-schemes - microbase - - microformats2-parser - - microformats2-types - microgroove - microlens-each - micrologger + - micro-recursion-schemes - microsoft-translator - - MicrosoftTranslator - mida - midi-music-box - - midi-utils - - midimory - midisurface - - mighttpd - - migrant-core + - midi-utils - migrant-hdbc - migrant-postgresql-simple - - migrant-sqlite-simple - mikmod - mikrokosmos - miku - milena - mime-directory - - minecraft-data - - minesweeper - - mini-egison - - miniforth - minilens - minilight - - minilight-lua - - minimung - minions - - minioperational - miniplex - minirotate - ministg @@ -5058,151 +2925,95 @@ broken-packages: - minst-idx - mios - MIP - - MIP-glpk - mirror-tweet - - miso - miso-action-logger - miso-examples - - miss - - miss-porcelain - - missing-py2 - - MissingPy - mit-3qvpPyAi6mH - mix-arrows - - mixed-strategies - mixpanel-client - - mkbndl - - mkcabal - ml-w - - mlist - mm2 - mmark - - mmark-cli - - mmark-ext - - mmsyn7h - mmtf - mmtl - - mmtl-base - - moan - Mobile-Legends-Hack-Cheats - modelicaparser - - modify-fasta - - modsplit - modular-prelude - - modular-prelude-classy - - modularity - module-management - modulespection - - modulo - - Moe - moe + - Moe - MoeDict - moesocks - mohws - - mole - mollie-api-haskell + - monadacme - monad-atom - monad-atom-simple - monad-bayes - monad-branch - - monad-exception + - MonadCatchIO-transformers + - MonadCompose - monad-fork - monad-http + - monadiccp + - monadic-recursion-schemes - monad-interleave + - Monadius - monad-levels - monad-lgbt + - monadLib-compose + - monadloc-pp - monad-log + - monadlog - monad-lrs - monad-mersenne-random - - monad-metrics-extensible - monad-mock - monad-open + - Monadoro - monad-parallel-progressbar - monad-param - monad-persist + - monadplus - monad-ran - monad-recorder - - monad-state + - monads-fd + - MonadStack - monad-statevar - monad-ste - monad-stlike-io - - monad-stlike-stm - monad-task - monad-timing - monad-tx - monad-unify - - monad-var - monad-wrap - - monadacme - - MonadCatchIO-mtl - - MonadCatchIO-mtl-foreign - - MonadCatchIO-transformers - - MonadCatchIO-transformers-foreign - - MonadCompose - - monadic-recursion-schemes - - monadiccp - - monadiccp-gecode - - Monadius - - MonadLab - - monadLib-compose - - monadloc-pp - - monadlog - - Monadoro - - monadplus - - monads-fd - - MonadStack - - monarch - - Monaris - Monatron - - Monatron-IO - mondo - - monetdb-mapi - money - - mongoDB - mongodb-queue - - mongrel2-handler - monitor - - monky - mono-foldable - - Monocle - monoid - monoid-absorbing - monoid-owns - monoidplus - monoids - monopati - - monte-carlo - months - monus - monzo - - moo - morfette - morfeusz - - morley - - morloc - - morpheus-graphql - - morpheus-graphql-app - morpheus-graphql-cli - - morpheus-graphql-subscriptions - morphisms-functors - - morphisms-functors-inventory - morphisms-objects - morte - - mosaico-lib - moto-postgresql - - motor-diagrams - motor-reflection - mount - movie-monad - - mp - - mpdmate - mpppc - - mprelude - - mpretty - mpris - - mprover - - mps - - mptcp-pm - mpvguihs - mqtt - mqtt-hs @@ -5210,152 +3021,82 @@ broken-packages: - mrm - ms - msgpack - - msgpack-aeson - msgpack-binary - - msgpack-idl - - msgpack-rpc - - msgpack-rpc-conduit - msh - msi-kb-backlit - - MSQueue - MTGBuilder - - mtgoxapi - mtl-c - mtl-evil-instances - mtl-extras - mtl-tf - mtlx - mtp - - mu-avro - - mu-graphql - - mu-grpc-client - - mu-grpc-common - - mu-grpc-server - - mu-kafka - - mu-lens - - mu-optics - - mu-persistent - - mu-prometheus - - mu-protobuf - - mu-rpc - - mu-schema - - mu-servant-server - - mu-tracing - MuCheck - - MuCheck-Hspec - - MuCheck-HUnit - - MuCheck-QuickCheck - - MuCheck-SmallCheck - mud - muesli - mulang - multext-east-msd - - multi-cabal - - multi-instance - - multi-trie - multiaddr - multiarg - - multibase - - multifocal - multihash - - multihash-serialise + - multi-instance - multilinear - - multilinear-io - multipass - multipath - multiplate-simplified - - multiplicity - multipool-persistent-postgresql - multirec - - multirec-alt-deriver - - multirec-binary - - multisetrewrite - multivariant - Munkres-simple - muon - - murder - murmur - murmur3 - - murmurhash3 - mushu - - music-graphics - - music-parts - - music-pitch - - music-preludes - - music-score - - music-sibelius - - music-suite - - music-util - - musicbrainz-email - musicScroll + - music-util - musicxml - - musicxml2 - mustache-haskell - - mutable-iter - - MutationOrder - - mute-unmute - mvar-lock - mvc - - mvc-updates - - mvclient - mxnet - - mxnet-dataiter - - mxnet-examples - - mxnet-nn - mxnet-nnvm - - my-package-testing - - my-test-docs - myanimelist-export - myo + - my-package-testing - MyPrimes - mysnapsession - - mysnapsession-example - mysql-effect - - mysql-haskell-openssl - mysql-simple-quasi - - mysql-simple-typed - mystem - - myTestlll - - mywatch + - my-test-docs - myxine-client - mzv - - n-tuple - n2o-protocols - - n2o-web - nagios-plugin-ekg - - nakadi-client - named-lock - - named-servant - - named-servant-client - named-servant-server - named-sop - namelist - - namespace + - nanocurses - nano-hmac - nano-md5 - - nanocurses - nanomsg - nanomsg-haskell - nanoparsec - NanoProlog - nanovg - - nanovg-simple - nanq - naperian - - NaperianNetCDF - naqsha - narc - - nat-sized-numbers - nationstates - nats-client - - nats-queue + - nat-sized-numbers - natural - - natural-number - NaturalLanguageAlphabets - NaturalSort - naver-translate - nbt - - NearContextAlgebra - neat - needle - neet @@ -5363,134 +3104,85 @@ broken-packages: - neither - neko-lib - Neks - - nemesis-titan - neptune-backend - - nerf - nero - - nero-wai - - nero-warp - nest - - nested-routes - - nested-sequence - NestedFunctor - nestedmap - - net-spider - - net-spider-cli - - net-spider-pangraph - - net-spider-rpl - - net-spider-rpl-cli + - nested-sequence - netclock - - netcore - netease-fm - - netlines - netrium - NetSNMP - netspec - - netstring-enumerator - - nettle-frp - - nettle-netkit - - nettle-openflow + - net-spider - netwire-input-javascript - netwire-vinylglfw-examples - network-address - - network-anonymous-i2p - - network-anonymous-tor - network-api-support - - network-arbitrary - network-attoparsec - network-bitcoin - network-builder - network-bytestring - - network-carbon - - network-connection - network-dns - - network-enumerator - - network-hans + - networked-game - network-house - - network-interfacerequest - - network-messagepack-rpc-websocket - - network-minihttp + - network-metrics + - network-msg - network-msgpack-rpc - - network-netpacket - network-packet-linux - - network-protocol-xmpp - - network-rpca - network-server - network-service - network-simple-sockaddr - network-simple-wss - network-socket-options - - network-stream - - network-topic-models - network-transport-amqp - network-transport-inmemory - network-uri-json - network-voicetext - network-wai-router - - network-websocket - - networked-game - neural - neural-network-blashs - neural-network-hmatrix - newhope - newports - newsletter - - newsletter-mailgun - newt - newtype-deriving - newtype-th - - newtype-zoo - next-ref - nextstep-plist - nfc - NGrams - - ngrams-loader - - ngx-export-tools-extra - niagra - nibblestring - nice-html - nicovideo-translator - - nikepub - - Ninjas - - nirum - nitro - nix-delegate - nix-deploy - nix-eval - nix-freeze-tree - - nix-thunk - - nix-tools - nixfromnpm - nixpkgs-update + - nix-tools - nkjp - nlp-scores - - nlp-scores-scripts - nm - NMap - nntp - - no-role-annots - noether - nofib-analyse - nofib-analyze - noise - - noli - nom - - Nomyx - - Nomyx-Core - - Nomyx-Language - - Nomyx-Rules - - Nomyx-Web - - non-empty-zipper - NonEmpty - nonempty-lift - - NonEmptyList - - normalization-insensitive - - NoSlow - - not-gloss-examples + - non-empty-zipper + - no-role-annots - notcpp + - not-gloss-examples - notifications-tray-icon - - notmuch-haskell - - notmuch-web - NoTrace - now-haskell - np-extras @@ -5498,156 +3190,109 @@ broken-packages: - nptools - ntp-control - ntrip-client - - nuha - - null-canvas + - n-tuple - nullary + - null-canvas - nullpipe - numbered-semigroups - NumberSieves - NumberTheory - numerals - numerals-base - - numeric-ode - numeric-qq - numeric-ranges - - numerical - numhask-array - numhask-free - - numhask-hedgehog - - numhask-histogram - numhask-prelude - - numhask-range - numhask-space - - numhask-test - - Nussinov78 - Nutri - - NXT - NXTDSL - nylas - - nymphaea - nyx-game - oanda-rest-api - oasis-xrd - oauth2-jwt-bearer - oauthenticated - - obd - - obdd - - oberon0 - - obj - Object - - objectid - ObjectIO - objective - oblivious-transfer - ocaml-export - - ochan - - octane - - octohat - - octopus - Octree - - oculus - odbc - - odd-jobs - OddWord - oden-go-packages - oeis2 - - off-simple - OGL - ogmarkup - - ohloh-hs - oi - oidc-client - - ois-input-manager - - olwrapper - om-actor + - omaketex + - ombra - om-doh + - omega + - Omega - om-elm - om-fail - om-http-logging - - omaketex - - ombra - - Omega - - omega - omnifmt - on-a-horse - - on-demand-ssh-tunnel - onama - ONC-RPC + - on-demand-ssh-tunnel - oneormore - - online - - online-csv - onpartitions - - OnRmt - onu-course - op - opaleye-classy - opaleye-sqlite - - opaleye-trans - open-adt - - open-adt-tutorial - - open-haddock - - open-pandoc - - open-signals - - open-typerep - - open-union - OpenAFP - - OpenAFP-Utils - openai-hs - - openai-servant + - openapi3-code-generator - openapi-petstore - openapi-typed - - openapi3-code-generator - opench-meteo - OpenCL - OpenCLRaw - OpenCLWrappers - opencv-raw - opendatatable - - OpenGLCheck - opengles + - open-haddock - openid-connect - - OpenSCAD + - open-pandoc + - open-signals - opensoundcontrol-ht - - openssh-github-keys - openssh-protocol - opentelemetry-http-client - opentheory-char - opentok - - opentracing-jaeger - - opentracing-zipkin-v1 - opentype - - OpenVG - OpenVGRaw - - openweathermap - Operads - operate-do - operational-extra - oplang - opn - optima - - optima-for-hasql - - optimal-blocks - optimization - - optimusprime - optional - options-time - optparse-applicative-simple - - optparse-enum - optparse-helper - orc - orchestrate - OrchestrateDB - - orchid - - orchid-demo - - order-maintenance + - ordered - order-statistics - ordinal - Ordinary - ordrea - oref - - org-mode - - org-mode-lucid - organize-imports + - org-mode - orgmode - origami - orizentic @@ -5656,14 +3301,11 @@ broken-packages: - oscpacking - oset - Oslo-Vectize - - OSM - osm-conduit - - osm-download - oso2pdf - osx-ar - ot - OTP - - otp-authenticator - ottparse-pretty - overloaded - overloaded-records @@ -5680,92 +3322,67 @@ broken-packages: - packman - packunused - pacman-memcache - - padKONTROL - pads-haskell - pagarme - - PageIO - pagure-hook-receiver - Paillier - - pairing - palette - - pan-os-syslog - - panda + - PandocAgda - pandoc-citeproc - - pandoc-csv2table - pandoc-filter-graphviz - pandoc-filter-indent - pandoc-include - - pandoc-japanese-filters - pandoc-lens - pandoc-markdown-ghci-filter - pandoc-placetable - - pandoc-plantuml-diagrams - pandoc-pyplot - pandoc-unlit - pandoc-utils - - PandocAgda - pang-a-lambda - pangraph - panpipe - pansite - pantry-tmp - - papa - - papa-base - papa-base-export - - papa-base-implement - - papa-export - - papa-implement - papa-include - papa-prelude - papa-prelude-core - papa-prelude-lens - papa-prelude-semigroupoids - papa-prelude-semigroups - - papa-semigroupoids - papa-semigroupoids-implement - paphragen - papillon - pappy - - paprika - - par-dual - paragon - - Paraiso - - Parallel-Arrows-Eden - parallel-tasks - - parameterized-utils - paranoia - parco - - parco-attoparsec - - parco-parsec - parcom-lib - - parconc-examples + - par-dual - pareto - - parochial - - parquet-hs - Parry - - parse-help - parseargs + - parsec2 + - parsec3 - parsec-free - parsec-parsers - parsec-pratt - - parsec2 - - parsec3 - parseerror-eq - parsely - - parser-combinators-tests - - parser-helper - parser241 + - parser-combinators-tests - parsergen + - parser-helper - parsers-megaparsec - - parsestar - parsimony - parsnip - partage - - partial-lens - partial-records - partly - passage - passman + - passman-core - PasswordGenerator - passwords - pasta @@ -5777,76 +3394,48 @@ broken-packages: - pathfindingcore - PathTree - patronscraper - - patterns - paypal-adaptive-hoops - paypal-api - paypal-rest-client - pb - - pb-next - pbc4hs - PBKDF2 - - pcap-enumerator - - pcapng + - pb-next - pcd-loader - - pcf - pcf-font - - pcf-font-embed - PCLT - - PCLT-DB - pcre-light-extra - - pdf-slave - - pdf-slave-template - - pdf-toolbox-content - - pdf-toolbox-core - - pdf-toolbox-document - - pdf-toolbox-viewer - pdfname + - pdf-slave-template - pdfsplit + - pdf-toolbox-viewer - pdftotext - pdynload - - peakachu - PeanoWitnesses - - pec - pecoff - pedersen-commitment - pedestrian-dag - peg - peggy - - pell - pencil - penntreebank-megaparsec - - penny - - penny-bin - - penny-lib - - penrose - - peparser - percent-encoder - perceptron - - perceptual-hash - peregrin - perf - - perf-analysis - PerfectHash - - perfecthash - perhaps - periodic - - periodic-client - - periodic-client-exe - periodic-common - - periodic-server - - perm - permutation - permutations - permute - - PermuteEffects - persist2er - Persistence - - persistent-audit - persistent-cereal - persistent-database-url + - persistent-discover - persistent-equivalence - - persistent-hssqlppp - - persistent-map - persistent-migration - persistent-mongoDB - persistent-mysql-haskell @@ -5856,82 +3445,51 @@ broken-packages: - persistent-redis - persistent-relational-record - persistent-template-classy - - persistent-test - - persistent-vector - persistent-zookeeper - persona - - persona-idp - pesca - - peyotls - - peyotls-codec - pez + - pgdl - pg-extras + - pgf2 - pg-harness - pg-harness-server - pg-recorder - pg-store - - pg-transact - - pgdl - - pgf2 - - pgsql-simple - pgstream - phasechange - phaser - phoityne - phone-numbers - phone-push - - phonetic-languages-examples - phonetic-languages-properties - - phonetic-languages-simplified-lists-examples - phonetic-languages-simplified-properties-lists - phonetic-languages-simplified-properties-lists-double - - phooey - - photoname - phraskell - Phsu - phybin - - pi-calculus - - pi-forall - - pi-hoole - pia-forward - - pianola + - pi-calculus - picedit - pickle - picologic - picoparsec - pictikz - - pier - pier-core - piet + - pi-forall - pig - - pinboard + - pi-hoole - pinch - - pinch-gen - pinchot - - ping - - pinpon - Pipe - - pipe-enumerator - pipes-async - - pipes-attoparsec-streaming - pipes-bgzf - - pipes-brotli - - pipes-cacophony - pipes-cereal - - pipes-cereal-plus - - pipes-conduit - pipes-core - - pipes-courier - pipes-errors - - pipes-extra - - pipes-files - - pipes-illumina - pipes-interleave - pipes-io - - pipes-key-value-csv - - pipes-mongodb - - pipes-p2p - - pipes-p2p-examples - pipes-protolude - pipes-rt - pipes-s3 @@ -5940,24 +3498,19 @@ broken-packages: - pipes-transduce - pipes-vector - pipes-zeromq4 - - pisigma - Piso - pit - - pitchtrack - pivotal-tracker - - pixel-printer - pixelated-avatar-generator - - pixiv + - pixel-printer - pkcs10 - pkcs7 - pkggraph - - pkgtreediff - plailude - plan-applicative - - plan-b - planar-graph + - plan-b - planb-token-introspection - - planet-mitchell - planet-mitchell-test - plankton - plat @@ -5965,88 +3518,45 @@ broken-packages: - PlayingCards - plist - plist-buddy - - plocketed - plot-gtk - - plot-gtk-ui - plot-gtk3 - - Plot-ho-matic + - plot-gtk-ui - plot-lab - - PlslTools - - plugins - plugins-auto - plugins-multistage - plumbers - plur - plural - plzwrk - - png-file - - pngload - pngload-fixed - pocket - - pocket-dns - - point-octree - pointedalternative - pointfree-fancy - pointful - pointless-haskell - - pointless-lenses - - pointless-rewrite - - poke - pokemon-go-protobuf-types - poker-eval - pokitdok - polar-configfile - polar-shader - - polh-lexicon - Pollutocracy - poly-cont - poly-control - - polydata - polydata-core - polynomial - - polysemy-chronos - - polysemy-conc - - polysemy-extra - - polysemy-fskvstore - - polysemy-http - - polysemy-kvstore-jsonfile - - polysemy-log - - polysemy-log-co - - polysemy-log-di - - polysemy-methodology - - polysemy-methodology-composite - - polysemy-optics - - polysemy-path - - polysemy-RandomFu - - polysemy-resume - - polysemy-test - - polysemy-time - - polysemy-vinyl - polysemy-zoo - - polyseq - polytypeable - - polytypeable-utils - - pomaps - - pomodoro - pomohoro - ponder - pong-server - - pontarius-xmpp - pool - pool-conduit - pop3-client - - popenhs - popkey - poppler - - porcupine-core - - porcupine-http - - porcupine-s3 - portager - porte - PortFusion - - ports - - poseidon - - poseidon-postgis - positron - posix-acl - posix-api @@ -6054,55 +3564,33 @@ broken-packages: - posix-waitpid - postcodes - postgres-embedded - - postgres-tmp - - postgres-websockets - postgresql-lo-stream - postgresql-named - - postgresql-query - postgresql-simple-bind - - postgresql-simple-migration - postgresql-simple-named - - postgresql-simple-queue - postgresql-simple-sop - - postgresql-simple-typed - postgresql-simple-url - - postgresql-syntax - - postgresql-tx-query - - postgresql-tx-squeal - - postgresql-tx-squeal-compat-simple - postgresql-typed-lifted + - postgres-tmp - postgrest-ws + - postgres-websockets - postie - - postmark - postmark-streams - postmaster - potato-tool - - potoki - - potoki-cereal - - potoki-conduit - potoki-core - - potoki-hasql - - potoki-zlib - - potrace-diagrams - powermate - powerpc - powerqueue-levelmem - - powerqueue-sqs - pprecord - PPrinter - pqc - - pqueue-mtl - - practice-room - praglude - preamble - precursor - - pred-set - - pred-trie - predicate-class - - predicate-transformers - predicate-typed - prednote - - prednote-test - prefork - pregame - preliminaries @@ -6115,106 +3603,69 @@ broken-packages: - presburger - present - press - - presto-hdbc - pretty-ghci - pretty-ncols - - pretty-types - - prettyprinter-lucid - prettyprinter-vty - - preview - prim-array - - prim-instances - - prim-ref - - primal - - primal-memory - primes-type + - prim-instances + - PrimitiveArray-Pretty - primitive-atomic - primitive-checked - - primitive-containers - primitive-convenience - primitive-foreign - primitive-indexed - primitive-maybe - primitive-simd - - primitive-sort - primitive-stablename - - PrimitiveArray-Pretty - - primula-board - - primula-bot + - prim-ref - pringletons - - print-debugger - printcess - - Printf-TH + - print-debugger - prints - - priority-queue - PriorityChansConverger - - ProbabilityMonads + - priority-queue - probable - - proc - process-conduit - - process-iterio + - processing - process-leksah - process-listlike - - process-progress - - process-qq - - process-streaming - - processing - processmemory - procrastinating-variable - procstat - - producer - - prof-flamegraph - - prof2dot - prof2pretty + - prof-flamegraph - profunctor-monad - progress - - progress-meter - - progress-reporting - - progressbar - progression - progressive + - progress-meter + - progress-reporting - proj4-hs-bindings - - project-m36 - projectile - - prolens - prolog-graph - - prologue - - prolude - - prometheus-effect - promise - pronounce - proof-combinators - - propane - Proper - properties - property-list - - proplang - prosidy - - prosidyc - prosper - proteaaudio - proteaaudio-sdl - - proteome + - protocol + - protocol-buffers-fork - proto-lens-arbitrary - proto-lens-combinators - - proto-lens-descriptors - proto-lens-optparse - - proto3-suite - - proto3-wire - - protobuf-native - - protocol - - protocol-buffers-descriptor-fork - - protocol-buffers-fork - protolude-lifted - - proton - proton-haskell - prototype - prove-everywhere-server - provenience - proxy-kindness - proxy-mapping - - psc-ide - - pseudo-boolean - pseudo-trie - PTQ - ptr-poker @@ -6222,50 +3673,26 @@ broken-packages: - publish - pubnub - pubsub - - puffytools - pugixml - - Pugs - - pugs-compat - pugs-DrIFT - - pugs-hsregex - PUH-Project - - punkt - - Pup-Events - - Pup-Events-Demo - Pup-Events-Server - - puppetresources - - pure-cdb - pure-io - pure-priority-queue - - pure-priority-queue-tests - - pure-zlib - - purescheme-wai-routing-core - - purescript - - purescript-ast - purescript-cst - - purescript-iso - - purescript-tsd-gen - - push-notifications - - push-notify - - push-notify-apn - - push-notify-ccs - - push-notify-general + - pure-zlib - pusher-haskell - pusher-ws - pushme + - push-notifications - putlenses - - puzzle-draw - - puzzle-draw-cmdline - - pvd - pyffi - pyfi - python-pickle - q4c12-twofinger - qc-oi-testgenerator - qd - - qd-vec - qed - - qhs - qhull-simple - qif - QIO @@ -6273,77 +3700,36 @@ broken-packages: - qlinear - qnap-decrypt - qr-imager - - qr-repa - qsem - QuadEdge - QuadTree - quantfin - quantification - quantum-arrow - - quantum-random - quarantimer - qudb - - Quelea - quenya-verb - - queryparser - - queryparser-demo - - queryparser-hive - - queryparser-presto - - queryparser-vertica - - questioner - - queuelike - - quick-schema - QuickAnnotate - - quickbench - quickbooks - - quickcheck-arbitrary-template - - quickcheck-poly - quickcheck-property-comb - quickcheck-property-monad - - quickcheck-regex - - quickcheck-relaxng - quickcheck-rematch - quickcheck-report - - quickcheck-state-machine - - quickcheck-state-machine-distributed - - quickcheck-string-random - - quickcheck-webdriver - QuickCheckVariant + - quickcheck-webdriver - quickjs-hs - QuickPlot - quickpull + - quick-schema - quickset - Quickson - quickspec - - quicktest - quickwebapp - - quipper - - quipper-algorithms - - quipper-all - - quipper-cabal - quipper-core - - quipper-demos - - quipper-language - - quipper-libraries - - quipper-rendering - - quipper-tools - quipper-utils - quiver - - quiver-binary - - quiver-bytestring - - quiver-cell - - quiver-csv - - quiver-enumerator - - quiver-groups - - quiver-http - - quiver-instances - - quiver-interleave - - quiver-sort - quokka - quoridor-hs - - qux - - R-pandoc - - raaz - RabbitMQ - rad - radian @@ -6352,157 +3738,94 @@ broken-packages: - radix - rados-haskell - raft - - rail-compiler-editor - - rails-session - - rainbow-tests - - raketka - rakhana - rakuten - - ralist - - rallod - raml - - rand-vars - randfile - rando - random-access-list - random-derive - - random-eff - - random-effin - - random-hypergeometric - - random-stream - RandomDotOrg + - random-eff + - random-stream + - rand-vars - Range - - range-set-list - - range-space - rangemin - - Ranka + - range-set-list - rapid - rapid-term - - rasa - - rasa-example-config - - rasa-ext-bufs - - rasa-ext-cmd - - rasa-ext-cursors - - rasa-ext-files - - rasa-ext-logger - - rasa-ext-slate - - rasa-ext-status-bar - - rasa-ext-style - - rasa-ext-views - - rasa-ext-vim - rascal - Rasenschach - - rating-chgk-info - rational-list - rattle - rattletrap - raven-haskell-scotty - - raw-feldspar - - rawr - raz - - razom-text-util - - rbr - rbst - - rc - rclient - - rdioh - react-flux - - react-flux-servant - react-haskell - - react-tutorial-haskell-server - reaction-logic - reactive-bacon - - reactive-balsa - reactive-banana - - reactive-banana-automation - - reactive-banana-bunch - - reactive-banana-gi-gtk - - reactive-banana-sdl - - reactive-banana-sdl2 - - reactive-banana-threepenny - - reactive-banana-wx - - reactive-fieldtrip - - reactive-glut - - reactive-jack - - reactive-midyim - reactive-thread - - reactor + - react-tutorial-haskell-server + - readability - read-bounded - read-ctags - read-io - - readability - readline - - readline-statevar - readme-lhs - - readpyc - readshp - really-simple-xml-parser - - reanimate - reanimate-svg - reasonable-lens - record - - record-aeson - record-encode - - record-gl - - record-preprocessor - - record-syntax - records - - records-th - - recursion-schemes - - recursion-schemes-ext - recursors - red-black-record - - reddit - redis-hs - redis-simple - redland - Redmine - - reduce-equations - reedsolomon - reenact - - Ref - ref - - ref-mtl + - Ref - refcount - Referees - references - - refh - refined-http-api-data - reflection-extras - - reflex-animation - - reflex-backend-socket - - reflex-backend-wai - reflex-basic-host + - reflex-dom-contrib + - reflex-dom-helper + - reflex-dom-helpers - reflex-dom-retractable - reflex-dom-svg - reflex-dynamic-containers - reflex-fsnotify - reflex-gadt-api - - reflex-ghci - reflex-gi-gtk - reflex-gloss - - reflex-gloss-scene + - reflex-jsx - reflex-libtelnet - - reflex-localize - - reflex-localize-dom - reflex-orphans - - reflex-process - reflex-sdl2 - reflex-transformers - reflex-vty + - ref-mtl - reformat - refractor - refresht - - refurb - reg-alloc - - reg-alloc-graph-color - - regex-deriv - regex-dfa - regex-generator - regex-parsec - - regex-pcre-text - - regex-pderiv - regex-posix-unittest + - regexpr-symbolic + - regexqq - regex-tdfa-pipes - regex-tdfa-quasiquoter - regex-tdfa-rc @@ -6511,26 +3834,12 @@ broken-packages: - regex-tdfa-utf8 - regex-tre - regex-type - - regex-wrapper - - regex-xmlschema - - regexp-tries - - regexpr-symbolic - - regexqq - - regional-pointers - regions - - regions-monadsfd - - regions-monadstf - - regions-mtl - register-machine-typelevel - registry - - registry-hedgehog - regress - regression-simple - regular - - regular-extras - - regular-web - - regular-xmlpickler - - reheat - rehoo - rei - reified-records @@ -6539,184 +3848,94 @@ broken-packages: - relapse - relational-postgresql8 - relational-query-postgresql-pure - - relative-date - relevant-time - reload - remark - remarks - remote - remote-debugger - - remote-json - - remote-json-client - - remote-json-server - remote-monad - - remotion - - render-utf8 - reorder-expression - repa-algorithms - - repa-array - repa-bytestring - - repa-convert - repa-devil - repa-eval - - repa-examples - - repa-flow - repa-linear-algebra - - repa-plugin - repa-scalar - repa-series - - repa-stream - - repa-v4l2 - repl - RepLib - replica - - replicant - ReplicateEffects - repo-based-blog - - repr - representable-functors - - representable-tries - - reprinter - reproject - - req-conduit - - req-oauth2 - - req-url-extra - reqcatcher + - req-conduit - request-monad - - rere - - rescue + - req-url-extra - reserve - reservoir - resin - - resistor-cube - resolve - resolve-trivial-conflicts - resource-effect - resource-embed - - resource-pool-catchio - - resource-simple - - respond - - rest-client - - rest-core - - rest-example - - rest-gen - - rest-happstack - - rest-snap - - rest-stringmap - - rest-types - - rest-wai - restartable - - restful-snap - - restricted-workers - restyle - rethinkdb - rethinkdb-client-driver - - rethinkdb-model - rethinkdb-wereHamster - retryer - reverse-geocoding - reversi - ReviewBoard - - rewrite - rewrite-inspector - - rewriting - - rezoom - - rfc - - rfc-env - - rfc-http-client - rfc-prelude - - rfc-psql - - rfc-redis - - rfc-servant - - rg - rhbzquery - - rhythm-game-tutorial - - rib - ribbit + - ribosome - RichConditional - ridley - - ridley-extras - riemann - riff - ring-buffer - - ring-buffers - - rio-process-pool - - riot - - risc-v - - risc386 - riscv-isa - Ritt-Wu - rivers - - rivet - rivet-migration - rivet-simple-deploy - RJson - - rl-satton - - Rlang-QQ - rlglue - RLP - - rlwe-challenges - - rmonad - - RMP - - RNAdesign - - RNAdraw - - RNAFold - - RNAFoldProgs - - RNAlien - - RNAwolf - - rncryptor - - rob + - rl-satton - robin - robots-txt - roc-cluster - - roc-cluster-demo - - rock - - rocksdb-haskell - - rocksdb-haskell-jprupp - - rocksdb-query - roku-api - rollbar - - rollbar-cli - rollbar-client - rollbar-hs - - rollbar-wai - - rollbar-yesod - roller - - RollingDirectory - ron-rdt - - ron-schema - - ron-storage - rope - - rose-trees - - rose-trie - rosebud - - roshask + - rose-trees - rosmsg - - rosmsg-bin - rosso - rotating-log - - rounded - - rounded-hw - rounding - roundtrip-aeson - - roundtrip-xml - - route-planning - rowrecord - - rpc + - R-pandoc - rpc-framework - - rpf - rpm - rpmbuild-order - rrule - - rsagl - - rsagl-frp - - rsagl-math - rspp - rss - - rss-conduit - rss2irc - rstream - - rtcm - RtMidi - rtnetlink - rtorrent-rpc @@ -6725,82 +3944,41 @@ broken-packages: - ruby-qq - ruff - ruin - - ruler - - ruler-core - - run-st - rungekutta - runhs - runmany - - runtime-arbitrary - - rv - rws - RxHaskell - - s-expression - - S3 - SableCC2Hs - safe-buffer-monad - safe-coerce - - safe-freeze - - safe-globals - - safe-lazy-io - - safe-length - - safe-numeric - - safe-plugins - - safe-printf - safecopy-migrate - safecopy-store + - safe-freeze + - safe-globals - safeint + - safe-lazy-io + - safe-length - safepath - - safer-file-handles - - safer-file-handles-bytestring - - safer-file-handles-text + - safe-plugins + - safe-printf - saferoute - - sai-shape-syb - sajson - - sak - salak-toml - Salsa - - saltine-quickcheck - - salvia - - salvia-demo - - salvia-extras - salvia-protocol - - salvia-sessions - - salvia-websocket - - samtools - - samtools-conduit - - samtools-enumerator - - samtools-iteratee - sandlib - sandman - sarasvati - - sarsi - - sasl - sat - - sat-micro-hs - satchmo - - satchmo-backends - - satchmo-examples - - satchmo-funsat - - satchmo-minisat - - satchmo-toysat - Saturnin - savage - sax - - SBench - sbvPlugin - - sc2-lowlevel - sc2-proto - - sc2-support - - sc3-rdu - - scalable-server - scaleimage - - SCalendar - scalendar - - scalp-webhooks - - scalpel-search - - scan-metadata - - scan-vector-machine - scanner-attoparsec - scc - scenegraph @@ -6808,57 +3986,36 @@ broken-packages: - schedevr - schedule-planner - schedyield - - schema - schemas - - schematic - - scholdoc - - scholdoc-citeproc - - scholdoc-texmath - scholdoc-types - - sci-ratio - SciBaseTypes - scidb-hquery - - scientific-notation - - SciFlow - - SciFlow-drmaa - - scion - - scion-browser + - sci-ratio - scons2dot - - scope - - scope-cairo - scottish - scotty-binding-play - scotty-blaze - scotty-fay - scotty-form - scotty-format - - scotty-hastache - scotty-params-parser - scotty-resource - scotty-rest - scotty-session - scotty-tls - scotty-view - - scp-streams - - scrabble-bot - - scrapbook - scrapbook-core - scrape-changes - ScratchFs - script-monad - - SCRIPTWriter - scrobble - - Scurry - scythe - scyther-proof - - sde-solver - sdl2-cairo-image - sdl2-compositor - sdl2-fps - sdr - seakale - - seakale-postgresql - - seakale-tests - sec - secdh - seclib @@ -6867,78 +4024,41 @@ broken-packages: - secp256k1-haskell - secp256k1-legacy - secret-santa - - secrm - - secure-sockets - SecureHash-SHA3 + - secure-sockets - secureUDP - - sednaDBXML - - seitz-symbol - selectors - - SelectSequencesFromMSA - selenium - - selenium-server - - self-extract - selinux - semantic-source - Semantique - semdoc - - semi-iso - semialign-extras - semibounded-lattices - Semigroup - semigroupoids-syntax - semigroups-actions - - semiring - - semiring-num - sendgrid-haskell - sendgrid-v3 - sensei - - sensenet - sensu-run - - sentence-jp - sentry - - seonbi - - seqaid - SeqAlign - - seqloc - - seqloc-datafiles - sequent-core - - sequor - serialize-instances - serialport - serokell-util - - serpentine - - serv - - serv-wai - servant-aeson-specs - servant-auth-cookie - - servant-auth-docs - servant-auth-hmac - - servant-auth-token - - servant-auth-token-acid - servant-auth-token-api - - servant-auth-token-leveldb - - servant-auth-token-persistent - - servant-auth-token-rocksdb - - servant-auth-wordpress - servant-avro - - servant-benchmark - - servant-cassava - - servant-checked-exceptions - - servant-checked-exceptions-core - - servant-cli - servant-client-js - - servant-client-namedargs - - servant-csharp - servant-db - - servant-db-postgresql - servant-dhall - servant-docs-simple - - servant-ede - servant-ekg - servant-elm - - servant-event-stream - - servant-examples - servant-fiat-content - servant-generate - servant-generic @@ -6946,210 +4066,130 @@ broken-packages: - servant-haxl-client - servant-hmac-auth - servant-http-streams - - servant-http2-client - - servant-iCalendar - servant-jquery - servant-js - servant-JuicyPixels - servant-kotlin - - servant-matrix-param - servant-mock - - servant-multipart - servant-namedargs - servant-nix - servant-pagination - servant-pandoc - - servant-polysemy - servant-pool - - servant-postgresql - servant-proto-lens - servant-purescript - servant-pushbullet-client - servant-py - servant-quickcheck - - servant-rawm-client - - servant-rawm-docs - servant-reason - servant-reflex - servant-router - servant-scotty - servant-seo - - servant-serf - - servant-server-namedargs - servant-smsc-ru - - servant-snap - servant-static-th - servant-streaming - - servant-streaming-client - - servant-streaming-docs - - servant-streaming-server - - servant-swagger-tags - servant-to-elm - - servant-waargonaut - servant-yaml - servant-zeppelin - - servant-zeppelin-client - - servant-zeppelin-server - - servant-zeppelin-swagger - server-generic - - serversession - - serversession-backend-acid-state - serversession-backend-persistent - serversession-backend-redis - - serversession-frontend-snap - - serversession-frontend-wai - serversession-frontend-yesod - services - ses-html-snaplet - SessionLogger - sessions - sessiontypes - - sessiontypes-distributed - Set - - set-of - - set-with - - setdown - setgame + - set-of - setoid - setters + - set-with - sexp - - sexp-grammar - sexpr-parser - sext - SFML - - SFML-control - sfmt - sfnt2woff - - SFont - SG - sgd - - SGdemo - - sgf - SGplus - - sgrep - sh2md - - sha-streams - - sha1 - shade - shadower - shake-bindist + - shakebook - shake-cabal-build - shake-dhall - shake-extras - shake-minify - - shake-minify-css - shake-pack - shake-path - shake-persist - - shakebook - - shaker - shakespeare-babel - shakespeare-sass - - shapefile - - shapely-data - shared-buffer - shared-fields + - sha-streams - she - - shelduck - - shell-pipe - Shellac - - Shellac-compatline - - Shellac-editline - - Shellac-haskeline - - Shellac-readline - shellish - shellmate - - shellmate-extras + - shell-pipe - shimmer - shine-examples - shivers-cfg - shoap - shopify - - shortcut-links - shorten-strings - - ShortestPathProblems - show-prettyprint - - showdown - - Shpadoinkle-backend-pardiff - Shpadoinkle-backend-snabbdom - - Shpadoinkle-backend-static - - Shpadoinkle-developer-tools - - Shpadoinkle-disembodied - - Shpadoinkle-examples - - Shpadoinkle-html - - Shpadoinkle-router - Shpadoinkle-streaming - - Shpadoinkle-template - - Shpadoinkle-widgets - - shpider - - shuffle - shwifty - - si-clock - - sibe - sifflet - sifflet-lib - - sigma-ij - - sign - - signable - - signals - - signature - signed-multiset - - signify-hs - - silkscreen - - silvi - simd - - simgi - simple-actors + - simpleargs - simple-atom - simple-bluetooth - - simple-c-value - simple-conduit - simple-config + - simpleconfig - simple-css - simple-download - simple-eval - - simple-firewire - simple-genetic-algorithm - simple-index - - simple-log-syslog + - simpleirc - simple-logging + - simple-log-syslog - simple-money - simple-neural-networks - - simple-nix - - simple-pascal + - simplenote - simple-pipe + - simpleprelude - simple-rope - simple-server + - simplesmtpclient - simple-sql-parser - simple-stacked-vm + - simplest-sqlite - simple-tabular - simple-tar - simple-ui - simple-units - simple-vec3 - simple-zipper - - simpleargs - - simpleconfig - - SimpleGL - - simpleirc - - simpleirc-lens - - SimpleLog - - simplenote - - simpleprelude - - SimpleServer - - simplesmtpclient - - simplest-sqlite - - simseq - singleton-dict - - singleton-typelits - - singletons-base - singletons-th + - singleton-typelits - singnal - singular-factory - sink - - siphon - - siren-json - - sirkel - sitepipe - sixfiguregroup - sized-grid @@ -7159,162 +4199,97 @@ broken-packages: - sjsp - SJW - skeletal-set - - skeleton - - skeletons - skell - skemmtun - skews - skulk - - skylark-client - skylighting-lucid - skype4hs - slack - slack-notify-haskell - slack-verify - - slack-web - slave-thread - sliceofpy - - slidemews - Slides - slim - - slip32 - sloane - - slot-lambda - sloth + - slot-lambda - slug - slugify - - slynx - - small-bytearray-builder - smallarray - smallcheck-kind-generics - smallcheck-laws - smallcheck-lens - smallpt-hs - - smallstring - smap - smartcheck - smartconstructor - smartGroup - - smartword - - smcdel - sme - smerdyakov - smiles - - smith - - smith-cli - - smith-client - - Smooth - smsaero - - smt-lib - smt2-parser + - smt-lib - SmtLib - smtlib2 - - smtlib2-debug - - smtlib2-pipe - - smtlib2-quickcheck - - smtlib2-timing - - smtp-mail-ng - SMTPClient + - smtp-mail-ng - smtps-gmail - smuggler - smuggler2 - snake - snake-game - snap-accept - - snap-auth-cli - snap-blaze-clay - snap-configuration-utilities - - snap-elm - snap-error-collector - - snap-extras - - snap-routes - - snap-stream - - snap-testing - - snap-utils - - snap-web-routes - snaplet-acid-state - - snaplet-actionlog - snaplet-amqp - - snaplet-auth-acid - - snaplet-coffee - snaplet-css-min - snaplet-customauth - snaplet-environments - snaplet-fay - - snaplet-hasql - - snaplet-haxl - - snaplet-hdbc - snaplet-hslogger - snaplet-influxdb - - snaplet-lss - - snaplet-mandrill - - snaplet-mongoDB - snaplet-mongodb-minimalistic - - snaplet-mysql-simple - - snaplet-oauth - snaplet-persistent - snaplet-postgresql-simple - - snaplet-postmark - - snaplet-purescript - - snaplet-recaptcha - - snaplet-redis - - snaplet-redson - - snaplet-rest - - snaplet-riak - snaplet-sass - snaplet-scoped-session - - snaplet-sedna - snaplet-ses-html - snaplet-sqlite-simple - - snaplet-sqlite-simple-jwt-auth - - snaplet-stripe - - snaplet-tasks - snaplet-typed-sessions - - snaplet-wordpress - snappy-conduit - - snappy-iteratee - - sndfile-enumerators + - snap-routes + - snap-stream + - snap-testing + - snap-web-routes - sneakyterm - SNet - snipcheck - - snm - - snmp - snorkels - - snow-white - - snowflake-core - - snowflake-server - snowtify - - Snusmumrik - - SoccerFun - - SoccerFunGL - socket-activation - - socket-io - - socket-sctp - - socket-unix - socketed - socketio - - sockets - sockets-and-pipes + - socket-sctp - socketson + - socket-unix - sodium - soegtk - softfloat-hs - solga - - solga-swagger - - solr - sonic-visualiser - Sonnex - SoOSiM - sorted - sorting - sorty - - souffle-dsl - souffle-haskell - sound-collage - - sounddelay - - soundgen - - source-code-server - - SourceGraph - sousit - soyuz - SpaceInvaders @@ -7322,109 +4297,62 @@ broken-packages: - SpacePrivateers - spake2 - spanout - - sparkle - - sparrow - spars - sparse - - sparse-lin-alg - - sparsebit - sparsecheck - - sparser - - spata + - sparse-lin-alg - special-functors - special-keys - - specialize-th - - species - - spectral-clustering - speculation - - speculation-transformers - - speechmatics - - spelling-suggest - - sphero - sphinx - - sphinx-cli - sphinxesc - - spice - - SpinCounter - - spir-v - spiros + - spir-v - splay - splaytree - - spline3 - - splines - splint - split-morphism - splitter - Spock - Spock-api-ghcjs - - Spock-auth - - Spock-lucid - - Spock-worker - spoonutil - spoty - Sprig - - sprinkles - spritz - - sproxy - - sproxy-web - - sproxy2 - spsa - spy - - sql-simple - - sql-simple-mysql - - sql-simple-pool - - sql-simple-postgresql - - sql-simple-sqlite - sqlcipher - sqlite - sqlite-simple-errors - - sqlite-simple-typed + - sql-simple - sqlvalue-list - sqsd-local - squeal-postgresql - - squeeze - - sr-extra - srcinst - sscan - - sscgi - ssh - ssh-tunnel - - sshd-lint - - sssp - - sstable - SSTG - st2 - stable-heap - stable-maps - stable-marriage - stable-memo - - stable-tree - - stack-bump - - stack-fix - - stack-hpc-coveralls - - stack-lib - - stack-network - - stack-prism - - stack-run - - stack-run-auto - - stack-type - - stack-wrapper - stack2cabal - stack2nix - - stackage - - stackage-build-plan - - stackage-cabal - stackage-cli - stackage-curator - stackage-metadata - - stackage-query - - stackage-sandbox - - stackage-setup - stackage-to-hackage - stackage-types - - stackage-upload - - stackage2nix + - stack-bump - stackcollapse-ghc + - stack-fix + - stack-lib + - stack-prism + - stack-run + - stack-type + - stack-wrapper - staged-gg - standalone-derive-topdown - standalone-haddock @@ -7435,18 +4363,13 @@ broken-packages: - state-bag - state-plus - state-record - - stateful-mtl - static-canvas - - static-closure - static-tensor - - static-text - statistics-dirichlet - statistics-fusion - statistics-hypergeometric-genvar - stats - statsd - - statsd-client - - statsdi - statvfs - stb-image-redux - stc-lang @@ -7461,186 +4384,113 @@ broken-packages: - stern-brocot - stgi - STL - - STLinkUSB - stm-chunked-queues - stm-firehose - stm-promise - stm-stats - - STM32-Zombie - - stmcontrol - stochastic - - StockholmAlignment - - stocks - Stomp - storable - storable-static-array - - storablevector-streamfusion - stp - str - Strafunski-ATermLib - - Strafunski-Sdf2Haskell - Strafunski-StrategyLib - StrappedTemplates - stratum-tool - - stratux - - stratux-demo - - stratux-http - stratux-types - - stratux-websockets - stream - - stream-fusion - - stream-monad - streamdeck - streamed - - streaming-base64 - - streaming-benchmarks - - streaming-brotli - - streaming-cassava - - streaming-concurrency + - stream-fusion - streaming-conduit - streaming-events - - streaming-fft - streaming-lzma - streaming-osm - streaming-pcap - streaming-png - - streaming-process - - streaming-sort - streaming-utils - streaming-with - streamly-fsnotify + - stream-monad - streamproc - - strelka - - strict-base-types - - strict-data - - strict-ghc-plugin - - strict-tuple-lens - StrictBench - StrictCheck + - strict-ghc-plugin - strictly + - strict-tuple-lens - string-isos - - string-quote - - string-typelits - stringlike + - string-quote - stringtable-atom - stripe - stripe-hs - stripe-http-streams - - stripe-scotty - stripe-signature - - stripe-wreq - strongswan-sql - - structural-induction - structural-traversal - - structured-mongoDB - structures - stt - stunclient - - stunts - - stutter - stylish-cabal - - stylist - stylized - - suavemente - - sub-state - - subhask - subleq-toolchain - submark - subsample - - substring-parser + - sub-state - subwordgraph - - successors - suffix-array - suffixarray - SuffixStructures - sugarhaskell - suitable - summoner - - summoner-tui - - sump - sunlight - sunroof-compiler - - sunroof-examples - - sunroof-server - - super-user-spark - superbubbles - - supercollider-ht - - supercollider-midi - - superconstraints - superevent - supermonad - supernova - supero + - super-user-spark - supervisor - supplemented - surjective - - sv - - sv-cassava - sv-core - - sv-svfactor - SVD2HS - svfactor - svg-builder-fork - - SVG2Q - - svg2q - svgcairo - - svgone - svgutils - svm-light-utils - svm-simple - svndump - swagger-petstore - swagger-test - - swapper - - swearjure - - sweet-egison - swf - swift-lda - swiss-ephemeris - - switch - - sws + - swisstable - syb-extras - - syb-with-class-instances-text - SybWidget + - syb-with-class-instances-text - syfco - - sylvia - sym - - sym-plot - symantic - - symantic-atom - symantic-cli - - symantic-http - - symantic-http-client - - symantic-http-demo - - symantic-http-pipes - - symantic-http-server - symantic-http-test - - symantic-lib - symantic-parser - symantic-xml - - symbiote - symbolic-link - symengine - symengine-hs - - symmetry-operations-symbols - sync - sync-mht - - syncthing-hs - - syntactic - - syntax - - syntax-attoparsec - - syntax-example - - syntax-example-json - - syntax-pretty - - syntax-printer - syntax-trees - syntax-trees-fork-bairyn - - SyntaxMacros - - syntaxnet-haskell - synthesizer - - synthesizer-llvm - - sys-process - Sysmon + - sys-process - system-canonicalpath - system-command - system-extra @@ -7649,93 +4499,52 @@ broken-packages: - system-linux-proc - system-locale - system-random-effect - - systemstats - - t-regex - - t3-client - t3-server - - ta - table - - table-layout - - table-tennis - tableaux - - Tables + - table-layout - tables + - Tables - tablestorage + - table-tennis - Tablify - tabloid - tabs - tag-bits - - tag-stream - tagged-exception-core - - tagged-list - - tagged-th - tagged-timers - taglib-api - tagsoup-ht - tagsoup-megaparsec - - tagsoup-navigate - tagsoup-parsec - tagsoup-selection - - tagstew - tai - tai64 - takahashi - Takusen - takusen-oracle - - tal - - tamarin-prover - - tamarin-prover-term - - tamarin-prover-theory - tamarin-prover-utils - Tape - tapioca - - target - - task - - task-distribution - TaskMonad - tasty-auto - - tasty-bdd - - tasty-checklist - tasty-fail-fast - tasty-grading-system - - tasty-groundhog-converters - tasty-hedgehog-coverage - - tasty-html - - tasty-integrate - - tasty-jenkins-xml - - tasty-laws - - tasty-lens - tasty-mgolden - - tasty-silver - tasty-stats - tasty-test-vector - - tateti-tateti - - Taxonomy - - TaxonomyTools - TBC - TBit - - tbox - tcache-AWS - - tccli - tcod-haskell - tcp - tcp-streams-openssl - - tdd-util - - tdigest-Chart - - tdlib - - tdlib-gen - - tdlib-types - tds - - TeaHS - teams - - techlab - teeth - telegram - telegram-api - - telegram-bot - - telegram-bot-simple - - telegram-raw-api - - telegram-types - teleport - teleshell - tellbot @@ -7743,56 +4552,42 @@ broken-packages: - template-default - template-haskell-util - template-hsml - - template-yj - templateify - templatepg + - template-yj - tempodb - temporal-csound - tempus - tensor - - tensor-safe - tensorflow - - tensorflow-core-ops - - tensorflow-logging - tensorflow-opgen - - tensorflow-ops - - term-rewriting - - termbox-banana + - tensor-safe - termbox-bindings - - terminal-text - termination-combinators - termplot + - term-rewriting - terntup - terraform-http-backend-pass - - terrahs - tersmu - - tesla + - testCom + - testcontainers - test-fixture - test-framework-doctest - test-framework-quickcheck - - test-framework-sandbox - test-framework-skip - test-framework-testing-feat - test-framework-th-prime - - test-karya - - test-pkg - - test-sandbox - - test-sandbox-compose - - test-sandbox-hunit - - test-sandbox-quickcheck - - test-shouldbe - - test-simple - - testbench - - testCom - - testcontainers - testloop - testpack - testpattern + - test-pkg - testrunner - - TeX-my-math + - test-sandbox + - test-shouldbe - tex2txt - texbuilder - texrunner + - text1 - text-all - text-and-plots - text-ascii @@ -7804,162 +4599,118 @@ broken-packages: - text-lips - text-markup - text-normal + - textocat-api - text-offset - - text-plus - text-position - text-register-machine - text-replace - - text-trie + - textual - text-utf8 - - text-utils - text-xml-qq - text-zipper-monad - - text1 - - textmatetags - - textocat-api - - textual - tfp-th - tftp - tga - - th-alpha - - th-build - - th-context - - th-dict-discovery - - th-fold - - th-format - - th-instance-reification - - th-instances - - th-kinds - - th-kinds-fork - - th-lego - - th-pprint - - th-sccs - - th-tc - - th-to-exp - - th-traced - - th-typegraph - thank-you-stars - - theatre + - th-build + - th-dict-discovery - thentos-cookie-session - Theora - theoremquest - - theoremquest-client + - th-fold + - th-format - thih - - thimk - Thingie + - th-instance-reification + - th-kinds + - th-kinds-fork + - th-lego - thock - thorn + - th-pprint - threadmanager - threepenny-editors - threepenny-gui-contextmenu - threepenny-gui-flexbox - thrift + - Thrift - throttled-io-loop + - th-sccs + - th-tc + - th-to-exp + - th-traced - thumbnail-plus - - thumbnail-polish - - tic-tac-toe - - tickle + - tianbar - TicTacToe - tictactoe3d - tidal-midi - - tidal-serial - tidal-vis - tie-knot - tiempo - tiger - tightrope - - tighttp - - timberc - - time-extras - - time-exts - - time-http - - time-io-access - - time-machine - - time-qq - - time-quote - - time-recurrence - - time-series - - time-series-lib - - time-w3c - - time-warp - timecalc + - time-extras + - time-machine - timemap - timeout - timeout-with-results - timeparsers - TimePiece - - timeprint + - time-qq + - time-quote + - time-recurrence + - time-series - timeseries + - time-series-lib - timeutils + - time-w3c - timezone-detect - timezone-olson-th - - timezone-unix - tini - tintin - - tiny-scheduler - TinyLaunchbury - - tinyMesh + - tiny-scheduler - tinytemplate - TinyURL - tinyXml - - tip-haskell-frontend - - tip-lib - - titan - titan-debug-yampa - titan-record-yampa - Titim - tkhs - tkyprof - - tls-extra - - tlynx - tmp-postgres - - tn - - to-haskell - - to-string-class - - to-string-instances - - toboggan - todo - - todos - tofromxml + - to-haskell - toilet - - token-limiter - - token-search - tokenify - tokenizer-streaming + - token-limiter + - token-search - tokstyle - - toktok - tokyocabinet-haskell - tokyotyrant-haskell - tomato-rubato-openal - toml - - tonatona-google-server-api - tonatona-persistent-postgresql - tonatona-persistent-sqlite - tonatona-servant - - too-many-cells - toodles - Top - - top - - topkata - torch - TORCS - - total-map + - to-string-class - TotalMap - touched - Tournament - - toxcore - - toxcore-c - toxiproxy-haskell - - toysolver - - tpar - - tpb - tptp - trace - trace-call - - trace-function-call - traced + - trace-function-call - tracetree - - tracing - tracing-control - tracked-files - tracker @@ -7967,402 +4718,241 @@ broken-packages: - traction - tracy - traildb - - trajectory - transactional-events - - transf - - transfer-db - - transformations - TransformeR - transformers-compose - - transformers-convert - transformers-lift - transformers-runnable - TransformersStepByStep - transient-universe - - transient-universe-tls - translatable-intset - translate - translate-cli - - trasa - - trasa-client - - trasa-extra - - trasa-form - - trasa-server - - trasa-th - traversal-template - travis - travis-meta-yaml - trawl - traypoweroff - treap - - tree-render-text - - tree-traversals - - TreeCounter - treemap - treemap-html - - treemap-html-tools + - tree-render-text - TreeStructures - - Treiber - - trek-app - - trek-db + - tree-traversals + - t-regex - tremulous-query - TrendGraph - trhsx - - triangulation - - TrieMap - - tries - trigger - trim - - trimpolya - tripLL - trivia - - trivial-constraint - tropical - tropical-geometry - true-name - - truelevel - - trurl - tsession - - tsession-happstack - - tsp-viz - tsparse + - tsp-viz - tsuntsun - tsvsql - - tsweb - ttask - tttool - tubes - tuntap - - tuntap-simple - - tup-functor - tuple-gen - - tuple-lenses - - tuple-morph - - tuple-ops - tupleinstances + - tuple-lenses - turing-machines - turing-music - - turingMachine - turtle-options - - TV - tweak - - twee - - tweet-hs - - twentefp-eventloop-graphics - - twentefp-eventloop-trees - - twentefp-graphs - - twentefp-rosetree - - twentefp-trees - twentefp-websockets - - twentyseven - twfy-api-client - twhs - - twidge - - twilight-stm - twilio - - twill - twine - twirp - - twitter - - twitter-conduit - - twitter-enumerator - twitter-feed - tx - - txt - txtblk - TYB - tyfam-witnesses - typalyze - - type-assertions - - type-cache - - type-cereal + - typeable-th - type-combinators - - type-combinators-quote - - type-combinators-singletons - - type-digits + - typed-encoding + - typedflow + - typedquery + - typed-wire - type-eq - type-fun + - typehash - type-indexed-queues - type-int - type-interpreter - type-level-bst - type-level-natural-number-induction - type-level-natural-number-operations + - typelevel-tensor - type-list + - TypeNat - type-of-html-static - - type-ord - - type-ord-spine-cereal + - typeparams - type-prelude - - type-sets + - typesafe-precure + - types-compat - type-settheory - type-spine - - type-structure - - type-sub-th - type-tree - type-unary - - typeable-th - - TypeClass - - typed-encoding - - typed-encoding-encoding - - typed-spreadsheet - - typed-streams - - typed-wire - - typedflow - - typedquery - - typehash - - TypeIlluminator - - typelevel - - typelevel-rewrite-rules - - typelevel-tensor - - TypeNat - - typenums - - typeparams - - types-compat - - typesafe-precure - - typescript-docs - typograffiti - - typson-beam - - typson-esqueleto - - typson-selda - tyro - - u2f - - uber - uberlast - - ucam-webauth - ucam-webauth-types - ucd - uconv - udp-conduit - udp-streaming - - uhc-light - - uhc-util - uhexdump - uhttpc - ui-command - - UMM - - unagi-bloomfilter - unamb-custom - - unbound - unbounded-delays-units - unboxed-containers - unboxed-references - unbreak - - unescaping-print - unfix-binders - - uni-events - - uni-graphs - - uni-htk - - uni-posixutil - - uni-reactor - - uni-uDrawGraph - - uni-util - - unicode-normalization - unicode-prelude - unicode-show - unicode-symbols - unicode-tricks - - uniform-io - - union + - uniform-fileio - union-map - uniprot-kb - uniqueid - uniquely-represented-sets - - uniqueness-periods-vector-examples - uniqueness-periods-vector-properties - units-attoparsec - unittyped - unitym-yesod + - uni-util - universal-binary - - universe - - universe-instances-base - - universe-instances-extended - - universe-instances-trans - - universe-th - - unix-fcntl - unix-handle - unix-process-conduit - unix-recursive - - unix-simple - unlifted-list - unliftio-messagebox - - unliftio-streams - unm-hip - unordered-containers-rematch - unordered-graphs - unordered-intmap - - unpack-funcs - unpacked-either - unpacked-maybe - - unpacked-maybe-numeric - - unpacked-these - - unpacked-validation - - unparse-attoparsec + - unpack-funcs - unroll-ghc-plugin - unsafely - - unscramble - unsequential - unused - uom-plugin - - up - Updater - uploadcare - upskirt - - urbit-airlock - - urbit-api - - urbit-hob - - ureader - - urembed - uri - uri-conduit - uri-encoder - - uri-enumerator - - uri-enumerator-file - uri-parse - uri-template - uri-templater - - url-bytes - - url-decoders - - url-generic - URLb - urlcheck - urldecode - - UrlDisp + - url-decoders - urldisp-happstack - urlencoded - - urlpath - - URLT + - url-generic - urn - urn-random - urxml - - usb - - usb-enumerator - - usb-hid - - usb-id-database - - usb-iteratee - - usb-safe - - userid - users-mysql-haskell - users-persistent - utf - utf8-prelude - utf8-validator - UTFTConverter - - util-exception - util-logict - util-plus - util-primitive - - util-primitive-control - util-universe - - uu-cco - - uu-cco-examples - - uu-cco-hut-parsing - - uu-cco-uu-parsinglib - uuagc-bootstrap - - uuagc-diagrams + - uu-cco - uuid-aeson - - uuid-bytes - - uuid-crypto + - uuid-orphans - uvector - - uvector-algorithms - uxadt - - v4l2 - - v4l2-examples - - vabal - vabal-lib - vacuum - - vacuum-cairo - - vacuum-graphviz - - vacuum-opengl - - vacuum-ubigraph - - valid-names - - validate-input - validated-types - Validation - validations + - valid-names - value-supply - vampire - var - varan - - variable-precision - variables + - variadic - variation + - vaultaire-common - vault-tool-server - vault-trans - - vaultaire-common - vcache - - vcache-trie - - vcard - vcatt - vcf - - vcsgui - vcswrapper - Vec-Boolean - Vec-OpenGLRaw - - Vec-Transform - vect-floating - - vect-floating-accelerate - vect-opengl - vector-bytestring - vector-clock - vector-conduit - - vector-endian - vector-fftw - vector-functorlazy - vector-heterogenous - - vector-instances-collections - vector-random - vector-read-instances - vector-space-map - vector-space-opengl - vector-space-points - vector-static - - vector-text - - vega-view - - venzone + - Vec-Transform - Verba - verbalexpressions - verdict - - verdict-json - - verifiable-expressions - verify - verilog - verismith - versioning - - versioning-servant - - vflow-types - - vfr-waypoints - - vgrep - vhd - vhdl - vicinity - - ViennaRNA-extras - viewprof - views - - vigilance - Villefort - - vimeta - vimus - vintage-basic - vinyl-json - vinyl-named-sugar - - vinyl-operational - vinyl-plus - vinyl-utils - vinyl-vectors - virthualenv - visibility - - vision - - visual-graphrewrite - - visual-prof - visualize-cbn + - visual-prof - vitrea - vk-aws-route53 - VKHS - - vocoder - - vocoder-audio - - vocoder-conduit - - vocoder-dunai - - voicebase - vowpal-utils - voyeur - vpq @@ -8372,21 +4962,13 @@ broken-packages: - vty-examples - vty-menu - vty-ui - - vty-ui-extras - - vulkan-api - - waargonaut - wacom-daemon - waddle - - wahsp - - wai-cli - - wai-devel - wai-git-http - wai-graceful - wai-handler-devel - wai-handler-fastcgi - - wai-handler-hal - wai-handler-scgi - - wai-handler-snap - wai-handler-webkit - wai-hmac-auth - wai-lens @@ -8394,22 +4976,15 @@ broken-packages: - wai-logger-buffered - wai-logger-prefork - wai-make-assets - - wai-middleware-cache - - wai-middleware-cache-redis - wai-middleware-catch - - wai-middleware-consul - - wai-middleware-content-type - wai-middleware-crowd - wai-middleware-delegate - wai-middleware-etag - wai-middleware-headers - wai-middleware-hmac-client - wai-middleware-preprocessor - - wai-middleware-rollbar - - wai-middleware-route - wai-middleware-static-caching - wai-middleware-travisci - - wai-middleware-validation - wai-rate-limit-redis - wai-request-spec - wai-responsible @@ -8422,120 +4997,73 @@ broken-packages: - wai-session-postgresql - wai-session-redis - wai-static-cache - - wai-thrift - - wai-throttler - waitfree + - wai-throttler - waitra - - waldo - wallpaper - warc - warp-dynamic - warp-grpc - warp-static - warp-systemd - - warped - - WashNGo - wasm - watchdog - watcher - watchit - - WAVE - - WaveFront - wavefront - wavefront-obj - - wavesurfer - - wavy - weak-bag - weather-api - - web-css - - web-encodings - - web-mongrel2 - - web-output - - web-page - - web-push - - web-rep - - web-routes-quasi - - web-routes-regular - - web-routes-transformers - - web-routing - - web3 - - webapi - webapp - - webauthn - WebBits - - WebBits-Html - - WebBits-multiplate - webcloud - - WebCont - webcrank - webcrank-dispatch - - webcrank-wai + - web-css - webdriver-angular - webdriver-snoy - - webdriver-w3c + - web-encodings - WeberLogic - webfinger-client - webify - webkit-javascriptcore - webmention + - web-output + - web-push - Webrexp - - webserver + - web-routes-quasi + - web-routes-transformers - webshow - websockets-rpc - webwire - WEditor - - WEditorBrick - - WEditorHyphen - weekdaze - - weighted - weighted-regexp - welshy - werewolf - - werewolf-slack - - what4 - Wheb - - wheb-mongo - - wheb-redis - - wheb-strapped - while-lang-parser - whim - whiskers - - whitespace - whois - why3 - wide-word - - wide-word-instances - WikimediaParser - - wikipedia4epub - - wild-bind-indicator - - wild-bind-task-x11 - windns - - windowslive - winerror - - winery - - winio - Wired - wires - wiring - witty - wkt - wkt-geom - - wl-pprint-ansiterm - - wl-pprint-extras - - wl-pprint-terminfo - - WL500gPControl - WL500gPLib - - wlc-hs + - wl-pprint-extras - WMSigner - - wobsurv - woe - woffex - wol - - wolf - - word - word2vec-model - - WordAlignment - - wordchoice - wordify - wordlist - WordNet @@ -8543,66 +5071,36 @@ broken-packages: - wordpass - wordpress-auth - wordsearch - - work-time - workdays - Workflow - - workflow-extra - workflow-osx - - workflow-pure - - workflow-types - workflow-windows + - work-time - wp-archivebot - - wraxml - - wrecker - - wrecker-ui - wreq-patchable - wreq-sb - - wright - - writer-cps-full - writer-cps-lens - writer-cps-monads-tf - writer-cps-morph - - ws - wsdl - wsedit - - wshterm - wsjtx-udp - - wss-client - wtk - - wtk-gtk - - wu-wei - - wumpus-basic - wumpus-core - - wumpus-drawing - - wumpus-microprint - - wumpus-tree - - WURFL - - wxAsteroids - - WXDiffCtrl - wxdirect - - wxFruit - - WxGeneric - - wxhnotepad - - wxSimpleCanvas - - wxturtle - - wyvern - - x-dsp - X11-extras - X11-rm - X11-xdamage - X11-xfixes - xchat-plugin - xcp - - xdcc - - xdot + - x-dsp - Xec - xenstore - xfconf - xformat - xhaskell-library - xhb - - xhb-atom-cache - - xhb-ewmh - xilinx-lava - xine - xing-api @@ -8611,108 +5109,64 @@ broken-packages: - xleb - xls - xlsior - - xlsx-tabular - xlsx-templater - - xml-catalog + - xml2json - xml-conduit-decode - xml-conduit-selectors - xml-conduit-stylist - - xml-enumerator - - xml-enumerator-combinators - xml-html-conduit-lens - - xml-monad - - xml-parsec - - xml-pipe - - xml-prettify - - xml-push - - xml-query - - xml-query-xml-conduit - - xml-query-xml-types - - xml-tydom-conduit - - xml-tydom-core - - xml2json - - xml2x - XmlHtmlWriter - - xmltv + - xml-parsec + - xml-prettify + - xml-query + - xml-tydom-core - XMMS - - xmms2-client - - xmms2-client-glib - xmonad-bluetilebranch - - xmonad-contrib-bluetilebranch - xmonad-contrib-gpl - xmonad-dbus - xmonad-eval - xmonad-vanessa - xmonad-windownames - - xmpipe - - XMPP - xor - - xorshift-plus - Xorshift128Plus - - xournal-builder - - xournal-convert - - xournal-parser - - xournal-render + - xorshift-plus - xournal-types - xrefcheck - xsact - - XSaiga - xsd - xslt - - xtc - xxhash - y0l0bot - yabi-muno - - Yablog - yackage - - YACPong - yahoo-finance-api - yahoo-finance-conduit - yahoo-prices - yahoo-web-search - yajl - - yajl-enumerator - yall - - yam - yam-config - - yam-datasource - - yam-logger - - yam-redis - - yam-servant - - yam-transaction - - yam-transaction-odbc - - yam-web - yaml-pretty-extras - - yaml-rpc - - yaml-rpc-scotty - - yaml-rpc-snap - - yaml-unscrambler - YamlReference + - yaml-rpc + - yampa2048 - yampa-glfw - yampa-gloss - yampa-glut - yampa-sdl2 - - yampa-test - - yampa2048 - YampaSynth + - yam-servant - yandex-translate - yaop - yap - yarr - - yarr-image-io - - yasi - - yavie - yaya-test - yaya-unsafe-test - - ycextra - - yeamer - yeller - - yeshql - yeshql-hdbc - yeshql-postgresql-simple - yesod-angular - yesod-angular-ui - - yesod-articles - yesod-auth-account - yesod-auth-account-fork - yesod-auth-bcrypt @@ -8720,57 +5174,38 @@ broken-packages: - yesod-auth-deskcom - yesod-auth-hmac-keccak - yesod-auth-kerberos - - yesod-auth-ldap - yesod-auth-ldap-mediocre - yesod-auth-ldap-native - - yesod-auth-lti13 - yesod-auth-nopassword - - yesod-auth-oauth2 - yesod-auth-pam - yesod-auth-smbclient - yesod-auth-zendesk - yesod-bootstrap - - yesod-colonnade - yesod-comments - yesod-content-pdf - - yesod-continuations - yesod-crud - yesod-crud-persist - yesod-datatables - yesod-dsl - - yesod-examples - yesod-fast-devel - - yesod-fay - yesod-filter - yesod-form-richtext - yesod-gitrev - yesod-goodies - - yesod-ip - yesod-job-queue - yesod-links - yesod-lucid - - yesod-mangopay - - yesod-markdown - - yesod-page-cursor - yesod-paginate - yesod-pagination - - yesod-paypal-rest - - yesod-platform - yesod-pnotify - yesod-pure - - yesod-purescript - yesod-raml - - yesod-raml-bin - - yesod-raml-docs - - yesod-raml-mock - yesod-recaptcha - yesod-routes - yesod-routes-flow - - yesod-routes-typescript - yesod-rst - yesod-s3 - yesod-sass - - yesod-session-redis - yesod-static-angular - yesod-static-remote - yesod-test-json @@ -8781,85 +5216,46 @@ broken-packages: - yggdrasil - yhccore - yhseq + - yices - yi-contrib - yi-monokai - yi-solarized - yi-spolsky - - yices - - yjftp - - yjftp-libs - - yoctoparsec - yoda - - Yogurt - - Yogurt-Standalone - - yoko - - york-lava - - yql - yst - - yu-auth - yu-core - - yu-launch - yu-tool - - yu-utils - - yuuko - - yx - yxdb-utils - - Z-Data - - Z-IO - - Z-MessagePack - - Z-YAML - z3-encoding - z85 - zabt - zampolit - - zasni-gerna - - zbar + - Z-Data - ZEBEDDE - zendesk-api - zenhack-prelude - zeno - - zephyr - - zerobin - - zeromq-haskell - - zeromq3-conduit - - zeromq3-haskell - zeromq4-clone-pattern - zeromq4-conduit - zeromq4-patterns - - zeroth + - zeromq-haskell - zettelkast - ZFS - zifter - - zifter-cabal - - zifter-git - - zifter-google-java-format - - zifter-hindent - - zifter-hlint - - zifter-stack - zigbee-znet25 - zip-conduit - zipedit - zipkin - - zipper - - zippo - - ziptastic-client - ziptastic-core - - zlib-enum - zm - ZMachine - - zmcat - zmidi-score - zoneinfo - zoom - - zoom-cache - - zoom-cache-pcm - - zoom-cache-sndfile - zoom-refs - - zoovisitor - zsdd - zsh-battery - zsyntax - ztar - - zuramaru - Zwaluw - zxcvbn-dvorak diff --git a/pkgs/development/haskell-modules/configuration-hackage2nix/main.yaml b/pkgs/development/haskell-modules/configuration-hackage2nix/main.yaml index fe22ee7ea6d..cc33944d1ee 100644 --- a/pkgs/development/haskell-modules/configuration-hackage2nix/main.yaml +++ b/pkgs/development/haskell-modules/configuration-hackage2nix/main.yaml @@ -104,6 +104,7 @@ extra-packages: - 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-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: peti: @@ -219,20 +220,22 @@ package-maintainers: - gitit - yarn-lock - yarn2nix + - large-hashable poscat: - hinit bdesham: - pinboard-notes-backup unsupported-platforms: + Allure: [ x86_64-darwin ] alsa-mixer: [ x86_64-darwin ] alsa-pcm: [ x86_64-darwin ] alsa-seq: [ x86_64-darwin ] AWin32Console: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] barbly: [ i686-linux, x86_64-linux, aarch64-linux, armv7l-linux ] bdcs-api: [ x86_64-darwin ] - bindings-sane: [ x86_64-darwin ] bindings-directfb: [ x86_64-darwin ] + bindings-sane: [ x86_64-darwin ] cut-the-crap: [ x86_64-darwin ] d3d11binding: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] DirectSound: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] @@ -242,8 +245,9 @@ unsupported-platforms: Euterpea: [ x86_64-darwin ] freenect: [ x86_64-darwin ] FTGL: [ x86_64-darwin ] - gi-dbusmenugtk3: [ x86_64-darwin ] + ghcjs-dom-hello: [ x86_64-darwin ] gi-dbusmenu: [ x86_64-darwin ] + gi-dbusmenugtk3: [ x86_64-darwin ] gi-ggit: [ x86_64-darwin ] gi-ibus: [ x86_64-darwin ] gi-ostree: [ x86_64-darwin ] @@ -256,8 +260,12 @@ unsupported-platforms: HFuse: [ x86_64-darwin ] hidapi: [ x86_64-darwin ] hommage-ds: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] + hpapi: [ x86_64-darwin ] HSoM: [ 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 ] libsystemd-journal: [ x86_64-darwin ] libtelnet: [ x86_64-darwin ] @@ -266,10 +274,10 @@ unsupported-platforms: lio-fs: [ x86_64-darwin ] logging-facade-journald: [ x86_64-darwin ] midi-alsa: [ x86_64-darwin ] - mpi-hs: [ aarch64-linux, x86_64-darwin ] mpi-hs-binary: [ aarch64-linux, x86_64-darwin ] mpi-hs-cereal: [ aarch64-linux, x86_64-darwin ] mpi-hs-store: [ aarch64-linux, x86_64-darwin ] + mpi-hs: [ aarch64-linux, x86_64-darwin ] mplayer-spot: [ aarch64-linux ] oculus: [ x86_64-darwin ] pam: [ x86_64-darwin ] @@ -279,7 +287,9 @@ unsupported-platforms: posix-api: [ x86_64-darwin ] Raincat: [ x86_64-darwin ] 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 ] rubberband: [ x86_64-darwin ] sbv: [ aarch64-linux ] @@ -290,21 +300,22 @@ unsupported-platforms: termonad: [ x86_64-darwin ] tokyotyrant-haskell: [ x86_64-darwin ] udev: [ x86_64-darwin ] + verifiable-expressions: [ aarch64-linux ] vrpn: [ x86_64-darwin ] + vulkan-utils: [ x86_64-darwin ] vulkan: [ i686-linux, armv7l-linux, x86_64-darwin ] VulkanMemoryAllocator: [ i686-linux, armv7l-linux, x86_64-darwin ] - vulkan-utils: [ x86_64-darwin ] webkit2gtk3-javascriptcore: [ x86_64-darwin ] Win32-console: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] Win32-dhcp-server: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] Win32-errors: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] Win32-extras: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] - Win32: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] Win32-junction-point: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] Win32-notify: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] Win32-security: [ i686-linux, x86_64-linux, x86_64-darwin, aarch64-linux, armv7l-linux ] - Win32-services: [ 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 ] xgboost-haskell: [ 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-painless - # these packages don't evaluate because they have broken (system) dependencies - - XML - - comark - - couch-simple + # These packages don‘t build because they use deprecated webkit versions. - diagrams-hsqml - - diagrams-reflex - dialog - - fltkhs-demos - - fltkhs-fluid-demos - - fltkhs-hello-world - - fltkhs-themes - - ghcjs-dom-hello - ghcjs-dom-webkit - - gi-javascriptcore - gi-webkit - - gi-webkit2 - - gi-webkit2webextension - - gsmenu - - haste-gapi - - haste-perch - - hbro - - hplayground - hs-mesos - hsqml - hsqml-datamodel - - hsqml-datamodel-vinyl - - hsqml-datemodel-vinyl - hsqml-demo-manic - - hsqml-demo-morris - - hsqml-demo-notes - hsqml-demo-notes - hsqml-demo-samples - - hsqml-morris - - hsqml-morris - hstorchat - - imprevu-happstack - - jsaddle-webkit2gtk - jsaddle-webkitgtk - jsc - lambdacat - - leksah - manatee-all - manatee-browser - manatee-reader - 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 - - tianbar - - trasa-reflex - - treersec - - wai-middleware-brotli - web-browser-in-haskell - webkit - webkitgtk3 diff --git a/pkgs/development/haskell-modules/configuration-hackage2nix/transitive-broken.yaml b/pkgs/development/haskell-modules/configuration-hackage2nix/transitive-broken.yaml index a8ccc4f3851..5e6f9510011 100644 --- a/pkgs/development/haskell-modules/configuration-hackage2nix/transitive-broken.yaml +++ b/pkgs/development/haskell-modules/configuration-hackage2nix/transitive-broken.yaml @@ -3,120 +3,3301 @@ # It is supposed to list all haskellPackages that cannot evaluate because they # depend on a dependency marked as broken. dont-distribute-packages: - - AesonBson - - HGamer3D-API - - HGamer3D-CAudio-Binding - - HGamer3D-OIS-Binding - - HipmunkPlayground - - Holumbus-Distribution - - Holumbus-MapReduce - - Holumbus-Storage - - KiCS - - KiCS-debugger - - KiCS-prophecy - - RESTng - - ViennaRNA-bindings - - XML + + - 4Blocks + - a50 + - abcBridge + - AbortT-monadstf + - AbortT-mtl + - accelerate-arithmetic + - accelerate-fourier + - accelerate-typelits + - access-token-provider + - ac-machine-conduit + - acme-php - acme-safe - - aeson-bson + - acousticbrainz-client + - activehs + - actor + - AC-Vector-Fancy + - addy + - adhoc-network + - adict + - ADPfusionForest + - ADPfusionSet + - adp-multi-monadiccp + - Advgame + - Advise-me + - aern2-real + - AERN-Net + - AERN-Real + - AERN-Real-Double + - AERN-Real-Interval + - AERN-RnToRm + - AERN-RnToRm-Plot + - aeson-native + - afv + - agda-server + - agda-snippets-hakyll + - agentx + - aip + - airship + - aivika-distributed + - algebra-checkers + - algebra-driven-design + - algebra-sql + - algolia + - AlgoRhythm + - AlignmentAlgorithms + - alms + - alpha + - alsa-gui + - alsa-pcm-tests + - alsa-seq-tests + - amazon-emailer-client-snap + - ampersand + - amqp-streamly + - analyze-client + - anatomy + - AndroidViewHierarchyImporter + - animate-example + - animate-frames + - animate-preview + - animate-sdl2 + - annah + - Annotations + - anonymous-sums-tests + - antagonist + - anticiv + - antlrc + - apelsin + - apiary + - apiary-authenticate + - apiary-clientsession + - apiary-cookie + - apiary-eventsource + - apiary-helics + - apiary-http-client + - apiary-logger + - apiary-memcached + - apiary-mongoDB + - apiary-persistent + - apiary-purescript + - apiary-redis + - apiary-session + - apiary-websockets + - api-rpc-pegnet + - apis + - api-yoti + - apotiki + - ApplePush - approx-rand-test - - barley - - bson-mapping + - arbor-monad-metric-datadog + - arch-hs + - archlinux-web + - arduino-copilot + - arff + - arghwxhaskell + - argon + - ariadne + - arithmetic-circuits + - array-forth + - arraylist + - ascii-table + - asic + - ASN1 + - assert4hs-hspec + - assert4hs-tasty + - assimp + - ast-monad-json + - astview + - atlassian-connect-core + - atmos-dimensional-tf + - atomic-primops-foreign + - atp + - AttoJson + - attoparsec-enumerator + - attoparsec-ip + - attoparsec-iteratee + - attoparsec-text-enumerator + - attoparsec-uri + - atuin + - audiovisual + - aura + - authoring + - AutoForms + - autonix-deps-kf5 + - avers + - avers-api + - avers-api-docs + - avers-server + - AvlTree + - avro-piper + - awesomium + - awesomium-glut + - aws-configuration-tools + - aws-dynamodb-conduit + - aws-dynamodb-streams + - aws-elastic-transcoder + - aws-kinesis + - aws-kinesis-client + - aws-kinesis-reshard + - aws-lambda + - aws-mfa-credentials + - aws-sdk + - aws-sdk-xml-unordered + - aws-sign4 + - aws-sns + - axiom + - azimuth-hs + - azure-functions-worker + - azure-service-api + - azure-servicebus + - babylon + - backblaze-b2-hs + - backdropper + - ballast + - bamboo + - bamboo-launcher + - bamboo-plugin-highlight + - bamboo-plugin-photo + - bamboo-theme-blueprint + - bamboo-theme-mini-html5 + - bamse + - bamstats + - Barracuda + - base16-lens + - base32-bytestring + - base62 + - base64-bytes + - baserock-schema + - BASIC + - batchd + - battlenet-yesod + - battleships + - bayes-stack + - bbi + - bdcs + - bdcs-api + - beam-automigrate + - beam-migrate + - beam-mysql + - beam-newtype-field + - beam-postgres + - beam-sqlite + - beam-th + - beautifHOL + - bech32-th + - bein + - belka + - BerlekampAlgorithm + - berp + - bff + - bglib + - billboard-parser + - billeksah-forms + - billeksah-main + - billeksah-pane + - binary-file + - binary-protocol-zmq + - binary-streams + - bindings-apr-util + - bindings-linux-videodev2 + - bindings-ppdev + - binding-wx + - binembed-example + - bioace + - bioalign + - Biobase + - BiobaseBlast + - BiobaseDotP + - BiobaseENA + - BiobaseEnsembl + - BiobaseFasta + - BiobaseFR3D + - BiobaseHTTP + - BiobaseHTTPTools + - BiobaseInfernal + - BiobaseMAF + - BiobaseTrainingData + - BiobaseTurner + - BiobaseTypes + - BiobaseVienna + - BiobaseXNA + - biofasta + - biofastq + - BioHMM + - bioinformatics-toolkit + - biophd + - biopsl + - biosff + - biostockholm + - bip32 + - birch-beer + - bird + - BirdPP + - bit-array + - bitcoin-address + - bitcoin-api + - bitcoin-api-extra + - bitcoin-block + - bitcoin-compact-filters + - bitcoind-regtest + - bitcoind-rpc + - bitcoin-keys + - bitcoin-rpc + - bitcoin-scripting + - bitcoin-tx + - bitcoin-types + - Bitly + - bitly-cli + - bitmaps + - bittorrent + - bla + - blakesum-demo + - BlastHTTP + - blastxml + - blatex + - blaze-builder-enumerator + - blaze-colonnade + - ble + - blink1 + - blip + - Blobs + - blogination + - BlogLiterately + - BlogLiterately-diagrams + - bloodhound-amazonka-auth + - bloxorz + - blubber + - bluetile + - blunt + - bno055-haskell + - bogre-banana + - bond-haskell + - bond-haskell-compiler + - bookkeeper-permissions + - Bookshelf + - boomslang + - boopadoop + - boots-cloud + - boots-web + - borel + - bowntz + - box + - box-csv + - box-socket + - breakout + - bricks + - bricks-internal-test + - bricks-parsec + - bricks-rendering + - bricks-syntax + - bronyradiogermany-streaming + - brotli-conduit + - brotli-streams + - b-tree + - btree + - buchhaltung + - buildbox-tools + - buildwrapper + - bulletproofs + - bulmex + - burnt-explorer + - bus-pirate + - buster-gtk + - buster-network + - butterflies - bv-sized-lens + - bytebuild + - bytehash + - bytelog + - bytesmith + - bytestring-read + - c0check + - cabal2arch + - cabal-bounds + - cabal-cache + - cabal-cargs + - cabalmdvrpm + - cabal-query + - cabalrpmdeps + - cabal-test + - cake + - cakyrespa + - cal3d-examples + - cal3d-opengl + - calc + - calculator + - caldims + - call + - camfort + - campfire + - candid + - canteven-http + - cao + - cap + - carboncopy + - CarneadesIntoDung + - car-pool + - cartel + - casadi-bindings + - casadi-bindings-control + - casadi-bindings-core + - casadi-bindings-ipopt-interface + - casadi-bindings-snopt-interface + - cash + - cassandra-cql + - cassandra-thrift + - cassy + - casui + - categorical-algebra + - category-extras + - CBOR + - CC-delcont-alt + - cctools-workqueue + - cef3-simple + - ceilometer-common + - celtchar + - cereal-enumerator + - cereal-io-streams + - cereal-streams + - certificate + - cfipu + - cflp + - cfopu + - cgrep + - chainweb-mining-client + - chakra + - chalkboard-viewer + - charade + - chart-cli + - Chart-fltkhs + - chart-svg + - chart-svg-various + - chart-unit + - cheapskate-terminal + - check-pvp + - chevalier-common + - chitauri + - choose-exe + - chorale-geo + - chp-mtl + - chp-plus + - chp-transformers + - chr-core + - chr-lang + - chromatin + - chu2 + - chunks + - ciphersaber2 + - citation-resolve + - citeproc-hs-pandoc-filter + - clac + - clafer + - claferIG + - claferwiki + - clash + - clash-ghc + - clash-ghc_1_4_1 + - clash-lib + - clash-lib_1_4_1 + - clash-multisignal - clash-prelude-quickcheck + - clash-systemverilog + - clash-verilog + - clash-vhdl + - classify-frog + - classy-miso + - clckwrks + - clckwrks-cli + - clckwrks-dot-com + - clckwrks-plugin-bugs + - clckwrks-plugin-ircbot + - clckwrks-plugin-mailinglist + - clckwrks-plugin-media + - clckwrks-plugin-page + - clckwrks-plugin-redirect + - clckwrks-theme-bootstrap + - clckwrks-theme-clckwrks + - clckwrks-theme-geo-bootstrap + - cless - click-clack + - clifford + - clippings + - clocked + - cloud-haskell + - cloud-seeder - cloudyfs + - clua + - ClustalParser + - clustertools + - clutterhs + - cmathml3 + - CMCompare + - cmptype + - cmv + - cnc-spec-compiler + - Coadjute + - codec + - codec-rpm + - codemonitor - cognimeta-utils + - coinbase-exchange + - colada + - collapse-duplication + - collection-json + - collections-base-instances + - co-log-polysemy-formatting + - color-counter + - colorless-http-client + - colorless-scotty + - colour-space + - columbia - comark + - Combinatorrent + - comic + - commsec-keyexchange - comonad-random + - ComonadSheet + - compact-mutable + - complexity + - computational-algebra + - concraft + - concraft-hr + - concraft-pl + - concrete-haskell + - concrete-haskell-autogen + - condor + - Condor + - conductive-hsc3 + - conductive-song + - conduit-vfs-zip + - confcrypt + - conferer-provider-dhall + - conferer-provider-yaml + - conferer-source-dhall + - conferer-source-yaml + - conffmt + - Configger + - configifier + - config-select + - configurator-ng + - constraint-manip + - constructible + - consumers + - container - containers-accelerate + - continuum + - continuum-client + - control + - control-monad-attempt + - control-monad-exception-monadsfd + - Control-Monad-MultiPass + - conversions + - convert + - convertible-ascii + - convertible-text + - coordinate + - copilot + - copilot-c99 + - copilot-cbmc + - copilot-language + - copilot-libraries + - copilot-theorem + - CoreFoundation + - coroutine-enumerator + - coroutine-iteratee + - couchdb-enumerator + - couch-simple + - CPBrainfuck + - CPL + - cprng-aes-effect + - cql-io-tinylog + - cqrs-example + - cqrs-memory + - cqrs-postgresql + - cqrs-sqlite3 + - cqrs-test + - cqrs-testkit + - craft + - craftwerk-cairo + - craftwerk-gtk + - craze + - crf-chain1 + - crf-chain1-constrained + - crf-chain2-generic + - crf-chain2-tiers + - criu-rpc + - crockford + - cron-compat + - cryptocipher + - crypto-conduit + - cryptoids + - cryptoids-class + - cryptol + - crystalfontz + - csg + - cspmchecker + - CSPM-cspm + - CSPM-Interpreter + - CSPM-ToProlog + - csv-enumerator + - ctpl + - cube + - cursedcsv + - cv-combinators + - cypher + - Dangerous + - dapi + - darcs-benchmark + - darcs-beta + - darcsden + - darcs-fastconvert + - DarcsHelpers + - darcswatch + - darkplaces-demo + - darkplaces-rcon-util + - dash-haskell + - data-accessor-monads-fd + - data-basic + - data-cycle + - datadog-tracing + - data-elf + - dataflow + - data-layer + - data-lens-fd + - data-lens-ixset + - data-lens-template + - data-object-json + - data-object-yaml + - data-result + - data-rtuple + - data-structure-inferrer + - date-conversions + - dbjava + - dbus-client + - ddate + - ddc-build + - ddc-core + - ddc-core-babel + - ddc-core-eval + - ddc-core-flow + - ddc-core-llvm + - ddc-core-salt + - ddc-core-simpl + - ddc-core-tetra + - ddc-driver + - ddci-core + - ddc-interface + - ddc-source-tetra + - ddc-tools + - ddc-war + - debug + - debug-trace-var + - decidable + - decimal-arithmetic + - dedukti + - deeplearning-hs + - deepzoom + - defargs + - DefendTheKing - definitive-graphics + - deka-tests + - delaunay + - delicious + - delimited-text + - delimiter-separated + - delta + - delta-h + - dependent-state + - dephd + - dep-t-advice + - deptrack-devops + - deptrack-dot + - dequeue + - derive-IG + - detour-via-uom + - devtools + - dewdrop + - dfinity-radix-tree + - dhall-docs + - dhcp-lease-parser + - dia-functions + - diagrams-braille + - diagrams-builder + - diagrams-haddock + - diagrams-html5 + - diagrams-pandoc + - diagrams-pgf + - diagrams-reflex + - diagrams-wx + - DifferenceLogic + - difference-monoid + - digestive-functors-hsp + - dingo-core + - dingo-example + - dingo-widgets + - diplomacy + - diplomacy-server + - dirfiles + - discogs-haskell + - discord-gateway + - discord-hs + - discord-register + - discord-rest + - DisTract + - distributed-process-async + - distributed-process-azure + - distributed-process-client-server + - distributed-process-ekg + - distributed-process-execution + - distributed-process-extras + - distributed-process-fsm + - distributed-process-lifted + - distributed-process-monad-control + - distributed-process-p2p + - distributed-process-platform + - distributed-process-registry + - distributed-process-simplelocalnet + - distributed-process-supervisor + - distributed-process-systest + - distributed-process-task + - distributed-process-tests + - distributed-process-zookeeper + - distribution-plot + - dixi + - dl-fedora + - dmenu-pkill + - dmenu-pmount + - dmenu-search + - DMuCheck + - DnaProteinAlignment + - doc-review + - DocTest + - doi + - DOM + - domain + - domain-core + - domain-optics + - dow + - download-media-content + - DP + - dph-examples + - dph-lifted-base + - dph-lifted-copy + - dph-lifted-vseg + - dph-prim-interface + - dph-prim-par + - dph-prim-seq + - DrHylo + - dropbox-sdk + - dropsolve + - DSH + - dsh-sql + - dsmc-tools + - DSTM + - dtd + - dumb-cas + - Dust + - Dust-tools + - Dust-tools-pcap + - dvda + - dynamic-cabal + - dynamic-plot + - dynobud + - DysFRP-Cairo + - DysFRP-Craftwerk + - eccrypto-ed25519-bindings - ecdsa + - edenskel + - edentv + - edge + - edges + - editable + - EditTimeReport - effective-aspects-mzv + - egison + - egison-pattern-src-haskell-mode + - egison-pattern-src-th-mode + - egison-quote + - egison-tutorial + - elerea-examples - eliminators_0_8 + - elliptic-curve + - elsa + - emacs-keys + - email + - emailparse + - embeddock + - embeddock-example + - embroidery + - engine-io-growler + - entangle + - EntrezHTTP + - enumerate + - enumerate-function + - enumerator-fd + - enumerator-tf + - ephemeral + - erf-native + - eros-client + - eros-http + - error-message + - errors-ext + - ersatz-toysat + - esotericbot + - EsounD + - estreps + - Etage-Graph + - EtaMOO + - Eternal10Seconds + - eternity + - eternity-timestamped + - ether + - Etherbunny + - ethereum-analyzer + - ethereum-analyzer-cli + - ethereum-analyzer-webui + - ethereum-client-haskell + - ethereum-merkle-patricia-db + - evdev-streamly + - eventful-postgresql + - eventful-sqlite + - event-monad + - EventSocket + - eventsource-geteventstore-store + - every-bit-counts + - exception-monads-fd + - exference + - expand + - expat-enumerator + - expiring-containers + - explicit-iomodes-bytestring + - explicit-iomodes-text + - explicit-sharing + - explore + - expressions-z3 + - extemp + - extensible-data + - extract-dependencies + - Facts + - factual-api + - fadno-braids + - FailureT + - fallingblocks + - falling-turnip + - family-tree + - fast-digits + - fastirc + - fault-tree + - fbrnch + - fcd + - FComp + - feature-flipper-postgres + - fedora-img-dl + - feed2lj + - feed2twitter + - feed-gipeda + - feed-translator + - fei-base + - fei-cocoapi + - fei-dataiter + - fei-datasets + - fei-examples + - fei-modelzoo + - fei-nn + - feldspar-compiler + - feldspar-language + - FermatsLastMargin + - festung + - ffmpeg-tutorials + - ficketed + - fields + - FieldTrip + - filepath-crypto + - filepather + - FilePather + - filepath-io-access + - filesystem-enumerator + - Finance-Treasury + - find-clumpiness + - findhttp + - FiniteMap + - firstify + - FirstOrderTheory + - fixed-point-vector + - fixed-point-vector-space + - fixhs + - fix-parser-simple + - flac-picture + - flashblast + - flatbuffers + - flexiwrap + - flexiwrap-smallcheck + - Flippi + - flite + - flowdock-api + - flower + - flowsim - fltkhs-demos - fltkhs-fluid-demos + - fltkhs-fluid-examples - fltkhs-hello-world - fltkhs-themes + - fluent-logger - fluent-logger-conduit + - FM-SBLEX + - foldl-transduce-attoparsec + - follower + - foo + - Forestry + - formal + - FormalGrammars + - format + - format-status + - forml + - formlets + - formlets-hsp + - forth-hll + - fortran-src-extras + - foscam-directory + - foscam-sort + - Foster + - fp-ieee + - fplll + - fpnla-examples + - frame-markdown + - Frames-beam + - Frames-dsv + - Frank + - freekick2 + - freelude + - freer-converse + - free-theorems-counterexamples + - free-theorems-seq + - free-theorems-seq-webui + - free-theorems-webui + - frpnow-gloss + - frpnow-gtk + - frpnow-gtk3 + - frpnow-vty + - ftdi + - ftp-client-conduit + - FTPLine + - ftree + - ftshell + - funbot + - funbot-git-hook + - funcons-lambda-cbv-mp + - funcons-simple + - funcons-tools + - functional-arrow + - function-combine + - functor-combo + - funflow-nix + - funion + - funnyprint + - funsat + - fused-effects-squeal + - fwgl-glfw + - fwgl-javascript + - fxpak + - g2 + - g2q + - gact + - galois-fft + - Gamgine + - gargoyle-postgresql-connect + - gbu + - gdax + - gdiff-ig + - GeBoP + - gedcom + - geek + - geek-server + - gelatin-freetype2 + - gelatin-fruity + - gelatin-gl + - gelatin-sdl2 + - gelatin-shaders + - Genbank + - Gene-CluEDO + - generics-mrsop-gdiff + - genesis + - genesis-test + - GenI + - geniconvert + - geni-gui + - geniserver + - geni-util + - GenSmsPdu + - GenussFold + - geodetic + - geolite-csv + - getemx + - ghc-imported-from + - ghc-instances + - ghci-pretty + - ghcjs-hplay + - ghc-mod + - ghc-tags-plugin + - ghcup + - ghc-vis + - ght + - gi-cairo-again + - gi-gsk + - gi-gstpbutils - gi-gtk_4_0_4 + - git-fmt + - git-gpush + - github-webhook-handler-snap + - gitlib-cross + - gitlib-s3 + - git-object + - git-remote-ipfs + - givegif + - gladexml-accessor + - glazier + - glazier-pipes + - glazier-react + - glazier-react-examples + - glazier-react-widget + - GLFW-OGL + - GLFW-task + - global + - global-config + - glome-hs + - GlomeView + - gloss-banana + - gloss-devil + - gloss-examples + - gloss-sodium + - gmap + - gmndl + - gnome-desktop + - gnomevfs + - gnss-converters + - gnuidn + - goal-geometry + - goal-probability + - goal-simulation - goat - - gridfs + - GoogleDirections + - google-drive + - google-mail-filters + - google-maps-geocoding + - googleplus + - GoogleSB + - google-static-maps + - GoogleTranslate + - gore-and-ash-actor + - gore-and-ash-async + - gore-and-ash-demo + - gore-and-ash-glfw + - gore-and-ash-lambdacube + - gore-and-ash-logging + - gore-and-ash-network + - gore-and-ash-sdl + - gore-and-ash-sync + - GPipe-Collada + - GPipe-Examples + - GPipe-GLFW + - GPipe-GLFW4 + - GPipe-TextureLoad + - gps + - gps2htmlReport + - GPX + - grab-form + - graflog + - grammar-combinators + - GrammarProducts + - grapefruit-examples + - grapefruit-records + - grapefruit-ui + - grapefruit-ui-gtk + - GraphHammer + - GraphHammer-examples + - graphicsFormats + - graphicstools + - graphql-client + - graph-rewriting-cl + - graph-rewriting-gl + - graph-rewriting-lambdascope + - graph-rewriting-layout + - graph-rewriting-ski + - graph-rewriting-strategies + - graph-rewriting-trs + - graph-rewriting-ww + - graphtype + - graph-visit + - greencard-lib + - gridbounds + - gridland + - grid-proto + - GrowlNotify + - grpc-etcd-client + - grpc-haskell + - grpc-haskell-core + - gruff + - gruff-examples + - gscholar-rss + - gsl-random-fu - gsmenu + - gstorable + - gtfs - gtk2hs-cast-glade - gtk2hs-cast-gnomevfs - gtk2hs-cast-gtkglext - gtk2hs-cast-gtksourceview2 + - Gtk2hsGenerics + - GtkGLTV + - gtkimageview + - gtkrsync + - gtk-serialized-event + - guarded-rewriting + - guess-combinator + - GuiHaskell + - GuiTV + - habit + - hablo + - hablog + - Hach + - hack2-handler-happstack-server + - hack2-handler-mongrel2-http + - hack2-handler-snap-server + - hackage2twitter + - hackage-server + - hack-contrib + - hack-contrib-press + - hack-handler-epoll + - hack-handler-evhttp + - hack-handler-fastcgi + - hack-handler-hyena + - hack-handler-simpleserver + - hackmanager + - hack-middleware-cleanpath + - hack-middleware-clientsession + - hack-middleware-jsonp + - haddock + - haddock_2_23_1 + - haddocset + - hadoop-tools + - haggis + - hails-bin + - hakyll-agda + - hakyll-alectryon + - hakyll-blaze-templates + - hakyll-contrib + - hakyll-contrib-csv + - hakyll-contrib-elm + - hakyll-contrib-hyphenation - hakyll-contrib-i18n + - hakyll-contrib-links + - hakyll-dhall + - hakyll-dir-list + - hakyll-elm + - hakyll-favicon + - hakyll-filestore + - hakyll-images + - hakyll-ogmarkup + - hakyll-process + - hakyll-R + - hakyll-sass + - hakyll-series + - hakyll-shakespeare + - hakyll-shortcut-links + - hakyll-typescript + - halberd + - hall-symbols + - halma-gui + - halma-telegram-bot + - ham + - HaMinitel + - hamusic + - hans-pcap + - happlets-lib-gtk + - HAppS-Data + - happs-hsp + - happs-hsp-template + - HAppS-IxSet + - HAppS-Server + - HAppS-State + - happstack-auth + - happstack-authenticate + - happstack-contrib + - happstack-data + - happstack-dlg + - happstack-facebook + - happstack-fay + - happstack-helpers + - happstack-ixset + - happstack-jmacro + - happstack-plugins + - happstack-state + - happstack-yui + - happs-tutorial + - happybara-webkit + - haquil + - hArduino + - hardware-edsl + - HaRe + - harg + - hark + - harmony + - HarmTrace + - haroonga-httpd - hascat - hascat-lib - hascat-setup - hascat-system + - HasGP + - Hashell + - hashflare + - haskarrow + - haskdeep + - haskeem + - haskell-abci + - haskell-aliyun + - haskell-bitmex-client + - haskelldb-connect-hdbc + - haskelldb-connect-hdbc-catchio-mtl + - haskelldb-connect-hdbc-catchio-tf + - haskelldb-connect-hdbc-catchio-transformers + - haskelldb-connect-hdbc-lifted + - haskelldb-dynamic + - haskelldb-flat + - haskelldb-hdbc + - haskelldb-hdbc-mysql + - haskelldb-hdbc-odbc + - haskelldb-hdbc-postgresql + - haskelldb-hdbc-sqlite3 + - haskelldb-hsql + - haskelldb-hsql-mysql + - haskelldb-hsql-odbc + - haskelldb-hsql-postgresql + - haskelldb-hsql-sqlite3 + - haskelldb-th + - haskell-docs + - haskell-eigen-util + - haskell-ftp + - haskell-pdf-presenter + - haskell-platform-test + - haskell-reflect + - haskell-src-exts-observe + - haskell-token-utils + - haskell-tools-ast + - haskell-tools-ast-fromghc + - haskell-tools-ast-gen + - haskell-tools-ast-trf + - haskell-tools-backend-ghc + - haskell-tools-builtin-refactorings + - haskell-tools-cli + - haskell-tools-daemon + - haskell-tools-debug + - haskell-tools-demo + - haskell-tools-experimental-refactorings + - haskell-tools-prettyprint + - haskell-tools-refactor + - haskell-tools-rewrite + - haskell-tor + - haskelm + - haskey-mtl + - haskgame + - hask-home + - haskoin-bitcoind + - haskoin-core + - haskoin-crypto + - haskoin-node + - haskoin-protocol + - haskoin-script + - haskoin-store + - haskoin-store-data + - haskoin-wallet + - haskoon + - haskoon-httpspec + - haskoon-salvia + - haskore-realtime + - haskore-supercollider + - haskore-synthesizer + - HaskRel + - hasktorch + - hasktorch-ffi-thc + - hasktorch-indef + - hasktorch-signatures + - hasktorch-zoo + - haskus-utils-compat + - haskus-web + - haslo + - hasloGUI + - hasparql-client + - hasql-cursor-query + - hasql-postgres + - hasql-postgres-options + - hasql-queue + - hastache-aeson + - haste-app - haste-gapi + - haste-lib + - haste-markup - haste-perch + - has-th + - Hate + - HaTeX-meta - hatexmpp3 + - HaTeX-qq + - HaVSA + - hawitter + - Hawk + - haxy + - Hayoo + - hback + - hbayes + - hbb + - hbcd + - hbf + - hcg-minus-cairo + - hcheat + - hcheckers + - hdbi + - hdbi-conduit + - hdbi-postgresql + - hdbi-sqlite + - hdbi-tests + - hdf + - hdiff + - hdirect + - hdocs + - hdph + - heart-app + - heatitup + - heavy-logger + - heavy-logger-amazon + - heavy-logger-instances + - heavy-log-shortcuts + - hecc + - hedgehog-checkers-lens + - hedgehog-gen-json + - Hedi + - hedis-pile + - heidi + - heist-aeson + - helics + - helics-wai + - helium + - hellage + - hellnet + - hemokit + - hen + - henet + - hepevt + - her-lexer-parsec + - hermit + - hermit-syb + - herringbone + - herringbone-embed + - herringbone-wai + - hesh + - hesql + - heterolist + - hevolisa + - hevolisa-dph + - hexpat-iteratee + - hfd + - hfiar + - hgalib + - HGamer3D-API + - HGamer3D-CAudio-Binding + - HGamer3D-OIS-Binding + - hgen + - hgeometry-svg + - hgithub + - hiccup + - hierarchical-spectral-clustering + - Hieroglyph + - HiggsSet + - highjson-swagger + - highjson-th + - himpy + - hinduce-classifier + - hinduce-classifier-decisiontree + - hinduce-examples + - hint-server + - hinvaders + - hinze-streams + - hipbot + - HipmunkPlayground + - Hipmunk-Utils + - hipsql-client + - hipsql-server + - hirt + - hist-pl + - hist-pl-dawg + - hist-pl-fusion + - hist-pl-lexicon + - hist-pl-lmf + - hit + - hit-graph + - HJScript + - hjsonschema + - hjugement-cli + - hlcm + - HLearn-algebra + - HLearn-approximation + - HLearn-classification + - HLearn-datastructures + - HLearn-distributions + - hledger-api + - hls + - hly + - hmark + - hmatrix-sundials + - hmeap + - hmeap-utils + - hmep + - hmm-lapack + - hmt + - hmt-diagrams + - HNM + - hnormalise + - hob + - Hoed + - hOff-display + - hogre + - hogre-examples + - Holumbus-Distribution + - Holumbus-MapReduce + - Holumbus-Searchengine + - Holumbus-Storage + - holy-project + - hommage + - HongoDB + - hood + - hoodie + - hoodle + - hoodle-builder + - hoodle-core + - hoodle-extra + - hoodle-parser + - hoodle-publish + - hoodle-render + - hoovie + - hoq + - hp2any-graph + - hp2any-manager + - hpaco + - hpaco-lib + - hpage + - hpaste + - hpc-tracer + - hPDB + - hPDB-examples - hplayground + - HPlot + - HPong + - hpqtypes-extras + - hprotoc-fork + - hps + - hps-cairo + - hpython + - hquantlib + - hranker + - HRay + - hreader + - hreader-lens + - hreq-client + - hreq-conduit + - HROOT + - HROOT-core + - HROOT-graf + - HROOT-hist + - HROOT-io + - HROOT-math + - HROOT-tree - hs2dot + - Hs2lib + - hsautogui + - hsbackup + - hsbencher-codespeed + - hsbencher-fusion + - hs-blake2 + - hs-brotli + - hsc3-auditor + - hsc3-cairo + - hsc3-data + - hsc3-db + - hsc3-dot + - hsc3-forth + - hsc3-graphs + - hsc3-lang + - hsc3-lisp + - hsc3-plot + - hsc3-process + - hsc3-rec + - hsc3-server + - hsc3-sf-hsndfile + - hsc3-unsafe + - hsc3-utils + - hscassandra + - hscope + - hsdev + - Hsed + - hset + - hsfacter + - hs-ffmpeg + - hs-gen-iface + - HSGEP + - HSHHelpers + - hslogstash + - hsnock + - HSoundFile + - HsParrot + - hspec-expectations-pretty + - hspec-pg-transact + - hspec-setup + - hspec-shouldbe + - hspec-test-sandbox + - hspecVariant + - hs-pkpass + - hsprocess + - hsql-mysql + - hsql-odbc + - hsql-postgresql + - hsql-sqlite3 - hsqml-datamodel-vinyl - hsqml-demo-morris - hsqml-morris + - hsreadability + - hssqlppp-th + - hs-swisstable-hashtables-class + - hstar + - hstox + - hstradeking + - HStringTemplateHelpers + - hstzaar + - hsubconvert + - HsWebots + - hswip + - hsx-jmacro + - hsx-xhtml + - HTab + - hts + - http2-client-exe + - http2-client-grpc + - http-client-auth + - http-enumerator + - http-io-streams + - https-everywhere-rules + - https-everywhere-rules-raw + - httpspec - hubris + - hugs2yc + - hulk + - hunit-gui + - hunp + - hunt-searchengine + - hunt-server + - hurdle + - husky + - huzzy + - hw-all + - hw-dsv + - hw-json + - hw-json-lens + - hw-json-simple-cursor + - hw-json-standard-cursor + - hw-kafka-avro + - hworker-ses + - hwormhole + - hws + - hw-simd-cli + - hwsl2-bytevector + - hwsl2-reducers + - hw-uri + - HXMPP + - hxmppc + - hxournal - hxt-binary - hxt-filter + - hxthelper + - hxweb + - hybrid + - Hydrogen + - hydrogen-cli + - hydrogen-cli-args + - hydrogen-data + - hydrogen-parsing + - hydrogen-prelude + - hydrogen-prelude-parsec + - hydrogen-syntax + - hydrogen-util + - hyena + - hylotab + - hyloutils + - hyperpublic + - ice40-prim + - ideas-math + - ideas-math-types + - ideas-statistics + - ide-backend + - ide-backend-common + - ide-backend-server + - ige-mac-integration + - ihaskell-rlangqq + - ihttp + - imap + - imbib + - imgurder + - imj-animation + - imj-base + - imj-game-hamazed + - imj-measure-stdout + - imm + - imparse + - imperative-edsl-vhdl + - importify - imprevu-happstack + - improve + - INblobs + - inch + - incremental-computing + - incremental-maps + - increments + - indentation + - indentation-parsec + - indentation-trifecta + - indexation + - IndexedList + - indieweb-algorithms + - infernu + - InfixApplicative + - inline-java + - inspector-wrecker + - instant-aeson + - instant-bytes + - instant-deepseq + - instant-hashable + - instant-zipper + - instapaper-sender + - interpolatedstring-qq + - interpolatedstring-qq-mwotton + - introduction-test + - intset + - invertible-hlist + - ion + - IORefCAS + - ip + - ipatch + - ipc + - ipld-cid + - ipprint + - iptadmin + - irc-fun-bot + - irc-fun-client + - irc-fun-color + - irc-fun-messages + - iri + - ironforge + - isevaluated + - ismtp + - isobmff-builder + - isohunt + - iteratee-compress + - iteratee-mtl + - iteratee-parsec + - iteratee-stm + - iterio-server + - iterm-show-diagrams + - iter-stats + - ivor + - ivory-avr-atmega328p-registers + - ivory-backend-c + - ivory-bitdata + - ivory-eval + - ivory-examples + - ivory-hw + - ivory-opts + - ivory-quickcheck + - ivory-serialize + - ivory-stdlib + - ivy-web + - iyql + - j2hs + - jail + - java-bridge-extras + - java-character - javaclass + - java-reflect + - javasf + - Javasf + - jmacro + - jmacro-rpc + - jmacro-rpc-happstack + - jmacro-rpc-snap + - jmonkey + - jobs-ui + - join + - jot + - JsContracts + - jsmw + - json2-hdbc + - json-ast-json-encoder + - json-autotype + - json-b + - JSONb + - JSON-Combinator + - JSON-Combinator-Examples + - json-enumerator + - JsonGrammar + - jsonifier + - json-incremental-decoder + - json-query + - jsons-to-schema + - json-syntax + - json-togo + - json-tokens + - jspath + - JunkDB-driver-gdbm + - JunkDB-driver-hashtables + - JuPyTer-notebook + - jvm + - jvm-batching + - jvm-streaming + - kafka-device + - kafka-device-glut + - kafka-device-joystick + - kafka-device-leap + - kafka-device-spacenav + - kafka-device-vrpn + - kaleidoscope + - kansas-lava + - kansas-lava-cores + - kansas-lava-papilio + - kansas-lava-shake + - karakuri + - katip-elasticsearch + - katip-rollbar + - kawaii + - keera-hails-i18n + - keera-hails-mvc-environment-gtk + - keera-hails-mvc-model-lightmodel + - keera-hails-mvc-model-protectedmodel + - keera-hails-mvc-solutions-gtk + - keera-hails-reactive-cbmvar + - keera-hails-reactive-fs + - keera-hails-reactive-gtk + - keera-hails-reactive-htmldom + - keera-hails-reactivelenses + - keera-hails-reactive-network + - keera-hails-reactive-polling + - keera-hails-reactive-wx + - keera-hails-reactive-yampa - keera-posture - - lambdabot-xmpp + - kevin + - keysafe + - keyvaluehash + - keyword-args + - kicad-data + - KiCS + - KiCS-debugger + - KiCS-prophecy + - kif-parser + - kit + - kleene + - kmeans-par + - kmeans-vector + - knead + - knead-arithmetic + - knit-haskell + - knots + - korfu + - ks-test + - kubernetes-client + - kurita + - laborantin-hs + - labsat + - labyrinth + - labyrinth-server + - laika + - lambdabot-zulip + - lambda-calculator + - lambdacms-media + - lambdacube + - lambdacube-bullet + - lambdacube-compiler + - lambdacube-core + - lambdacube-edsl + - lambdacube-engine + - lambdacube-examples + - lambdacube-gl + - lambdacube-samples + - LambdaDesigner + - lambda-devs + - lambdaFeed + - LambdaINet + - lambdaLit + - lambda-options + - LambdaPrettyQuote + - LambdaShell + - lambdaya-bus + - lambdiff + - lang + - language-boogie + - language-eiffel + - language-kort + - language-Modula2 + - language-ninja + - language-oberon + - language-python-colour + - language-qux + - language-spelling + - lapack + - lapack-carray + - lapack-comfort-array + - lat + - latex-formulae-hakyll + - latex-formulae-pandoc + - latex-svg-hakyll + - latex-svg-pandoc + - layered-state + - layers-game + - layouting + - lazy-hash + - lazy-hash-cache + - ldapply + - LDAPv3 + - leaky + - lean + - legion + - legion-discovery + - legion-discovery-client + - legion-extra - leksah + - leksah-server + - lens-utils + - levmar + - levmar-chart + - lex-applicative + - lgtk + - lha + - lhae + - lhe + - libconfig + - libcspm + - liblastfm + - liblawless + - liblinear-enumerator + - libmolude + - libraft + - librato + - libssh2-conduit + - libxml-enumerator + - lifetimes + - lifted-base-tf + - lightning-haskell + - lightstep-haskell + - lighttpd-conf + - lighttpd-conf-qq + - linear-circuit + - linearmap-category + - linearscan-hoopl + - LinearSplit + - LinkChecker + - linkchk + - linkcore + - linux-ptrace + - lio-eci11 + - lion + - liquid-base + - liquid-bytestring + - liquid-containers + - liquid-ghc-prim - liquidhaskell-cabal-demo + - liquid-parallel + - liquid-platform + - liquid-prelude + - liquid-vector + - listenbrainz-client + - list-t-attoparsec + - list-t-html-parser + - list-witnesses + - live-sequencer + - llvm + - llvm-analysis + - llvm-base-types + - llvm-base-util + - llvm-data-interop + - llvm-dsl + - llvm-extension + - llvm-extra + - llvm-general + - llvm-general-quote + - llvm-pretty-bc-parser + - llvm-tf + - llvm-tools + - lmonad-yesod + - localize + - local-search + - locked-poll + - log + - logging-effect-extra + - logic-classes + - LogicGrowsOnTrees + - LogicGrowsOnTrees-MPI + - LogicGrowsOnTrees-network + - LogicGrowsOnTrees-processes + - log-postgres + - log-utils + - lojban + - lojysamban + - lol-apps + - lol-benches + - lol-cpp + - loli + - lol-repa + - lol-tests + - lol-typing + - longshot + - loop-effin + - lorentz + - lostcities + - loup + - LslPlus + - ls-usb + - lsystem + - lti13 + - luachunk + - lucid-colonnade + - lucienne + - Lucu + - luhn + - lui + - luminance-samples + - lvish + - Lykah + - lz4-conduit + - lzma-enumerator + - macbeth-lib + - machines-amazonka + - macosx-make-standalone + - magicbane + - magico + - magic-wormhole + - mahoro + - maid + - mailgun + - mail-pool + - majordomo + - majority + - manatee + - manatee-anything + - manatee-core + - manatee-curl + - manatee-editor + - manatee-filemanager + - manatee-imageviewer + - manatee-ircclient + - manatee-mplayer + - manatee-pdfviewer + - manatee-processmanager + - manatee-template + - manatee-terminal + - manatee-welcome + - manifold-random + - manifolds + - marionetta + - markdown2svg + - markdown-pap + - markov-processes + - markup + - marmalade-upload + - marquise + - marvin + - masakazu-bot + - master-plan + - matchers + - mathblog + - mathlink + - math-programming-glpk + - math-programming-tests + - matsuri + - maxent + - maxent-learner-hw-gui + - maxsharing + - MaybeT-transformers + - MC-Fold-DP + - mcmc + - mcmc-samplers + - mDNSResponder-client + - mealy + - mediabus-fdk-aac + - mediabus-rtp + - mellon-gpio + - mellon-web + - memcache-conduit + - mergeful-persistent + - mergeless-persistent + - merkle-patricia-db + - MetaObject + - meta-par-accelerate + - metaplug + - metar + - metar-http + - Metrics + - metronome + - MFlow + - Mhailist + - Michelangelo + - microformats2-parser + - microformats2-types + - micro-gateway + - MicrosoftTranslator + - midimory + - mighttpd + - minecraft-data + - minesweeper + - mini-egison + - miniforth + - minilight-lua + - minimung + - minioperational + - MIP-glpk + - miss + - MissingPy + - missing-py2 + - miss-porcelain + - mixed-strategies + - mkbndl + - mkcabal + - mlist + - mmark-cli + - mmark-ext + - mmtl-base + - moan + - modify-fasta + - modsplit + - modularity + - modular-prelude-classy + - modulo + - mole + - MonadCatchIO-mtl + - MonadCatchIO-mtl-foreign + - MonadCatchIO-transformers-foreign + - monad-exception + - monadiccp-gecode + - MonadLab + - monad-state + - monad-stlike-stm + - monarch + - Monaris + - Monatron-IO + - monetdb-mapi + - mongrel2-handler + - monky + - Monocle + - monte-carlo + - moo + - morley + - morloc + - morphisms-functors-inventory + - mosaico-lib + - motor-diagrams + - mp - mp3decoder + - mpdmate + - mprelude + - mpretty + - mprover + - mps + - mptcp-pm + - msgpack-aeson + - msgpack-idl + - msgpack-rpc + - msgpack-rpc-conduit + - MSQueue + - mtgoxapi + - MuCheck-Hspec + - MuCheck-HUnit + - MuCheck-QuickCheck + - MuCheck-SmallCheck + - mu-grpc-client + - mu-grpc-server + - multibase + - multi-cabal + - multifocal + - multihash-serialise + - multilinear-io + - multiplicity + - multirec-alt-deriver + - multirec-binary + - multisetrewrite + - murder + - murmurhash3 + - musicbrainz-email + - music-graphics + - music-parts + - music-pitch + - music-preludes + - music-score + - music-sibelius + - music-suite + - musicxml2 + - mutable-iter + - MutationOrder + - mute-unmute + - mu-tracing + - mvclient + - mvc-updates + - mxnet-dataiter + - mxnet-examples + - mxnet-nn + - mysnapsession-example + - mysql-haskell-openssl + - mysql-simple-typed + - myTestlll + - mywatch + - n2o-web + - nakadi-client + - nanovg-simple + - NaperianNetCDF + - nats-queue + - natural-number + - NearContextAlgebra + - nemesis-titan + - nerf + - nero-wai + - nero-warp + - nested-routes + - netcore + - netlines + - net-spider-cli + - net-spider-pangraph + - net-spider-rpl + - net-spider-rpl-cli + - netstring-enumerator + - nettle-frp + - nettle-netkit + - nettle-openflow + - network-anonymous-i2p + - network-anonymous-tor + - network-connection + - network-enumerator + - network-hans + - network-interfacerequest + - network-messagepack-rpc-websocket + - network-minihttp + - network-netpacket - network-pgi + - network-protocol-xmpp + - network-rpca + - network-stream + - network-topic-models + - network-websocket + - newsletter-mailgun + - ngrams-loader + - ngx-export-tools-extra + - nikepub + - Ninjas + - nirum + - nlp-scores-scripts + - Nomyx - nomyx-api - nomyx-core + - Nomyx-Core - nomyx-language + - Nomyx-Language - nomyx-library + - Nomyx-Rules - nomyx-server + - Nomyx-Web + - NonEmptyList + - NoSlow + - notmuch-haskell + - notmuch-web + - numerical + - numeric-ode + - numhask-hedgehog + - numhask-histogram + - numhask-range + - numhask-test + - Nussinov78 + - NXT + - nymphaea + - obd + - obdd + - oberon0 + - obj + - objectid + - ochan + - octane + - octohat + - octopus + - oculus + - odd-jobs + - off-simple + - ohloh-hs + - ois-input-manager + - olwrapper - one-liner_2_0 + - online + - online-csv + - OnRmt + - open-adt-tutorial + - OpenAFP-Utils + - OpenGLCheck - openpgp-crypto-api + - OpenSCAD + - openssh-github-keys + - opentracing-jaeger + - opentracing-zipkin-v1 + - open-union + - OpenVG + - optima-for-hasql + - optimal-blocks + - optimusprime + - orchid + - orchid-demo + - order-maintenance + - org-mode-lucid + - OSM + - osm-download + - otp-authenticator + - padKONTROL + - PageIO + - pairing + - panda + - pandoc-japanese-filters + - pan-os-syslog + - papa + - papa-base + - papa-base-implement + - papa-export + - papa-implement + - papa-semigroupoids + - paprika + - Paraiso + - Parallel-Arrows-Eden + - parco-attoparsec + - parconc-examples + - parco-parsec + - parquet-hs + - parse-help + - parsestar + - partial-lens + - passman-cli - patch-image + - patterns + - pcap-enumerator + - pcapng + - pcf + - pcf-font-embed + - PCLT-DB + - pdf-slave + - peakachu + - pec + - pell + - penny + - penny-bin + - penny-lib + - penrose + - peparser - perdure - - persistent-mysql_2_13_0_0 - - persistent-postgresql_2_13_0_0 - - persistent-sqlite_2_13_0_0 + - perf-analysis + - perfecthash + - periodic-client + - periodic-client-exe + - periodic-server + - perm + - PermuteEffects + - persistent-audit + - persistent-hssqlppp + - persistent-map + - persona-idp + - peyotls + - peyotls-codec + - pgsql-simple + - pg-transact + - phonetic-languages-examples + - phonetic-languages-simplified-lists-examples + - phooey + - photoname + - pianola + - pier + - ping + - pinpon + - pipe-enumerator + - pipes-attoparsec-streaming + - pipes-brotli + - pipes-cacophony + - pipes-cereal-plus + - pipes-conduit + - pipes-courier + - pipes-extra + - pipes-files + - pipes-illumina + - pipes-key-value-csv + - pipes-p2p + - pipes-p2p-examples + - pisigma + - pitchtrack + - pkgtreediff + - planet-mitchell + - plocketed + - Plot-ho-matic + - PlslTools + - png-file + - pngload + - pocket-dns + - pointless-lenses + - pointless-rewrite + - point-octree + - poke + - polh-lexicon + - polydata + - polysemy-extra + - polysemy-fskvstore + - polysemy-kvstore-jsonfile + - polysemy-log-co + - polysemy-methodology + - polysemy-methodology-composite + - polysemy-optics + - polysemy-path + - polysemy-RandomFu + - polysemy-vinyl + - polyseq + - polytypeable-utils + - pomodoro - pontarius-mediaserver - - pontarius-xmpp-extras - - pontarius-xpmn + - popenhs + - porcupine-core + - porcupine-http + - porcupine-s3 + - ports + - poseidon + - poseidon-postgis + - postgresql-query + - postgresql-simple-queue + - postgresql-simple-typed + - postgresql-tx-query + - postgresql-tx-squeal + - postgresql-tx-squeal-compat-simple + - postmark + - potoki + - potoki-cereal + - potoki-conduit + - potoki-hasql + - potoki-zlib + - powerqueue-sqs + - pqueue-mtl + - practice-room + - prednote-test + - pred-set + - pred-trie + - presto-hdbc + - preview + - primula-board + - primula-bot + - Printf-TH + - ProbabilityMonads + - proc + - process-iterio + - process-progress + - process-qq + - process-streaming - procrastinating-structure + - producer + - prof2dot + - progressbar + - project-m36 + - prologue + - prolude + - prometheus-effect + - propane + - proplang + - prosidyc + - proteome + - proto3-suite + - protobuf-native + - protocol-buffers-descriptor-fork + - proto-lens-descriptors + - proton + - psc-ide + - puffytools + - Pugs + - pugs-compat + - pugs-hsregex + - punkt + - Pup-Events + - Pup-Events-Demo + - puppetresources + - pure-cdb + - pure-priority-queue-tests + - purescript + - purescript-iso + - purescript-tsd-gen + - push-notify + - push-notify-apn + - push-notify-ccs + - push-notify-general + - puzzle-draw + - puzzle-draw-cmdline + - pvd + - qd-vec + - qhs + - qr-repa + - quantum-random + - Quelea + - queryparser + - queryparser-demo + - queryparser-hive + - queryparser-presto + - queryparser-vertica + - questioner + - queuelike + - quickbench + - quickcheck-poly + - quickcheck-regex + - quickcheck-relaxng + - quickcheck-state-machine + - quickcheck-state-machine-distributed + - quicktest + - quipper + - quipper-algorithms + - quipper-all + - quipper-cabal + - quipper-demos + - quipper-language + - quipper-libraries + - quipper-rendering + - quipper-tools + - quiver-binary + - quiver-bytestring + - quiver-cell + - quiver-csv + - quiver-enumerator + - quiver-groups + - quiver-http + - quiver-instances + - quiver-interleave + - quiver-sort + - qux + - rail-compiler-editor + - rails-session + - rainbow-tests + - raketka + - rallod + - random-effin + - random-hypergeometric + - range-space + - Ranka + - rasa + - rasa-example-config + - rasa-ext-bufs + - rasa-ext-cmd + - rasa-ext-cursors + - rasa-ext-files + - rasa-ext-logger + - rasa-ext-slate + - rasa-ext-status-bar + - rasa-ext-style + - rasa-ext-views + - rasa-ext-vim + - rating-chgk-info + - raw-feldspar + - rawr + - razom-text-util + - rbr + - rc + - rdioh + - react-flux-servant - reactive + - reactive-balsa + - reactive-banana-automation + - reactive-banana-bunch + - reactive-banana-gi-gtk + - reactive-banana-sdl + - reactive-banana-sdl2 + - reactive-banana-threepenny + - reactive-banana-wx + - reactive-fieldtrip + - reactive-glut + - reactive-jack + - reactive-midyim + - reactor + - readline-statevar + - readpyc + - reanimate + - record-aeson + - record-gl + - record-preprocessor + - records-th + - record-syntax + - reddit - redHandlers + - reduce-equations + - refh + - reflex-animation + - reflex-backend-socket + - reflex-backend-wai - reflex-dom-colonnade + - reflex-ghci + - reflex-gloss-scene + - reflex-process + - refurb + - reg-alloc-graph-color + - regex-deriv - regex-genex - - ribosome + - regex-pcre-text + - regex-pderiv + - regexp-tries + - regex-xmlschema + - regional-pointers + - regions-monadsfd + - regions-monadstf + - regions-mtl + - registry-hedgehog + - regular-extras + - regular-web + - regular-xmlpickler + - reheat + - relative-date + - remote-json + - remote-json-client + - remote-json-server + - remotion + - repa-array + - repa-convert + - repa-examples + - repa-flow + - repa-plugin + - repa-stream + - repa-v4l2 + - replicant + - repr + - representable-tries + - req-oauth2 + - resistor-cube + - resource-pool-catchio + - resource-simple + - respond + - rest-client + - rest-core + - rest-example + - restful-snap + - rest-gen + - rest-happstack + - RESTng + - restricted-workers + - rest-snap + - rest-stringmap + - rest-types + - rest-wai + - rethinkdb-model + - rewrite + - rewriting + - rezoom + - rfc + - rfc-env + - rfc-http-client + - rfc-psql + - rfc-redis + - rfc-servant + - rhythm-game-tutorial + - rib - ribosome-root - ribosome-test + - ridley-extras + - rio-process-pool + - riot - ripple + - risc-v + - rivet + - Rlang-QQ + - rlwe-challenges + - rmonad + - RMP + - RNAdesign + - RNAdraw + - RNAFold + - RNAFoldProgs + - RNAlien + - RNAwolf + - rncryptor + - rob - robot + - roc-cluster-demo + - rock - roguestar-engine - roguestar-gl - roguestar-glut + - rollbar-cli + - rollbar-wai + - rollbar-yesod + - RollingDirectory + - ron-schema + - ron-storage + - rose-trie + - roshask + - rosmsg-bin + - rounded-hw + - roundtrip-xml - route-generator + - route-planning + - rpc + - rpf + - rsagl + - rsagl-frp + - rsagl-math + - rtcm + - ruler + - ruler-core + - runtime-arbitrary + - S3 + - safe-numeric + - safer-file-handles + - safer-file-handles-bytestring + - safer-file-handles-text + - sai-shape-syb + - sak + - saltine-quickcheck + - salvia + - salvia-demo + - salvia-extras + - salvia-sessions + - salvia-websocket + - samtools + - samtools-conduit + - samtools-enumerator + - samtools-iteratee + - sarsi + - sasl + - satchmo-backends + - satchmo-examples + - satchmo-funsat + - satchmo-minisat + - satchmo-toysat + - sat-micro-hs + - SBench - sc2hs - - sexpresso + - sc2-lowlevel + - sc2-support + - sc3-rdu + - scalable-server + - SCalendar + - scalpel-search + - scalp-webhooks + - scan-vector-machine + - schema + - schematic + - scholdoc + - scholdoc-citeproc + - scholdoc-texmath + - scientific-notation + - SciFlow + - SciFlow-drmaa + - scion + - scion-browser + - scope + - scope-cairo + - scotty-hastache + - scp-streams + - scrabble-bot + - scrapbook + - SCRIPTWriter + - Scurry + - sde-solver + - seakale-postgresql + - seakale-tests + - secrm + - sednaDBXML + - seitz-symbol + - SelectSequencesFromMSA + - selenium-server + - self-extract + - semi-iso + - semiring + - semiring-num + - sensenet + - sentence-jp + - seonbi + - seqaid + - seqloc + - seqloc-datafiles + - sequor + - serpentine + - serv + - servant-auth-token + - servant-auth-token-acid + - servant-auth-token-leveldb + - servant-auth-token-persistent + - servant-auth-token-rocksdb + - servant-auth-wordpress + - servant-cli + - servant-client-namedargs + - servant-csharp + - servant-db-postgresql + - servant-ede + - servant-event-stream + - servant-examples + - servant-http2-client + - servant-matrix-param + - servant-polysemy + - servant-postgresql + - servant-server-namedargs + - servant-snap + - servant-streaming-client + - servant-streaming-docs + - servant-streaming-server + - servant-swagger-tags + - servant-waargonaut + - servant-zeppelin-client + - servant-zeppelin-server + - servant-zeppelin-swagger + - serv-wai + - sessiontypes-distributed + - setdown + - s-expression + - SFML-control + - SFont + - SGdemo + - sgf + - sgrep + - sha1 + - shake-minify-css + - shaker + - shapefile + - shapely-data + - shelduck + - Shellac-compatline + - Shellac-editline + - Shellac-haskeline + - Shellac-readline + - shellmate-extras - shine-varying + - ShortestPathProblems + - showdown + - Shpadoinkle-backend-pardiff + - Shpadoinkle-backend-static + - Shpadoinkle-developer-tools + - Shpadoinkle-disembodied + - Shpadoinkle-examples + - Shpadoinkle-html + - Shpadoinkle-router + - Shpadoinkle-template + - Shpadoinkle-widgets + - shpider + - shuffle + - sibe + - si-clock + - sigma-ij + - signable + - signals + - signature + - signify-hs + - silvi + - simgi + - simple-c-value + - simple-firewire + - SimpleGL + - simpleirc-lens + - SimpleLog + - simple-nix + - simple-pascal + - SimpleServer + - simseq - singleton-nats_0_4_6 + - singletons-base + - siphon + - siren-json + - sirkel + - skeleton + - skeletons + - skylark-client + - slidemews + - slip32 + - small-bytearray-builder + - smallstring + - smartword + - smcdel + - smith + - smith-cli + - smith-client + - Smooth + - smtlib2-debug + - smtlib2-pipe + - smtlib2-quickcheck + - smtlib2-timing - smtp2mta + - snap-auth-cli + - snap-elm + - snap-extras + - snaplet-actionlog + - snaplet-auth-acid + - snaplet-coffee + - snaplet-hasql + - snaplet-haxl + - snaplet-hdbc + - snaplet-lss + - snaplet-mandrill + - snaplet-mongoDB + - snaplet-mysql-simple + - snaplet-oauth + - snaplet-postmark + - snaplet-recaptcha + - snaplet-redson + - snaplet-rest + - snaplet-riak + - snaplet-sedna + - snaplet-sqlite-simple-jwt-auth + - snaplet-stripe + - snaplet-tasks + - snaplet-wordpress + - snappy-iteratee + - snap-utils + - sndfile-enumerators - sneathlane-haste + - snm + - snmp + - snowflake-core + - snowflake-server + - snow-white + - Snusmumrik + - SoccerFun + - SoccerFunGL - sock2stream + - sockets + - solga-swagger + - solr + - souffle-dsl + - sounddelay + - soundgen + - source-code-server + - SourceGraph + - sparkle + - sparrow + - sparsebit + - sparser + - spata + - specialize-th + - species + - spectral-clustering + - speculation-transformers + - speechmatics + - spelling-suggest + - sphero + - sphinx-cli + - spice + - SpinCounter + - spline3 + - splines + - Spock-auth + - Spock-lucid + - Spock-worker + - sprinkles + - sproxy + - sproxy2 + - sproxy-web + - sqlite-simple-typed + - sql-simple-mysql + - sql-simple-pool + - sql-simple-postgresql + - sql-simple-sqlite + - sr-extra + - sscgi + - sshd-lint + - sssp + - sstable + - stable-tree + - stackage + - stackage2nix + - stackage-build-plan + - stackage-cabal + - stackage-query + - stackage-sandbox + - stackage-setup + - stackage-upload + - stack-hpc-coveralls + - stack-network + - stack-run-auto - starrover2 + - stateful-mtl + - static-closure + - statsd-client + - statsdi + - STLinkUSB + - STM32-Zombie + - stmcontrol + - StockholmAlignment + - storablevector-streamfusion + - Strafunski-Sdf2Haskell + - stratux + - stratux-demo + - stratux-http + - stratux-websockets + - streaming-base64 + - streaming-brotli + - streaming-concurrency + - streaming-fft + - streaming-process + - streaming-sort + - strelka + - strict-data + - string-typelits + - stripe-scotty + - structural-induction + - structured-mongoDB + - stunts + - stutter + - subhask + - substring-parser + - summoner-tui + - sump + - sunroof-examples + - sunroof-server + - supercollider-ht + - supercollider-midi + - superconstraints + - sv + - sv-cassava + - svg2q + - SVG2Q + - svgone + - sv-svfactor + - swapper + - swearjure + - sweet-egison + - switch + - sylvia + - symantic-atom + - symantic-lib + - symbiote + - symmetry-operations-symbols + - sym-plot + - syncthing-hs + - syntax + - syntax-attoparsec + - syntax-example + - syntax-example-json + - SyntaxMacros + - syntaxnet-haskell + - syntax-pretty + - syntax-printer + - synthesizer-llvm + - systemstats + - t3-client + - ta + - taffybar + - tagged-list + - tagged-th + - tagsoup-navigate + - tagstew + - tag-stream + - tal + - tamarin-prover + - tamarin-prover-term + - tamarin-prover-theory + - target + - task + - task-distribution + - tasty-bdd + - tasty-groundhog-converters + - tasty-integrate + - tasty-jenkins-xml + - tasty-laws + - tasty-lens + - tateti-tateti + - Taxonomy + - TaxonomyTools + - tbox + - tccli + - tdd-util + - tdlib + - tdlib-gen + - tdlib-types + - TeaHS + - techlab + - telegram-bot + - telegram-raw-api + - telegram-types + - tensorflow-core-ops + - tensorflow-logging + - tensorflow-ops + - termbox-banana + - terminal-text + - terrahs + - testbench + - test-framework-sandbox + - test-sandbox-compose + - test-sandbox-hunit + - test-sandbox-quickcheck + - test-simple + - TeX-my-math + - textmatetags + - text-plus + - text-trie - text-xml-generic + - th-alpha + - th-context + - theatre + - theoremquest-client + - thimk + - th-instances + - th-typegraph + - thumbnail-polish + - tickle + - tic-tac-toe + - tidal-serial + - tighttp + - timberc + - time-exts + - time-http + - time-io-access + - timeprint + - time-warp + - timezone-unix + - tinyMesh + - tip-haskell-frontend + - tip-lib + - titan + - tls-extra + - tn + - toboggan + - todos + - toktok + - too-many-cells + - top + - topkata + - to-string-instances + - total-map + - toxcore + - toxcore-c + - toysolver + - tpar + - tpb + - trajectory + - transf + - transfer-db + - transformations + - transformers-convert + - transient-universe-tls + - trasa + - trasa-client + - trasa-extra + - trasa-form - trasa-reflex + - trasa-server + - trasa-th + - TreeCounter + - treemap-html-tools - treersec + - Treiber + - trek-app + - trek-db + - triangulation + - TrieMap + - tries + - trimpolya + - truelevel + - trurl + - tsession-happstack + - tsweb + - tuntap-simple + - tup-functor - tuple-hlist + - tuple-morph + - tuple-ops + - turingMachine + - twentefp-eventloop-graphics + - twentefp-eventloop-trees + - twentefp-graphs + - twentefp-rosetree + - twentefp-trees + - twentyseven + - twidge + - twilight-stm + - twill + - twitter + - twitter-enumerator + - type-assertions + - type-cache + - type-cereal + - TypeClass + - type-combinators-quote + - type-combinators-singletons + - typed-encoding-encoding + - type-digits + - typed-spreadsheet + - typed-streams + - TypeIlluminator + - typelevel + - typelevel-rewrite-rules + - type-ord + - type-ord-spine-cereal + - typescript-docs + - type-sets + - type-structure + - type-sub-th + - typson-beam + - typson-esqueleto + - typson-selda + - u2f + - uber + - ucam-webauth + - uhc-light + - uhc-util + - UMM + - unagi-bloomfilter + - unbound + - unicode-normalization + - uni-events + - uniformBase + - uniform-io + - uni-graphs + - uni-htk + - uni-posixutil + - uniqueness-periods-vector-examples + - uni-reactor + - uni-uDrawGraph + - universe-th + - unix-fcntl + - unix-simple + - unpacked-maybe-numeric + - unpacked-these + - unpacked-validation + - unparse-attoparsec + - unscramble + - up + - urbit-airlock + - urbit-api + - urbit-hob + - ureader + - urembed + - uri-enumerator + - uri-enumerator-file + - url-bytes + - UrlDisp + - urlpath + - URLT + - usb + - usb-enumerator + - usb-hid + - usb-id-database + - usb-iteratee + - usb-safe + - util-exception + - util-primitive-control + - uu-cco-examples + - uu-cco-hut-parsing + - uu-cco-uu-parsinglib + - uuid-bytes + - uuid-crypto + - uvector-algorithms + - v4l2 + - v4l2-examples + - vabal + - vacuum-cairo + - vacuum-graphviz + - vacuum-opengl + - vacuum-ubigraph + - variable-precision + - vcache-trie + - vcard + - vcsgui + - vect-floating-accelerate + - vector-endian + - vector-instances-collections + - vector-text + - venzone + - verdict-json + - versioning-servant + - vflow-types + - vfr-waypoints + - ViennaRNA-extras + - vigilance + - vinyl-operational + - vision + - visual-graphrewrite + - vocoder + - vocoder-audio + - vocoder-conduit + - vocoder-dunai + - voicebase + - vty-ui-extras + - waargonaut + - wahsp + - wai-cli + - wai-devel - wai-dispatch + - wai-handler-snap - wai-hastache - wai-middleware-brotli + - wai-middleware-cache + - wai-middleware-cache-redis + - wai-middleware-consul + - wai-middleware-content-type + - wai-middleware-rollbar + - wai-middleware-route - wai-session-tokyocabinet + - wai-thrift + - waldo + - warped + - WashNGo + - WAVE + - WaveFront + - wavesurfer + - wavy + - web3 + - webapi + - WebBits-Html + - WebBits-multiplate + - WebCont + - webcrank-wai + - webdriver-w3c + - web-mongrel2 + - web-page + - web-rep + - web-routes-regular + - web-routing + - webserver + - WEditorBrick + - WEditorHyphen + - weighted + - werewolf-slack + - what4 + - wheb-mongo + - wheb-redis + - wheb-strapped + - whitespace + - wide-word-instances + - wikipedia4epub + - windowslive + - winio + - WL500gPControl + - wlc-hs + - wl-pprint-ansiterm + - wl-pprint-terminfo + - wobsurv + - wolf + - WordAlignment + - workflow-extra + - workflow-pure + - workflow-types + - wraxml + - wrecker + - wrecker-ui + - wright + - writer-cps-full + - ws + - wss-client + - wtk-gtk + - wumpus-basic + - wumpus-drawing + - wumpus-microprint + - wumpus-tree + - WURFL + - wu-wei - wx + - wxAsteroids - wxc - wxcore - + - WXDiffCtrl + - wxFruit + - WxGeneric + - wxhnotepad + - wxSimpleCanvas + - wxturtle + - wyvern + - xdcc + - xhb-atom-cache + - xhb-ewmh + - XML + - xml2x + - xml-catalog + - xml-enumerator + - xml-enumerator-combinators + - xml-monad + - xml-pipe + - xml-push + - xml-query-xml-conduit + - xml-query-xml-types + - xmltv + - xml-tydom-conduit + - xmms2-client + - xmms2-client-glib + - xmonad-contrib-bluetilebranch + - xmpipe + - XMPP + - xournal-builder + - xournal-convert + - xournal-parser + - xournal-render + - XSaiga + - xtc + - Yablog + - YACPong + - yajl-enumerator + - yam + - yam-datasource + - yam-logger + - yaml-rpc-scotty + - yaml-rpc-snap + - yaml-unscrambler + - yam-redis + - yam-transaction + - yam-transaction-odbc + - yam-web + - yarr-image-io + - yavie + - ycextra + - yeamer + - yeshql + - yesod-articles + - yesod-auth-ldap + - yesod-auth-lti13 + - yesod-colonnade + - yesod-continuations + - yesod-examples + - yesod-ip + - yesod-mangopay + - yesod-paypal-rest + - yesod-platform + - yesod-purescript + - yesod-raml-bin + - yesod-raml-docs + - yesod-raml-mock + - yesod-routes-typescript + - yesod-session-redis + - yjftp + - yjftp-libs + - Yogurt + - Yogurt-Standalone + - yoko + - york-lava + - yql + - yu-launch + - yuuko + - zasni-gerna + - zephyr + - zerobin + - zeromq3-conduit + - zeromq3-haskell + - zeroth + - zifter-cabal + - zifter-git + - zifter-google-java-format + - zifter-hindent + - zifter-hlint + - zifter-stack + - Z-IO + - zipper + - zippo + - ziptastic-client + - zlib-enum + - zmcat + - Z-MessagePack + - zoom-cache + - zoom-cache-pcm + - zoom-cache-sndfile + - zoovisitor + - zuramaru + - Z-YAML diff --git a/pkgs/development/haskell-modules/hackage-packages.nix b/pkgs/development/haskell-modules/hackage-packages.nix index 24849b1e5ba..d04023b09e8 100644 --- a/pkgs/development/haskell-modules/hackage-packages.nix +++ b/pkgs/development/haskell-modules/hackage-packages.nix @@ -46,7 +46,6 @@ self: { description = "A tetris-like game (works with GHC 6.8.3 and Gtk2hs 0.9.13)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "AAI" = callPackage @@ -243,7 +242,6 @@ self: { description = "Fancy type-system stuff for AC-Vector"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ACME" = callPackage @@ -317,7 +315,6 @@ self: { description = "Dynamic programming on tree and forest structures"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ADPfusionSet" = callPackage @@ -343,7 +340,6 @@ self: { description = "Dynamic programming for Set data structures"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "AERN-Basics" = callPackage @@ -381,7 +377,6 @@ self: { description = "Compositional lazy dataflow networks for exact real number computation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "AERN-Real" = callPackage @@ -399,7 +394,6 @@ self: { description = "arbitrary precision real interval arithmetic"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "AERN-Real-Double" = callPackage @@ -424,7 +418,6 @@ self: { description = "arbitrary precision real interval arithmetic"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "AERN-Real-Interval" = callPackage @@ -442,7 +435,6 @@ self: { description = "arbitrary precision real interval arithmetic"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "AERN-RnToRm" = callPackage @@ -460,7 +452,6 @@ self: { description = "polynomial function enclosures (PFEs) approximating exact real functions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "AERN-RnToRm-Plot" = callPackage @@ -479,7 +470,6 @@ self: { description = "GL plotting of polynomial function enclosures (PFEs)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "AES" = callPackage @@ -582,7 +572,6 @@ self: { description = "ASN.1 support for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "AVar" = callPackage @@ -618,7 +607,6 @@ self: { description = "Monads-tf instances for the AbortT monad transformer"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "AbortT-mtl" = callPackage @@ -631,7 +619,6 @@ self: { description = "mtl instances for the AbortT monad transformer"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "AbortT-transformers" = callPackage @@ -723,7 +710,6 @@ self: { description = "Lisperati's adventure game in Lisp translated to Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Advise-me" = callPackage @@ -754,7 +740,6 @@ self: { description = "Assessment services for the Advise-Me project"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "AesonBson" = callPackage @@ -909,7 +894,6 @@ self: { description = "Algorithmic music composition"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "AlgorithmW" = callPackage @@ -942,7 +926,6 @@ self: { description = "Collection of alignment algorithms"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Allure" = callPackage @@ -971,8 +954,9 @@ self: { ]; description = "Near-future Sci-Fi roguelike and tactical squad combat game"; license = lib.licenses.agpl3Plus; - hydraPlatforms = lib.platforms.none; - broken = true; + platforms = [ + "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" + ]; }) {}; "AndroidViewHierarchyImporter" = callPackage @@ -993,7 +977,6 @@ self: { description = "Android view hierarchy importer"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Animas" = callPackage @@ -1020,7 +1003,6 @@ self: { description = "Constructing, analyzing and destructing annotated trees"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Ansi2Html" = callPackage @@ -1067,7 +1049,6 @@ self: { description = "Library for Apple Push Notification Service"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "AppleScript" = callPackage @@ -1174,7 +1155,6 @@ self: { description = "Simple lightweight JSON parser, generator & manipulator based on ByteString"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Attrac" = callPackage @@ -1223,7 +1203,6 @@ self: { description = "GUI library based upon generic programming (SYB3)"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "AvlTree" = callPackage @@ -1236,7 +1215,6 @@ self: { description = "Balanced binary trees using the AVL algorithm"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BASIC" = callPackage @@ -1249,7 +1227,6 @@ self: { description = "Embedded BASIC"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BCMtools" = callPackage @@ -1385,7 +1362,6 @@ self: { description = "An ad-hoc P2P chat program"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Befunge93" = callPackage @@ -1461,7 +1437,6 @@ self: { description = "Factorization of polynomials over finite field"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BiGUL" = callPackage @@ -1540,7 +1515,6 @@ self: { description = "Libary for Hidden Markov Models in HMMER3 format"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Biobase" = callPackage @@ -1563,7 +1537,6 @@ self: { description = "Base library for bioinformatics"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BiobaseBlast" = callPackage @@ -1591,7 +1564,6 @@ self: { description = "BLAST-related tools"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BiobaseDotP" = callPackage @@ -1604,7 +1576,6 @@ self: { description = "Vienna / DotBracket / ExtSS parsers"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BiobaseENA" = callPackage @@ -1628,7 +1599,6 @@ self: { description = "European Nucleotide Archive data"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BiobaseEnsembl" = callPackage @@ -1647,7 +1617,6 @@ self: { description = "Ensembl related datastructures and functions"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BiobaseFR3D" = callPackage @@ -1664,7 +1633,6 @@ self: { description = "Importer for FR3D resources"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BiobaseFasta" = callPackage @@ -1690,7 +1658,6 @@ self: { description = "streaming FASTA parser"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BiobaseHTTP" = callPackage @@ -1709,7 +1676,6 @@ self: { description = "Libary to interface with the Bioinformatics HTTP services - Entrez Ensembl"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BiobaseHTTPTools" = callPackage @@ -1731,7 +1697,6 @@ self: { description = "Tools to query Bioinformatics HTTP services e.g. Entrez, Ensembl."; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BiobaseInfernal" = callPackage @@ -1771,7 +1736,6 @@ self: { description = "Infernal data structures and tools"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BiobaseMAF" = callPackage @@ -1784,7 +1748,6 @@ self: { description = "Multiple Alignment Format"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BiobaseNewick" = callPackage @@ -1834,7 +1797,6 @@ self: { description = "RNA folding training data"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BiobaseTurner" = callPackage @@ -1853,7 +1815,6 @@ self: { description = "Import Turner RNA parameters"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BiobaseTypes" = callPackage @@ -1887,7 +1848,6 @@ self: { description = "Collection of types for bioinformatics"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BiobaseVienna" = callPackage @@ -1904,7 +1864,6 @@ self: { description = "Import Vienna energy parameters"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BiobaseXNA" = callPackage @@ -1947,7 +1906,6 @@ self: { description = "Efficient RNA/DNA/Protein Primary/Secondary Structure"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BirdPP" = callPackage @@ -1962,7 +1920,6 @@ self: { description = "A preprocessor for Bird-style Literate Haskell comments with Haddock markup"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BitStringRandomMonad" = callPackage @@ -1997,8 +1954,6 @@ self: { ]; description = "A module to aid in the (de)serialisation of binary data"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Bitly" = callPackage @@ -2011,7 +1966,6 @@ self: { description = "A library to access bit.ly URL shortener."; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BlastHTTP" = callPackage @@ -2030,7 +1984,6 @@ self: { description = "Libary to interface with the NCBI blast REST interface"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Blobs" = callPackage @@ -2053,7 +2006,6 @@ self: { description = "Diagram editor"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BlogLiterately" = callPackage @@ -2079,7 +2031,6 @@ self: { description = "A tool for posting Haskelly articles to blogs"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "BlogLiterately-diagrams" = callPackage @@ -2102,7 +2053,6 @@ self: { description = "Include images in blog posts with inline diagrams code"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Blogdown" = callPackage @@ -2178,7 +2128,6 @@ self: { description = "A simple document organizer with some wiki functionality"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Boolean" = callPackage @@ -2297,7 +2246,6 @@ self: { description = "Encode/Decode values to/from CBOR"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "CC-delcont" = callPackage @@ -2328,7 +2276,6 @@ self: { description = "Three new monad transformers for multi-prompt delimited control"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "CC-delcont-cxe" = callPackage @@ -2464,7 +2411,6 @@ self: { description = "Infernal covariance model comparison"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "CMQ" = callPackage @@ -2511,7 +2457,6 @@ self: { description = "A simple Brainfuck interpretter"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "CPL" = callPackage @@ -2528,7 +2473,6 @@ self: { description = "An interpreter of Hagino's Categorical Programming Language (CPL)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "CSPM-CoreLanguage" = callPackage @@ -2594,7 +2538,6 @@ self: { description = "An interpreter for CSPM"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "CSPM-ToProlog" = callPackage @@ -2609,7 +2552,6 @@ self: { description = "some modules specific for the ProB tool"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "CSPM-cspm" = callPackage @@ -2636,7 +2578,6 @@ self: { description = "cspm command line tool for analyzing CSPM specifications"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "CTRex" = callPackage @@ -2907,7 +2848,6 @@ self: { description = "A translation from the Carneades argumentation model into Dung's AFs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Cartesian" = callPackage @@ -3064,7 +3004,6 @@ self: { description = "A backend for the Chart library for FLTKHS"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Chart-gtk" = callPackage @@ -3324,7 +3263,6 @@ self: { description = "Libary for parsing Clustal tools output"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Coadjute" = callPackage @@ -3343,7 +3281,6 @@ self: { description = "A generic build tool"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Codec-Compression-LZF" = callPackage @@ -3412,7 +3349,6 @@ self: { description = "A concurrent bittorrent client"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Command" = callPackage @@ -3468,7 +3404,6 @@ self: { description = "A library for expressing spreadsheet-like computations as the fixed-points of comonads"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Compactable" = callPackage @@ -3554,7 +3489,6 @@ self: { description = "Information retrieval library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ConfigFile" = callPackage @@ -3595,7 +3529,6 @@ self: { description = "Parse config files"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Configurable" = callPackage @@ -3738,7 +3671,6 @@ self: { description = "A Library for Writing Multi-Pass Algorithms"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Control-Monad-ST2" = callPackage @@ -3803,7 +3735,6 @@ self: { description = "Bindings to Mac OSX's CoreFoundation framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Coroutine" = callPackage @@ -4043,7 +3974,6 @@ self: { description = "Distributed Mutation Analysis framework for MuCheck"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "DOH" = callPackage @@ -4081,7 +4011,6 @@ self: { description = "DOM Level 2 bindings for the WebBits package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "DP" = callPackage @@ -4098,7 +4027,6 @@ self: { description = "Pragmatic framework for dynamic programming"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "DPM" = callPackage @@ -4239,7 +4167,6 @@ self: { description = "Database Supported Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "DSTM" = callPackage @@ -4262,7 +4189,6 @@ self: { description = "A framework for using STM within distributed systems"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "DTC" = callPackage @@ -4288,7 +4214,6 @@ self: { description = "Monads for operations that can exit early and produce warnings"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Dao" = callPackage @@ -4333,7 +4258,6 @@ self: { description = "Code used by Patch-Shack that seemed sensible to open for reusability"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Data-Angle" = callPackage @@ -4505,8 +4429,6 @@ self: { libraryHaskellDepends = [ base haskell-src mtl TypeCompose ]; description = "Arrows for \"deep application\""; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "DeepDarkFantasy" = callPackage @@ -4546,7 +4468,6 @@ self: { description = "A simple RTS game"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Delta-Lambda" = callPackage @@ -4650,7 +4571,6 @@ self: { description = "A theory solver for conjunctions of literals in difference logic"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "DifferentialEvolution" = callPackage @@ -4751,7 +4671,6 @@ self: { description = "Distributed Bug Tracking System"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "DiscussionSupportSystem" = callPackage @@ -4854,7 +4773,6 @@ self: { description = "Frameshift-aware alignment of protein sequences with DNA sequences"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "DocTest" = callPackage @@ -4873,7 +4791,6 @@ self: { description = "Test interactive Haskell examples"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Docs" = callPackage @@ -4904,7 +4821,6 @@ self: { description = "A tool for deriving hylomorphisms"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "DrIFT" = callPackage @@ -4981,7 +4897,6 @@ self: { description = "Polymorphic protocol engine"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Dust-crypto" = callPackage @@ -5035,7 +4950,6 @@ self: { description = "Network filtering exploration tools"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Dust-tools-pcap" = callPackage @@ -5058,7 +4972,6 @@ self: { description = "Network filtering exploration tools that rely on pcap"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "DynamicTimeWarp" = callPackage @@ -5105,7 +5018,6 @@ self: { description = "dysFunctional Reactive Programming on Cairo"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "DysFRP-Craftwerk" = callPackage @@ -5123,7 +5035,6 @@ self: { description = "dysFunctional Reactive Programming on Craftwerk"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "EEConfig" = callPackage @@ -5238,7 +5149,6 @@ self: { description = "Query language and report generator for edit logs"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Eight-Ball-Pool-Hack-Cheats" = callPackage @@ -5383,7 +5293,6 @@ self: { description = "Libary to interface with the NCBI Entrez REST service"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Enum" = callPackage @@ -5477,7 +5386,6 @@ self: { description = "Type-safe bindings to EsounD (ESD; Enlightened Sound Daemon)"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "EstProgress" = callPackage @@ -5516,7 +5424,6 @@ self: { description = "A new implementation of the LambdaMOO server"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) pcre;}; "Etage" = callPackage @@ -5553,7 +5460,6 @@ self: { description = "Data-flow based graph algorithms"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Eternal10Seconds" = callPackage @@ -5569,7 +5475,6 @@ self: { description = "A 2-D shooting game"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Etherbunny" = callPackage @@ -5592,7 +5497,6 @@ self: { description = "A network analysis toolkit for Haskell"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) libpcap;}; "EuroIT" = callPackage @@ -5639,7 +5543,6 @@ self: { description = "Interfaces with FreeSwitch Event Socket"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Extra" = callPackage @@ -5699,7 +5602,6 @@ self: { description = "Compose music"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "FM-SBLEX" = callPackage @@ -5714,7 +5616,6 @@ self: { description = "A set of computational morphology tools for Swedish diachronic lexicons"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "FModExRaw" = callPackage @@ -5807,7 +5708,6 @@ self: { description = "A command-line FTP client"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Facebook-Password-Hacker-Online-Latest-Version" = callPackage @@ -5850,7 +5750,6 @@ self: { description = "A collection of facts about the real world"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "FailureT" = callPackage @@ -5863,7 +5762,6 @@ self: { description = "Failure Monad Transformer"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "FastPush" = callPackage @@ -5928,7 +5826,6 @@ self: { description = "Annotate ps and pdf documents"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "FerryCore" = callPackage @@ -5979,7 +5876,6 @@ self: { description = "Functional 3D"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "FileManip" = callPackage @@ -6031,7 +5927,6 @@ self: { description = "Functions on System.FilePath"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "FileSystem" = callPackage @@ -6084,8 +5979,6 @@ self: { ]; description = "Finite totally-ordered sets"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Finance-Quote-Yahoo" = callPackage @@ -6120,7 +6013,6 @@ self: { description = "Obtain Treasury yield curve data"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "FindBin" = callPackage @@ -6144,7 +6036,6 @@ self: { description = "A finite map implementation, derived from the paper: Efficient sets: a balancing act, S. Adams, Journal of functional programming 3(4) Oct 1993, pp553-562"; license = lib.licenses.bsdOriginal; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "FirstOrderTheory" = callPackage @@ -6157,7 +6048,6 @@ self: { description = "Grammar and typeclass for first order theories"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "FixedPoint-simple" = callPackage @@ -6188,7 +6078,6 @@ self: { description = "Wiki"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "FloatingHex" = callPackage @@ -6312,7 +6201,6 @@ self: { description = "Comparison of trees and forests"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ForkableT" = callPackage @@ -6351,7 +6239,6 @@ self: { description = "(Context-free) grammars in formal language theory"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Fortnite-Hack-Cheats-Free-V-Bucks-Generator" = callPackage @@ -6397,7 +6284,6 @@ self: { description = "Utilities to generate and solve puzzles"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "FpMLv53" = callPackage @@ -6501,7 +6387,6 @@ self: { description = "A library for accessing Postgres tables as in-memory data structures"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Frames-dsv" = callPackage @@ -6520,7 +6405,6 @@ self: { description = "Alternative CSV parser for the Frames package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Frames-map-reduce" = callPackage @@ -6580,7 +6464,6 @@ self: { description = "An experimental programming language with typed algebraic effects"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "FreeTypeGL" = callPackage @@ -6702,7 +6585,6 @@ self: { description = "A binding for GLFW (OGL)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs.xorg) libX11; inherit (pkgs.xorg) libXrandr;}; "GLFW-b" = callPackage @@ -6753,7 +6635,6 @@ self: { description = "GLFW utility functions to use together with monad-task"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GLHUI" = callPackage @@ -6873,7 +6754,6 @@ self: { description = "Parse GPX files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GPipe" = callPackage @@ -6907,7 +6787,6 @@ self: { description = "Load GPipe meshes from Collada files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GPipe-Core" = callPackage @@ -6949,7 +6828,6 @@ self: { description = "Examples for the GPipes package"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GPipe-GLFW" = callPackage @@ -6963,7 +6841,6 @@ self: { description = "GLFW OpenGL context creation for GPipe"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GPipe-GLFW4" = callPackage @@ -6994,7 +6871,6 @@ self: { description = "GLFW OpenGL context creation for GPipe"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GPipe-TextureLoad" = callPackage @@ -7007,7 +6883,6 @@ self: { description = "Load GPipe textures from filesystem"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GTALib" = callPackage @@ -7050,7 +6925,6 @@ self: { description = "Some kind of game library or set of utilities"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Ganymede" = callPackage @@ -7098,7 +6972,6 @@ self: { description = "Several games"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GenI" = callPackage @@ -7133,7 +7006,6 @@ self: { description = "A natural language generator (specifically, an FB-LTAG surface realiser)"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GenSmsPdu" = callPackage @@ -7148,7 +7020,6 @@ self: { description = "Automatic SMS message generator"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Genbank" = callPackage @@ -7168,7 +7039,6 @@ self: { description = "Libary for processing the NCBI genbank format"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Gene-CluEDO" = callPackage @@ -7195,7 +7065,6 @@ self: { description = "Hox gene clustering"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GeneralTicTacToe" = callPackage @@ -7250,7 +7119,6 @@ self: { description = "MCFGs for Genus-1 RNA Pseudoknots"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GeoIp" = callPackage @@ -7455,7 +7323,6 @@ self: { description = "SDL Frontend for Glome ray tracer"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GoogleChart" = callPackage @@ -7500,7 +7367,6 @@ self: { description = "Haskell Interface to Google Directions API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GoogleSB" = callPackage @@ -7517,7 +7383,6 @@ self: { description = "Interface to Google Safe Browsing API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GoogleSuggest" = callPackage @@ -7546,7 +7411,6 @@ self: { description = "Interface to Google Translate API"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GotoT-transformers" = callPackage @@ -7596,7 +7460,6 @@ self: { description = "Grammar products and higher-dimensional grammars"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Graph500" = callPackage @@ -7632,7 +7495,6 @@ self: { description = "GraphHammer Haskell graph analyses framework inspired by STINGER"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GraphHammer-examples" = callPackage @@ -7651,7 +7513,6 @@ self: { description = "Test harness for TriangleCount analysis"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GraphSCC" = callPackage @@ -7680,6 +7541,7 @@ self: { description = "Graph-Theoretic Analysis library"; license = "unknown"; hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "Grempa" = callPackage @@ -7759,7 +7621,6 @@ self: { description = "Notification utility for Growl"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Gtk2hsGenerics" = callPackage @@ -7776,7 +7637,6 @@ self: { description = "Convenience functions to extend Gtk2hs"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GtkGLTV" = callPackage @@ -7793,7 +7653,6 @@ self: { description = "OpenGL support for Gtk-based GUIs for Tangible Values"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GtkTV" = callPackage @@ -7807,8 +7666,6 @@ self: { ]; description = "Gtk-based GUIs for Tangible Values"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GuiHaskell" = callPackage @@ -7828,7 +7685,6 @@ self: { description = "A graphical REPL and development environment for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "GuiTV" = callPackage @@ -7841,7 +7697,6 @@ self: { description = "GUIs for Tangible Values"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "H" = callPackage @@ -7920,7 +7775,6 @@ self: { description = "HAppS data manipulation libraries"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HAppS-IxSet" = callPackage @@ -7937,7 +7791,6 @@ self: { ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HAppS-Server" = callPackage @@ -7959,7 +7812,6 @@ self: { description = "Web related tools and services"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HAppS-State" = callPackage @@ -7980,7 +7832,6 @@ self: { description = "Event-based distributed state"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HAppS-Util" = callPackage @@ -8031,8 +7882,6 @@ self: { ]; description = "High-level library for building command line interfaces"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HCard" = callPackage @@ -8685,7 +8534,6 @@ self: { description = "HJScript is a Haskell EDSL for writing JavaScript programs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HJVM" = callPackage @@ -8745,7 +8593,6 @@ self: { description = "Algebraic foundation for homomorphic learning"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HLearn-approximation" = callPackage @@ -8765,7 +8612,6 @@ self: { ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HLearn-classification" = callPackage @@ -8789,7 +8635,6 @@ self: { ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HLearn-datastructures" = callPackage @@ -8806,7 +8651,6 @@ self: { ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HLearn-distributions" = callPackage @@ -8831,7 +8675,6 @@ self: { description = "Distributions for use with the HLearn library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HList" = callPackage @@ -8956,7 +8799,6 @@ self: { description = "Happy Network Manager"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HNumeric" = callPackage @@ -9031,8 +8873,6 @@ self: { testHaskellDepends = [ base HTF ]; description = "Generation of PDF documents"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HPath" = callPackage @@ -9106,7 +8946,6 @@ self: { description = "A minimal monadic PLplot interface for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {plplotd-gnome2 = null;}; "HPong" = callPackage @@ -9126,7 +8965,6 @@ self: { description = "A simple OpenGL Pong game based on GLFW"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HROOT" = callPackage @@ -9145,7 +8983,6 @@ self: { description = "Haskell binding to the ROOT data analysis framework"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HROOT-core" = callPackage @@ -9160,7 +8997,6 @@ self: { description = "Haskell binding to ROOT Core modules"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HROOT-graf" = callPackage @@ -9177,7 +9013,6 @@ self: { description = "Haskell binding to ROOT Graf modules"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HROOT-hist" = callPackage @@ -9194,7 +9029,6 @@ self: { description = "Haskell binding to ROOT Hist modules"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HROOT-io" = callPackage @@ -9211,7 +9045,6 @@ self: { description = "Haskell binding to ROOT IO modules"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HROOT-math" = callPackage @@ -9228,7 +9061,6 @@ self: { description = "Haskell binding to ROOT Math modules"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HROOT-tree" = callPackage @@ -9245,7 +9077,6 @@ self: { description = "Haskell binding to ROOT Tree modules"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HRay" = callPackage @@ -9261,7 +9092,6 @@ self: { description = "Haskell raytracer"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HSFFIG" = callPackage @@ -9303,7 +9133,6 @@ self: { description = "Gene Expression Programming evolutionary algorithm in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HSH" = callPackage @@ -9341,7 +9170,6 @@ self: { description = "Convenience functions that use HSH, instances for HSH"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HSet" = callPackage @@ -9385,8 +9213,6 @@ self: { testHaskellDepends = [ aeson attoparsec base HTF text ]; description = "Small template engine"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HSoM" = callPackage @@ -9422,7 +9248,6 @@ self: { description = "Audio file reading/writing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HStringTemplate" = callPackage @@ -9460,7 +9285,6 @@ self: { description = "Convenience functions and instances for HStringTemplate"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HSvm" = callPackage @@ -9558,7 +9382,6 @@ self: { description = "Tableau based theorem prover for hybrid logics"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HTicTacToe" = callPackage @@ -9663,7 +9486,6 @@ self: { description = "A (prototyped) easy to use XMPP library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HXQ" = callPackage @@ -9711,7 +9533,6 @@ self: { description = "An Haskell library to drive the french Minitel through a serial port"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HaPy" = callPackage @@ -9760,7 +9581,6 @@ self: { description = "the Haskell Refactorer"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HaTeX" = callPackage @@ -9800,7 +9620,6 @@ self: { description = "This package is deprecated. From version 3, HaTeX does not need this anymore."; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HaTeX-qq" = callPackage @@ -9817,7 +9636,6 @@ self: { description = "Quasiquoters for HaTeX"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HaVSA" = callPackage @@ -9838,7 +9656,6 @@ self: { description = "An implementation of the Version Space Algebra learning framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HaXml" = callPackage @@ -9876,7 +9693,6 @@ self: { description = "Simple chat"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HackMail" = callPackage @@ -10010,7 +9826,6 @@ self: { description = "Harmony Analysis and Retrieval of Music"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HarmTrace-Base" = callPackage @@ -10079,7 +9894,6 @@ self: { description = "A Haskell library for inference using Gaussian processes"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Haschoo" = callPackage @@ -10119,7 +9933,6 @@ self: { description = "Simple shell written in Haskell"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HaskRel" = callPackage @@ -10137,7 +9950,6 @@ self: { description = "HaskRel, Haskell as a DBMS with support for the relational algebra"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HaskellAnalysisProgram" = callPackage @@ -10216,8 +10028,6 @@ self: { ]; description = "Client support for POP3, SMTP, and IMAP"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HaskellNet-SSL" = callPackage @@ -10337,7 +10147,6 @@ self: { description = "A small 2D game framework"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Hawk" = callPackage @@ -10360,7 +10169,6 @@ self: { description = "Haskell Web Application Kit"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Hayoo" = callPackage @@ -10388,7 +10196,6 @@ self: { description = "The Hayoo! search engine for Haskell API search on hackage"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Hclip" = callPackage @@ -10422,7 +10229,6 @@ self: { description = "Line oriented editor"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HerbiePlugin" = callPackage @@ -10481,7 +10287,6 @@ self: { description = "Purely functional 2D graphics for visualization"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HiggsSet" = callPackage @@ -10499,7 +10304,6 @@ self: { description = "A multi-index set with advanced query capabilites"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Hipmunk" = callPackage @@ -10514,6 +10318,7 @@ self: { description = "A Haskell binding for Chipmunk"; license = "unknown"; hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "Hipmunk-Utils" = callPackage @@ -10527,7 +10332,6 @@ self: { description = "Useful functions for Hipmunk"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HipmunkPlayground" = callPackage @@ -10621,7 +10425,6 @@ self: { description = "Lightweight algorithmic debugging"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HoleyMonoid" = callPackage @@ -10696,7 +10499,6 @@ self: { description = "A search and indexing engine"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Holumbus-Storage" = callPackage @@ -10748,7 +10550,6 @@ self: { description = "A Simple Key Value Store"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HostAndPort" = callPackage @@ -10805,7 +10606,6 @@ self: { description = "A Library and Preprocessor that makes it easier to create shared libs from Haskell programs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HsASA" = callPackage @@ -10925,7 +10725,6 @@ self: { description = "Haskell integration with Parrot virtual machine"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "HsPerl5" = callPackage @@ -11001,7 +10800,6 @@ self: { description = "Webots bindings for Haskell"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {Controller = null; driver = null;}; "HsYAML" = callPackage @@ -11067,7 +10865,6 @@ self: { description = "Stream Editor in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Hsmtlib" = callPackage @@ -11161,7 +10958,6 @@ self: { description = "The library for generating a WebGL scene for the web"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "I1M" = callPackage @@ -11228,7 +11024,6 @@ self: { description = "Editor and interpreter for Interaction Nets"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "IOR" = callPackage @@ -11262,7 +11057,6 @@ self: { description = "Atomic compare and swap for IORefs and STRefs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "IOSpec" = callPackage @@ -11393,7 +11187,6 @@ self: { description = "Length- and element-indexed lists sitting somewhere between homogeneous and fully heterogeneous"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "InfixApplicative" = callPackage @@ -11406,7 +11199,6 @@ self: { description = "liftA2 for infix operators"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "IntFormats" = callPackage @@ -11572,7 +11364,6 @@ self: { description = "A combinator library on top of a generalised JSON type"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "JSON-Combinator-Examples" = callPackage @@ -11587,7 +11378,6 @@ self: { description = "Example uses of the JSON-Combinator library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "JSONParser" = callPackage @@ -11620,7 +11410,6 @@ self: { description = "JSON parser that uses byte strings"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "JYU-Utils" = callPackage @@ -11672,7 +11461,6 @@ self: { description = "A utility to print the SourceFile attribute of one or more Java class files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Javav" = callPackage @@ -11736,7 +11524,6 @@ self: { description = "Design-by-contract for JavaScript"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "JsonGrammar" = callPackage @@ -11759,7 +11546,6 @@ self: { description = "Combinators for bidirectional JSON parsing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "JuPyTer-notebook" = callPackage @@ -11777,7 +11563,6 @@ self: { description = "JuPyTer notebook parser"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "JuicyPixels" = callPackage @@ -11969,7 +11754,6 @@ self: { ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "JunkDB-driver-hashtables" = callPackage @@ -11985,7 +11769,6 @@ self: { ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "JustParse" = callPackage @@ -12301,7 +12084,6 @@ self: { description = "Lightweight Directory Access Protocol (LDAP) version 3"; license = lib.licenses.gpl2Plus; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "LParse" = callPackage @@ -12410,7 +12192,6 @@ self: { description = "A type-safe EDSL for TouchDesigner written in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "LambdaHack" = callPackage @@ -12446,8 +12227,9 @@ self: { ]; description = "A game engine library for tactical squad ASCII roguelike dungeon crawlers"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; + platforms = [ + "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" + ]; }) {}; "LambdaINet" = callPackage @@ -12468,7 +12250,6 @@ self: { description = "Graphical Interaction Net Evaluator for Optimal Evaluation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "LambdaNet" = callPackage @@ -12511,7 +12292,6 @@ self: { description = "Quasiquoter, and Arbitrary helpers for the lambda calculus"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "LambdaShell" = callPackage @@ -12530,7 +12310,6 @@ self: { description = "Simple shell for evaluating lambda expressions"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Lambdajudge" = callPackage @@ -12745,7 +12524,6 @@ self: { description = "Partition the sequence of items to the subsequences in the order given"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "LinguisticsTypes" = callPackage @@ -12791,7 +12569,6 @@ self: { description = "Check a bunch of local html files for broken links"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Liquorice" = callPackage @@ -12964,7 +12741,6 @@ self: { description = "a parallel implementation of logic programming using distributed tree exploration"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "LogicGrowsOnTrees-MPI" = callPackage @@ -12987,7 +12763,6 @@ self: { description = "an adapter for LogicGrowsOnTrees that uses MPI"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {openmpi = null;}; "LogicGrowsOnTrees-network" = callPackage @@ -13014,7 +12789,6 @@ self: { description = "an adapter for LogicGrowsOnTrees that uses multiple processes running in a network"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "LogicGrowsOnTrees-processes" = callPackage @@ -13042,7 +12816,6 @@ self: { description = "an adapter for LogicGrowsOnTrees that uses multiple processes for parallelism"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "LslPlus" = callPackage @@ -13064,7 +12837,6 @@ self: { description = "An execution and testing framework for the Linden Scripting Language (LSL)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Lucu" = callPackage @@ -13086,7 +12858,6 @@ self: { description = "HTTP Daemonic Library"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Lykah" = callPackage @@ -13116,7 +12887,6 @@ self: { description = "A static website and blog generator"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "MASMGen" = callPackage @@ -13163,7 +12933,6 @@ self: { description = "Folding algorithm based on nucleotide cyclic motifs"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "MFlow" = callPackage @@ -13190,7 +12959,6 @@ self: { description = "stateful, RESTful web framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "MHask" = callPackage @@ -13258,7 +13026,6 @@ self: { description = "A GLPK backend to the MIP library"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) glpk;}; "MSQueue" = callPackage @@ -13271,7 +13038,6 @@ self: { description = "Michael-Scott queue"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "MTGBuilder" = callPackage @@ -13422,7 +13188,6 @@ self: { description = "MaybeT monad transformer using transformers instead of mtl"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "MazesOfMonad" = callPackage @@ -13538,7 +13303,6 @@ self: { description = "A meta-object system for Haskell based on Perl 6"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Metrics" = callPackage @@ -13551,7 +13315,6 @@ self: { description = "Evaluation metrics commonly used in supervised machine learning"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Mhailist" = callPackage @@ -13571,7 +13334,6 @@ self: { description = "Haskell mailing list manager"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Michelangelo" = callPackage @@ -13589,7 +13351,6 @@ self: { description = "OpenGL for dummies"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "MicrosoftTranslator" = callPackage @@ -13607,7 +13368,6 @@ self: { description = "Interface for Microsoft Translator"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "MiniAgda" = callPackage @@ -13691,7 +13451,6 @@ self: { description = "Haskell interface to Python"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Mobile-Legends-Hack-Cheats" = callPackage @@ -13776,7 +13535,6 @@ self: { description = "Monad-transformer version of the Control.Exception module"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "MonadCatchIO-mtl-foreign" = callPackage @@ -13789,7 +13547,6 @@ self: { description = "Polymorphic combinators for working with foreign functions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "MonadCatchIO-transformers" = callPackage @@ -13823,7 +13580,6 @@ self: { description = "Polymorphic combinators for working with foreign functions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "MonadCompose" = callPackage @@ -13854,7 +13610,6 @@ self: { description = "Automatically generate layered monads"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "MonadPrompt" = callPackage @@ -13959,7 +13714,6 @@ self: { description = "A simple tetris clone"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Monatron" = callPackage @@ -13985,7 +13739,6 @@ self: { description = "MonadIO instances for the Monatron transformers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Monocle" = callPackage @@ -13998,7 +13751,6 @@ self: { description = "Symbolic computations in strict monoidal categories with LaTeX output"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "MorseCode" = callPackage @@ -14047,7 +13799,6 @@ self: { description = "Automated Mutation Testing for HUnit tests"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "MuCheck-Hspec" = callPackage @@ -14063,7 +13814,6 @@ self: { description = "Automated Mutation Testing for Hspec tests"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "MuCheck-QuickCheck" = callPackage @@ -14079,7 +13829,6 @@ self: { description = "Automated Mutation Testing for QuickCheck tests"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "MuCheck-SmallCheck" = callPackage @@ -14095,7 +13844,6 @@ self: { description = "Automated Mutation Testing for SmallCheck tests"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Munkres" = callPackage @@ -14187,7 +13935,6 @@ self: { description = "Most likely order of mutation events in RNA"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "MyPrimes" = callPackage @@ -14274,7 +14021,6 @@ self: { description = "A Haskell interface to Lego Mindstorms NXT"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {bluetooth = null;}; "NXTDSL" = callPackage @@ -14372,7 +14118,6 @@ self: { description = "Instances of NcStore for hypercuboids"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "NaturalLanguageAlphabets" = callPackage @@ -14437,7 +14182,6 @@ self: { description = "Context Algebra of near"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Neks" = callPackage @@ -14565,7 +14309,6 @@ self: { description = "Ninja game"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "NoHoed" = callPackage @@ -14597,7 +14340,6 @@ self: { description = "Microbenchmarks for various array libraries"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "NoTrace" = callPackage @@ -14643,7 +14385,6 @@ self: { description = "A Nomic game in haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Nomyx-Core" = callPackage @@ -14671,7 +14412,6 @@ self: { description = "A Nomic game in haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Nomyx-Language" = callPackage @@ -14692,7 +14432,6 @@ self: { description = "Language to express rules for Nomic"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Nomyx-Rules" = callPackage @@ -14711,7 +14450,6 @@ self: { description = "Language to express rules for Nomic"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Nomyx-Web" = callPackage @@ -14737,7 +14475,6 @@ self: { description = "Web gui for Nomyx"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "NonEmpty" = callPackage @@ -14768,7 +14505,6 @@ self: { description = "A list with a length of at least one"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "NumInstances" = callPackage @@ -14847,7 +14583,6 @@ self: { description = "Nussinov78 using the ADPfusion library"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Nutri" = callPackage @@ -14916,7 +14651,6 @@ self: { description = "Parse OpenStreetMap files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "OTP" = callPackage @@ -15084,7 +14818,6 @@ self: { description = "Text UI library for performing parallel remote SSH operations"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "OneTuple" = callPackage @@ -15150,7 +14883,6 @@ self: { description = "Assorted utilities to work with AFP data streams"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "OpenAL" = callPackage @@ -15243,7 +14975,6 @@ self: { description = "Quickcheck instances for various data structures"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "OpenGLRaw" = callPackage @@ -15292,7 +15023,6 @@ self: { description = "ADT wrapper and renderer for OpenSCAD models"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "OpenVG" = callPackage @@ -15305,7 +15035,6 @@ self: { description = "OpenVG (ShivaVG-0.2.1) binding"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "OpenVGRaw" = callPackage @@ -15504,7 +15233,6 @@ self: { description = "An addon to PCLT package: enchance PCLT catalog with PostgreSQL powers"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "PDBtools" = callPackage @@ -15611,7 +15339,6 @@ self: { description = "Page-oriented extraction and composition library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Paillier" = callPackage @@ -15679,7 +15406,6 @@ self: { description = "a code generator for partial differential equations solvers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Parallel-Arrows-BaseSpec" = callPackage @@ -15730,7 +15456,6 @@ self: { description = "Eden based backend for @Parallel-Arrows-Definition@"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Parallel-Arrows-Multicore" = callPackage @@ -15934,7 +15659,6 @@ self: { description = "Permutations of effectful computations"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Persistence" = callPackage @@ -16064,7 +15788,6 @@ self: { description = "Real-time line plotter for generic data"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "PlslTools" = callPackage @@ -16085,7 +15808,6 @@ self: { description = "So far just a lint like program for PL/SQL. Diff and refactoring tools are planned"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Plural" = callPackage @@ -16256,7 +15978,6 @@ self: { libraryHaskellDepends = [ base haskell98 pretty template-haskell ]; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "PriorityChansConverger" = callPackage @@ -16282,7 +16003,6 @@ self: { description = "Probability distribution monads"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Probnet" = callPackage @@ -16360,7 +16080,6 @@ self: { description = "A Perl 6 Implementation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Pup-Events" = callPackage @@ -16381,7 +16100,6 @@ self: { description = "A networked event handling framework for hooking into other programs"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Pup-Events-Client" = callPackage @@ -16416,7 +16134,6 @@ self: { description = "A networked event handling framework for hooking into other programs"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Pup-Events-PQueue" = callPackage @@ -16556,7 +16273,6 @@ self: { description = "Programming with Eventual Consistency over Cassandra"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "QuickAnnotate" = callPackage @@ -16800,7 +16516,6 @@ self: { description = "Binding to code that controls a Segway RMP"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {canlib = null; ftd2xx = null;}; "RNAFold" = callPackage @@ -16824,7 +16539,6 @@ self: { description = "RNA secondary structure prediction"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "RNAFoldProgs" = callPackage @@ -16845,7 +16559,6 @@ self: { description = "RNA secondary structure folding"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "RNAdesign" = callPackage @@ -16872,7 +16585,6 @@ self: { description = "Multi-target RNA sequence design"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "RNAdraw" = callPackage @@ -16893,7 +16605,6 @@ self: { description = "Draw RNA secondary structures"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "RNAlien" = callPackage @@ -16927,7 +16638,6 @@ self: { description = "Unsupervized construction of RNA family models"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "RNAwolf" = callPackage @@ -16949,7 +16659,6 @@ self: { description = "RNA folding with non-canonical basepairs and base-triplets"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "RSA" = callPackage @@ -17117,7 +16826,6 @@ self: { description = "HTTP to XMPP omegle chats gate"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Rasenschach" = callPackage @@ -17381,7 +17089,6 @@ self: { description = "quasiquoter for inline-R code"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "RollingDirectory" = callPackage @@ -17407,7 +17114,6 @@ self: { description = "Limits the size of a directory's contents"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "RoyalMonad" = callPackage @@ -17473,7 +17179,6 @@ self: { description = "Library for accessing S3 compatible storage services"; license = lib.licenses.gpl3Plus; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "SBench" = callPackage @@ -17492,7 +17197,6 @@ self: { description = "A benchmark suite for runtime and heap measurements over a series of inputs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "SCRIPTWriter" = callPackage @@ -17513,7 +17217,6 @@ self: { description = "ESCRIPT: a human friendly language for programming Bitcoin scripts"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "SCalendar" = callPackage @@ -17531,7 +17234,6 @@ self: { description = "This is a library for handling calendars and resource availability based on the \"top-nodes algorithm\" and set operations"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "SDL" = callPackage @@ -17664,7 +17366,6 @@ self: { description = "Higher level library on top of SFML"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "SFont" = callPackage @@ -17677,7 +17378,6 @@ self: { description = "SFont SDL Bitmap Fonts"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "SG" = callPackage @@ -17705,7 +17405,6 @@ self: { description = "An example of using the SG and OpenGL libraries"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "SGplus" = callPackage @@ -17873,7 +17572,6 @@ self: { description = "STLink USB interface in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "STM32-Zombie" = callPackage @@ -17891,7 +17589,6 @@ self: { description = "control a STM32F103 microcontroller"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "STM32F103xx-SVD" = callPackage @@ -17954,7 +17651,6 @@ self: { description = "Code generation tool for Quartz code from a SVG"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "SVGFonts" = callPackage @@ -18142,7 +17838,6 @@ self: { description = "Scientific workflow management system"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "SciFlow-drmaa" = callPackage @@ -18160,7 +17855,6 @@ self: { description = "Scientific workflow management system"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ScratchFs" = callPackage @@ -18200,7 +17894,6 @@ self: { description = "A cross platform P2P VPN application built using Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "SecureHash-SHA3" = callPackage @@ -18254,7 +17947,6 @@ self: { description = "Selects a representative subset of sequences from multiple sequence alignment"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Semantique" = callPackage @@ -18335,6 +18027,34 @@ self: { broken = true; }) {}; + "ShellCheck_0_7_1" = callPackage + ({ mkDerivation, aeson, array, base, bytestring, containers + , deepseq, Diff, directory, filepath, mtl, parsec, process + , QuickCheck, regex-tdfa + }: + mkDerivation { + pname = "ShellCheck"; + version = "0.7.1"; + sha256 = "06m4wh891nah3y0br4wh3adpsb16zawkb2ijgf1vcz61fznj6ps1"; + isLibrary = true; + isExecutable = true; + libraryHaskellDepends = [ + aeson array base bytestring containers deepseq Diff directory + filepath mtl parsec process QuickCheck regex-tdfa + ]; + executableHaskellDepends = [ + aeson array base bytestring containers deepseq Diff directory + filepath mtl parsec QuickCheck regex-tdfa + ]; + testHaskellDepends = [ + aeson array base bytestring containers deepseq Diff directory + filepath mtl parsec QuickCheck regex-tdfa + ]; + description = "Shell script analysis tool"; + license = lib.licenses.gpl3Only; + hydraPlatforms = lib.platforms.none; + }) {}; + "ShellCheck" = callPackage ({ mkDerivation, aeson, array, base, bytestring, containers , deepseq, Diff, directory, filepath, mtl, parsec, process @@ -18389,7 +18109,6 @@ self: { description = "\"compatline\" backend module for Shellac"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Shellac-editline" = callPackage @@ -18404,7 +18123,6 @@ self: { description = "Editline backend module for Shellac"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Shellac-haskeline" = callPackage @@ -18417,7 +18135,6 @@ self: { description = "Haskeline backend module for Shellac"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Shellac-readline" = callPackage @@ -18432,7 +18149,6 @@ self: { description = "Readline backend module for Shellac"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ShortestPathProblems" = callPackage @@ -18454,7 +18170,6 @@ self: { description = "grammars for TSP and SHP"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ShowF" = callPackage @@ -18502,7 +18217,6 @@ self: { description = "A Virtual Dom in pure Haskell, based on Html as an Alignable Functor"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Shpadoinkle-backend-snabbdom" = callPackage @@ -18534,7 +18248,6 @@ self: { description = "A backend for rendering Shpadoinkle as Text"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Shpadoinkle-console" = callPackage @@ -18581,7 +18294,6 @@ self: { description = "Chrome extension to aide in development"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Shpadoinkle-disembodied" = callPackage @@ -18601,7 +18313,6 @@ self: { description = "Shpadoinkle as a static site"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Shpadoinkle-examples" = callPackage @@ -18634,7 +18345,6 @@ self: { description = "Example usages of Shpadoinkle"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Shpadoinkle-html" = callPackage @@ -18654,7 +18364,6 @@ self: { description = "A typed, template generated Html DSL, and helpers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Shpadoinkle-lens" = callPackage @@ -18690,7 +18399,6 @@ self: { description = "A single page application rounter for Shpadoinkle based on Servant"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Shpadoinkle-streaming" = callPackage @@ -18725,7 +18433,6 @@ self: { description = "Read standard file formats into Shpadoinkle with Template Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Shpadoinkle-widgets" = callPackage @@ -18750,7 +18457,6 @@ self: { description = "A collection of common reusable types and components"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Shrub" = callPackage @@ -18814,7 +18520,6 @@ self: { description = "A Simple Graphics Library from the SimpleH framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "SimpleH" = callPackage @@ -18852,7 +18557,6 @@ self: { description = "Simple, configurable logging"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "SimpleServer" = callPackage @@ -18874,7 +18578,6 @@ self: { description = "A simple static file server, for when apache is overkill"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "SimpleTableGenerator" = callPackage @@ -18953,7 +18656,6 @@ self: { description = "A tiny, lazy SMT solver"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "SmtLib" = callPackage @@ -18990,7 +18692,6 @@ self: { description = "E-library directory based on FUSE virtual file system"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) zip;}; "SoOSiM" = callPackage @@ -19029,7 +18730,6 @@ self: { description = "Football simulation framework for teaching functional programming"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "SoccerFunGL" = callPackage @@ -19050,7 +18750,6 @@ self: { description = "OpenGL UI for the SoccerFun framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Sonnex" = callPackage @@ -19084,7 +18783,6 @@ self: { description = "Static code analysis using graph-theoretic techniques"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Southpaw" = callPackage @@ -19154,7 +18852,6 @@ self: { description = "Lock free Spin Counter"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Spintax" = callPackage @@ -19246,7 +18943,6 @@ self: { description = "Provides authentification helpers for Spock"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Spock-core" = callPackage @@ -19303,7 +18999,6 @@ self: { description = "Lucid support for Spock"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Spock-worker" = callPackage @@ -19322,7 +19017,6 @@ self: { description = "Background workers for Spock"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "SpreadsheetML" = callPackage @@ -19426,7 +19120,6 @@ self: { description = "Libary for Stockholm aligmnent format"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Stomp" = callPackage @@ -19477,7 +19170,6 @@ self: { description = "Converts SDF to Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Strafunski-StrategyLib" = callPackage @@ -19641,7 +19333,6 @@ self: { description = "Syntax Macros in the form of an EDSL"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Sysmon" = callPackage @@ -19776,8 +19467,6 @@ self: { libraryHaskellDepends = [ base DeepArrow TypeCompose ]; description = "Tangible Values -- composable interfaces"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "TYB" = callPackage @@ -19934,7 +19623,6 @@ self: { description = "Libary for parsing, processing and vizualization of taxonomy data"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "TaxonomyTools" = callPackage @@ -19955,7 +19643,6 @@ self: { description = "Tool for parsing, processing, comparing and visualizing taxonomy data"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "TeX-my-math" = callPackage @@ -19985,7 +19672,6 @@ self: { description = "Render general Haskell math to LaTeX. Or: math typesetting with high signal-to-noise–ratio."; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "TeaHS" = callPackage @@ -20002,7 +19688,6 @@ self: { description = "TeaHS Game Creation Library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Tensor" = callPackage @@ -20100,6 +19785,7 @@ self: { description = "Haskell bindings for the Apache Thrift RPC system"; license = "unknown"; hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "Tic-Tac-Toe" = callPackage @@ -20332,7 +20018,6 @@ self: { description = "Wait-free Tree Counter"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "TreeStructures" = callPackage @@ -20369,7 +20054,6 @@ self: { description = "Lock free Treiber stack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "TrendGraph" = callPackage @@ -20406,7 +20090,6 @@ self: { description = "Automatic type inference of generalized tries with Template Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Twofish" = callPackage @@ -20446,7 +20129,6 @@ self: { description = "Typing speed game"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "TypeCompose" = callPackage @@ -20474,7 +20156,6 @@ self: { description = "TypeIlluminator is a prototype tool exploring debugging of type errors/"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "TypeNat" = callPackage @@ -20534,7 +20215,6 @@ self: { description = "A small command-line accounting tool"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "URLT" = callPackage @@ -20553,7 +20233,6 @@ self: { description = "Library for maintaining correctness of URLs within an application"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "URLb" = callPackage @@ -20665,7 +20344,6 @@ self: { description = "Url dispatcher. Helps to retain friendly URLs in web applications."; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Useful" = callPackage @@ -20881,7 +20559,6 @@ self: { description = "ViennaRNA v2 extensions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ViennaRNAParser" = callPackage @@ -20972,7 +20649,6 @@ self: { description = "WAVE audio file IO library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "WEditor" = callPackage @@ -21003,7 +20679,6 @@ self: { description = "Text-editor widget with dynamic line-wrapping for use with Brick"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "WEditorHyphen" = callPackage @@ -21017,7 +20692,6 @@ self: { description = "Language-specific hyphenation policies for WEditor"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "WL500gPControl" = callPackage @@ -21035,7 +20709,6 @@ self: { description = "A simple command line tools to control the Asus WL500gP router"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "WL500gPLib" = callPackage @@ -21085,7 +20758,6 @@ self: { description = "Convert the WURFL file into a Parsec parser"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "WXDiffCtrl" = callPackage @@ -21099,7 +20771,6 @@ self: { description = "WXDiffCtrl"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "WashNGo" = callPackage @@ -21119,7 +20790,6 @@ self: { description = "WASH is a family of EDSLs for programming Web applications in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "WaveFront" = callPackage @@ -21137,7 +20807,6 @@ self: { description = "Parsers and utilities for the OBJ WaveFront 3D model format"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Weather" = callPackage @@ -21182,7 +20851,6 @@ self: { description = "JavaScript analysis tools"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "WebBits-multiplate" = callPackage @@ -21200,7 +20868,6 @@ self: { description = "A Multiplate instance for JavaScript"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "WebCont" = callPackage @@ -21220,7 +20887,6 @@ self: { description = "Continuation based web programming for Happstack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "WeberLogic" = callPackage @@ -21526,7 +21192,6 @@ self: { description = "Bigram word pair alignments"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "WordNet" = callPackage @@ -21608,7 +21273,6 @@ self: { description = "Generic (SYB3) construction of wxHaskell widgets"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "X" = callPackage @@ -21809,7 +21473,6 @@ self: { description = "XMPP library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "XSaiga" = callPackage @@ -21837,7 +21500,6 @@ self: { description = "An implementation of a polynomial-time top-down parser suitable for NLP"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Xauth" = callPackage @@ -21917,7 +21579,6 @@ self: { description = "Yet Another Pong Clone using SDL"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "YFrob" = callPackage @@ -21966,7 +21627,6 @@ self: { description = "A simple blog engine powered by Yesod"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "YamlReference" = callPackage @@ -22073,7 +21733,6 @@ self: { description = "A MUD client library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Yogurt-Standalone" = callPackage @@ -22094,7 +21753,6 @@ self: { description = "A functional MUD client"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) readline;}; "Z-Data" = callPackage @@ -22150,7 +21808,6 @@ self: { description = "Simple and high performance IO toolkit for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Z-MessagePack" = callPackage @@ -22176,7 +21833,6 @@ self: { description = "MessagePack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "Z-YAML" = callPackage @@ -22195,7 +21851,6 @@ self: { description = "YAML tools"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ZEBEDDE" = callPackage @@ -22315,7 +21970,6 @@ self: { description = "Compare genome assemblies"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "abacate" = callPackage @@ -22370,7 +22024,6 @@ self: { description = "Bindings for ABC, A System for Sequential Synthesis and Verification"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {abc = null;}; "abcnotation" = callPackage @@ -22543,7 +22196,6 @@ self: { description = "Drive Aho-Corasick machines in Conduit pipelines"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "acc" = callPackage @@ -22611,7 +22263,6 @@ self: { description = "Linear algebra and interpolation using the Accelerate framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "accelerate-bignum" = callPackage @@ -22851,7 +22502,6 @@ self: { description = "Fast Fourier transform and convolution using the Accelerate framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "accelerate-fourier-benchmark" = callPackage @@ -23129,7 +22779,6 @@ self: { description = "a typesafe way encode accelerate matrices and vectors"; license = lib.licenses.isc; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "accelerate-utility" = callPackage @@ -23196,7 +22845,6 @@ self: { description = "Provides Access Token for Services"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "accuerr" = callPackage @@ -23772,7 +23420,6 @@ self: { description = "The flexibility of Haskell and the safety of PHP"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "acme-pointful-numbers" = callPackage @@ -23966,7 +23613,6 @@ self: { description = "AcousticBrainz API client"; license = lib.licenses.cc0; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "acquire" = callPackage @@ -24038,7 +23684,6 @@ self: { description = "Haskell code presentation tool"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "activehs-base" = callPackage @@ -24095,7 +23740,6 @@ self: { description = "Actors with multi-headed receive clauses"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "acts" = callPackage @@ -24235,7 +23879,6 @@ self: { description = "A full-featured library for parsing, validating, and rendering email addresses"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "adhoc-network" = callPackage @@ -24254,7 +23897,6 @@ self: { description = "Ad-hoc P2P network protocol"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "adict" = callPackage @@ -24277,7 +23919,6 @@ self: { description = "Approximate dictionary searching"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "adjunction" = callPackage @@ -24395,7 +24036,6 @@ self: { description = "Subword construction in adp-multi using monadiccp"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "adtrees" = callPackage @@ -24431,8 +24071,6 @@ self: { testHaskellDepends = [ base directory filepath HUnit text ]; description = "Advent of Code REST API bindings and servant API"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "advent-of-code-ocr" = callPackage @@ -24508,7 +24146,6 @@ self: { description = "Exact real numbers via Cauchy sequences and MPFR"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aeson" = callPackage @@ -24823,8 +24460,6 @@ self: { ]; description = "Extra goodies for aeson"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aeson-filthy" = callPackage @@ -24969,8 +24604,6 @@ self: { ]; description = "Injecting fields into aeson values"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aeson-iproute" = callPackage @@ -25057,7 +24690,6 @@ self: { description = "Fast JSON parsing and encoding (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aeson-optics" = callPackage @@ -25606,7 +25238,6 @@ self: { description = "Infinite state model checking of iterative C programs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ag-pictgen" = callPackage @@ -25671,7 +25302,6 @@ self: { description = "Http server for Agda (prototype)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "agda-snippets" = callPackage @@ -25711,7 +25341,6 @@ self: { description = "Literate Agda support using agda-snippets, for Hakyll pages"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "agda-unused" = callPackage @@ -25734,8 +25363,6 @@ self: { testHaskellDepends = [ base containers filepath hspec text ]; description = "Check for unused code in an Agda project"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "agda2lagda" = callPackage @@ -25773,7 +25400,6 @@ self: { description = "AgentX protocol for write SNMP subagents"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "agum" = callPackage @@ -25837,7 +25463,6 @@ self: { description = "Aeronautical Information Package (AIP)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "air" = callPackage @@ -25945,7 +25570,6 @@ self: { description = "A Webmachine-inspired HTTP library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "airtable-api" = callPackage @@ -26014,7 +25638,6 @@ self: { description = "Parallel distributed discrete event simulation module for the Aivika library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aivika-experiment" = callPackage @@ -26080,8 +25703,6 @@ self: { ]; description = "Diagrams-based charting backend for the Aivika simulation library"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aivika-gpss" = callPackage @@ -26437,7 +26058,6 @@ self: { description = "Model and test API surfaces algebraically"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "algebra-dag" = callPackage @@ -26474,7 +26094,6 @@ self: { description = "Companion library for the book Algebra-Driven Design by Sandy Maguire"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "algebra-sql" = callPackage @@ -26502,7 +26121,6 @@ self: { description = "Relational Algebra and SQL Code Generation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "algebraic" = callPackage @@ -26644,7 +26262,6 @@ self: { description = "A client implementing the Algolia search API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "algorithmic-composition-additional" = callPackage @@ -26876,7 +26493,6 @@ self: { description = "a practical affine language"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "alpaca-netcode" = callPackage @@ -26915,7 +26531,6 @@ self: { description = "A compiler for the Alpha language"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "alphachar" = callPackage @@ -27012,7 +26627,6 @@ self: { description = "Some simple interactive programs for sending MIDI control messages via ALSA"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "alsa-midi" = callPackage @@ -27087,7 +26701,6 @@ self: { description = "Tests for the ALSA audio signal library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "alsa-seq" = callPackage @@ -27125,7 +26738,6 @@ self: { description = "Tests for the ALSA sequencer library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "altcomposition" = callPackage @@ -27311,7 +26923,6 @@ self: { description = "Client library for amazon-emailer daemon"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "amazon-products" = callPackage @@ -28194,8 +27805,6 @@ self: { ]; description = "Amazon Elastic Compute Cloud SDK"; license = lib.licenses.mpl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "amazonka-ecr" = callPackage @@ -29307,8 +28916,6 @@ self: { ]; description = "Provides conduits to upload data to S3 using the Multipart API"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "amazonka-sagemaker" = callPackage @@ -29830,7 +29437,6 @@ self: { description = "Toolsuite for automated design of business processes"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "amqp" = callPackage @@ -29897,7 +29503,6 @@ self: { description = "A simple streamly wrapper for amqp"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "amqp-utils" = callPackage @@ -30022,7 +29627,6 @@ self: { description = "Client for analyze service"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "anansi" = callPackage @@ -30104,7 +29708,6 @@ self: { description = "Anatomy: Atomo documentation system"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "android" = callPackage @@ -30289,7 +29892,6 @@ self: { description = "Animation for sprites"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "animate-frames" = callPackage @@ -30312,7 +29914,6 @@ self: { description = "Convert sprite frames to animate files"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "animate-preview" = callPackage @@ -30339,7 +29940,6 @@ self: { description = "Preview tool for sprite animation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "animate-sdl2" = callPackage @@ -30352,7 +29952,6 @@ self: { description = "sdl2 + animate auxiliary library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "anki-tools" = callPackage @@ -30397,7 +29996,6 @@ self: { description = "Medium-level language that desugars to Morte"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "annihilator" = callPackage @@ -30460,7 +30058,6 @@ self: { description = "QuickCheck functions to accompany the anonymous-sums package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ansi-escape-codes" = callPackage @@ -30530,8 +30127,6 @@ self: { ]; description = "sdl-like functions for terminal applications, based on ansi-terminal"; license = lib.licenses.gpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ansi-wl-pprint" = callPackage @@ -30589,7 +30184,6 @@ self: { description = "A web interface to Antisplice dungeons"; license = lib.licenses.agpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "antfarm" = callPackage @@ -30640,7 +30234,6 @@ self: { description = "This is an IRC bot for Mafia and Resistance"; license = lib.licenses.agpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "antigate" = callPackage @@ -30697,8 +30290,6 @@ self: { testToolDepends = [ hspec-discover ]; description = "Please see the README on Github at "; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "antiope-contract" = callPackage @@ -30712,8 +30303,6 @@ self: { ]; description = "Please see the README on Github at "; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "antiope-core" = callPackage @@ -30740,8 +30329,6 @@ self: { testToolDepends = [ hspec-discover ]; description = "Please see the README on Github at "; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "antiope-dynamodb" = callPackage @@ -30764,8 +30351,6 @@ self: { testToolDepends = [ hspec-discover ]; description = "Please see the README on Github at "; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "antiope-es" = callPackage @@ -30785,8 +30370,6 @@ self: { testToolDepends = [ hspec-discover ]; description = "Please see the README on Github at "; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "antiope-messages" = callPackage @@ -30811,8 +30394,6 @@ self: { testToolDepends = [ hspec-discover ]; description = "Please see the README on Github at "; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "antiope-optparse-applicative" = callPackage @@ -30864,8 +30445,6 @@ self: { testToolDepends = [ hspec-discover ]; description = "Please see the README on Github at "; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "antiope-shell" = callPackage @@ -30895,8 +30474,6 @@ self: { testToolDepends = [ hspec-discover ]; description = "Please see the README on Github at "; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "antiope-sns" = callPackage @@ -30920,8 +30497,6 @@ self: { testToolDepends = [ hspec-discover ]; description = "Please see the README on Github at "; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "antiope-sqs" = callPackage @@ -30948,8 +30523,6 @@ self: { testToolDepends = [ hspec-discover ]; description = "Please see the README on Github at "; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "antiope-swf" = callPackage @@ -31055,7 +30628,6 @@ self: { description = "Haskell binding to the ANTLR parser generator C runtime library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {antlr3c = null;}; "anydbm" = callPackage @@ -31304,7 +30876,6 @@ self: { description = "Server and community browser for the game Tremulous"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "api-builder" = callPackage @@ -31457,7 +31028,6 @@ self: { description = "simple json-rpc client for PegNet"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "api-tools" = callPackage @@ -31492,8 +31062,6 @@ self: { benchmarkHaskellDepends = [ base criterion text time ]; description = "DSL for generating API boilerplate and docs"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "api-yoti" = callPackage @@ -31515,7 +31083,6 @@ self: { description = "Api bindings for Yoti services"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "apiary" = callPackage @@ -31549,7 +31116,6 @@ self: { description = "Simple and type safe web framework that generate web API documentation"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "apiary-authenticate" = callPackage @@ -31570,7 +31136,6 @@ self: { description = "authenticate support for apiary web framework"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "apiary-clientsession" = callPackage @@ -31589,7 +31154,6 @@ self: { description = "clientsession support for apiary web framework"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "apiary-cookie" = callPackage @@ -31606,7 +31170,6 @@ self: { description = "Cookie support for apiary web framework"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "apiary-eventsource" = callPackage @@ -31619,7 +31182,6 @@ self: { description = "eventsource support for apiary web framework"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "apiary-helics" = callPackage @@ -31640,7 +31202,6 @@ self: { description = "helics support for apiary web framework"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "apiary-http-client" = callPackage @@ -31658,7 +31219,6 @@ self: { description = "A http client for Apiary"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "apiary-logger" = callPackage @@ -31677,7 +31237,6 @@ self: { description = "fast-logger support for apiary web framework"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "apiary-memcached" = callPackage @@ -31697,7 +31256,6 @@ self: { description = "memcached client for apiary web framework"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "apiary-mongoDB" = callPackage @@ -31716,7 +31274,6 @@ self: { description = "mongoDB support for apiary web framework"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "apiary-persistent" = callPackage @@ -31735,7 +31292,6 @@ self: { description = "persistent support for apiary web framework"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "apiary-purescript" = callPackage @@ -31756,7 +31312,6 @@ self: { description = "purescript compiler for apiary web framework"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "apiary-redis" = callPackage @@ -31769,7 +31324,6 @@ self: { description = "redis support for apiary web framework"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "apiary-session" = callPackage @@ -31782,7 +31336,6 @@ self: { description = "session support for apiary web framework"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "apiary-websockets" = callPackage @@ -31795,7 +31348,6 @@ self: { description = "websockets support for apiary web framework"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "apioiaf-client" = callPackage @@ -31829,7 +31381,6 @@ self: { description = "A Template Haskell library for generating type safe API calls"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "apns-http2" = callPackage @@ -31890,7 +31441,6 @@ self: { description = "a faster debian repository"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "app-lens" = callPackage @@ -32336,8 +31886,6 @@ self: { testToolDepends = [ hspec-discover ]; description = "Datadog client for Haskell"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "arbor-lru-cache" = callPackage @@ -32454,7 +32002,6 @@ self: { description = "Metric library backend for datadog"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "arbor-postgres" = callPackage @@ -32569,7 +32116,6 @@ self: { description = "Distribute hackage packages to archlinux"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "arch-web" = callPackage @@ -32634,8 +32180,6 @@ self: { libraryToolDepends = [ cpphs ]; description = "Common interface using libarchive"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "archive-sig" = callPackage @@ -32745,7 +32289,6 @@ self: { description = "Website maintenance for Arch Linux packages"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "archnews" = callPackage @@ -32782,7 +32325,6 @@ self: { description = "Arduino programming in haskell using the Copilot stream DSL"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "arena" = callPackage @@ -32827,7 +32369,6 @@ self: { description = "Generate Attribute-Relation File Format (ARFF) files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "arghwxhaskell" = callPackage @@ -32842,7 +32383,6 @@ self: { description = "An interpreter for the Argh! programming language in wxHaskell"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "argon" = callPackage @@ -32870,7 +32410,6 @@ self: { description = "Measure your code's complexity"; license = lib.licenses.isc; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "argon2" = callPackage @@ -32952,7 +32491,6 @@ self: { description = "Go-to-definition for Haskell"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "arion" = callPackage @@ -33102,7 +32640,6 @@ self: { description = "Arithmetic circuits for zkSNARKs"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "arithmoi" = callPackage @@ -33180,8 +32717,6 @@ self: { ]; description = "Prevent serialization backwards compatibility problems using golden tests"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "arpa" = callPackage @@ -33249,8 +32784,6 @@ self: { testHaskellDepends = [ base tasty tasty-hunit ]; description = "Builders for arrays"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "array-chunks" = callPackage @@ -33268,8 +32801,6 @@ self: { ]; description = "Lists of chunks"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "array-forth" = callPackage @@ -33296,7 +32827,6 @@ self: { description = "A simple interpreter for arrayForth, the language used on GreenArrays chips"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "array-list" = callPackage @@ -33311,8 +32841,6 @@ self: { ]; description = "IsList instances of Array for OverloadedLists extension"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "array-memoize" = callPackage @@ -33398,7 +32926,6 @@ self: { description = "Memory-efficient ArrayList implementation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "arrow-extras" = callPackage @@ -33785,7 +33312,6 @@ self: { description = "ASCII table"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ascii-th" = callPackage @@ -33891,7 +33417,6 @@ self: { description = "Action Script Instrumentation Compiler"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "asif" = callPackage @@ -34176,7 +33701,6 @@ self: { description = "integration point of assert4hs and hspec"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "assert4hs-tasty" = callPackage @@ -34190,7 +33714,6 @@ self: { description = "Provider for tasty runner to run assert4hs tests"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "assertions" = callPackage @@ -34252,7 +33775,6 @@ self: { description = "The Assimp asset import library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) assimp;}; "assoc" = callPackage @@ -34363,7 +33885,6 @@ self: { description = "A library for writing JSON"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ast-path" = callPackage @@ -34459,7 +33980,6 @@ self: { description = "A GTK-based abstract syntax tree viewer for custom languages and parsers"; license = lib.licenses.bsdOriginal; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "astview-utils" = callPackage @@ -34776,7 +34296,6 @@ self: { description = "Atlassian Connect snaplet for the Snap Framework and helper code"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "atlassian-connect-descriptor" = callPackage @@ -34798,8 +34317,6 @@ self: { ]; description = "Code that helps you create a valid Atlassian Connect Descriptor"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "atmos" = callPackage @@ -34839,7 +34356,6 @@ self: { description = "dimensional-tf wrapper on atmos package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "atndapi" = callPackage @@ -34990,7 +34506,6 @@ self: { description = "An atomic counter implemented using the FFI"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "atomic-primops-vector" = callPackage @@ -35069,7 +34584,6 @@ self: { description = "Interface to automated theorem provers"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "atp-haskell" = callPackage @@ -35424,7 +34938,6 @@ self: { description = "Pass input from an enumerator to an Attoparsec parser"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "attoparsec-expr" = callPackage @@ -35455,7 +34968,6 @@ self: { description = "Parse IP data types with attoparsec"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "attoparsec-iso8601" = callPackage @@ -35489,7 +35001,6 @@ self: { description = "An adapter to convert attoparsec Parsers into blazing-fast Iteratees"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "attoparsec-parsec" = callPackage @@ -35548,7 +35059,6 @@ self: { description = "(deprecated)"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "attoparsec-time" = callPackage @@ -35599,7 +35109,6 @@ self: { description = "URI parser / printer using attoparsec"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "attoparsec-varword" = callPackage @@ -35647,7 +35156,6 @@ self: { description = "Embedded Turtle language compiler in Haskell, with Epic output"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "audacity" = callPackage @@ -35690,7 +35198,6 @@ self: { description = "A battery-included audiovisual framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "augeas" = callPackage @@ -35805,7 +35312,6 @@ self: { description = "A secure package manager for Arch Linux and the AUR"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "authenticate" = callPackage @@ -35901,7 +35407,6 @@ self: { description = "A library for writing papers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "auto" = callPackage @@ -36090,7 +35595,6 @@ self: { description = "Generate dependencies for KDE 5 Nix expressions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "autopack" = callPackage @@ -36194,7 +35698,6 @@ self: { description = "Server-side implementation of the Avers storage model"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "avers-api" = callPackage @@ -36212,7 +35715,6 @@ self: { description = "Types describing the core and extended Avers APIs"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "avers-api-docs" = callPackage @@ -36232,7 +35734,6 @@ self: { description = "Swagger documentation for the Avers API"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "avers-server" = callPackage @@ -36254,7 +35755,6 @@ self: { description = "Server implementation of the Avers API"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aviation-cessna172-diagrams" = callPackage @@ -36417,7 +35917,6 @@ self: { description = "Tool for decoding avro"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "avwx" = callPackage @@ -36466,7 +35965,6 @@ self: { description = "High-level Awesomium bindings"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "awesomium-glut" = callPackage @@ -36479,7 +35977,6 @@ self: { description = "Utilities for using Awesomium with GLUT"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "awesomium-raw" = callPackage @@ -36612,7 +36109,6 @@ self: { description = "Configuration types, parsers & renderers for AWS services"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aws-dynamodb-conduit" = callPackage @@ -36631,7 +36127,6 @@ self: { description = "Conduit-based interface for AWS DynamoDB"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aws-dynamodb-streams" = callPackage @@ -36655,7 +36150,6 @@ self: { description = "Haskell bindings for Amazon DynamoDB Streams"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aws-easy" = callPackage @@ -36759,7 +36253,6 @@ self: { description = "Haskell suite for the Elastic Transcoder service"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aws-general" = callPackage @@ -36813,7 +36306,6 @@ self: { description = "Bindings for Amazon Kinesis"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aws-kinesis-client" = callPackage @@ -36849,7 +36341,6 @@ self: { description = "A producer & consumer client library for AWS Kinesis"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aws-kinesis-reshard" = callPackage @@ -36879,7 +36370,6 @@ self: { description = "Reshard AWS Kinesis streams in response to Cloud Watch metrics"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aws-lambda" = callPackage @@ -36900,7 +36390,6 @@ self: { description = "Haskell bindings for AWS Lambda"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aws-lambda-haskell-runtime" = callPackage @@ -36944,8 +36433,6 @@ self: { ]; description = "Run wai applications on AWS Lambda"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aws-lambda-runtime" = callPackage @@ -36970,8 +36457,6 @@ self: { executableHaskellDepends = [ aeson base lens lens-aeson text ]; description = "Haskell on AWS Lambda Runtime API"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aws-larpi" = callPackage @@ -37011,7 +36496,6 @@ self: { description = "Keep your AWS credentials file up to date with MFA-carrying credentials"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aws-performance-tests" = callPackage @@ -37087,7 +36571,6 @@ self: { description = "AWS SDK for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aws-sdk-text-converter" = callPackage @@ -37132,7 +36615,6 @@ self: { description = "The xml parser for aws-sdk package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aws-ses-easy" = callPackage @@ -37152,8 +36634,6 @@ self: { benchmarkHaskellDepends = [ base criterion ]; description = "Wrapper over Amazonka's SES"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aws-sign4" = callPackage @@ -37178,7 +36658,6 @@ self: { description = "Amazon Web Services (AWS) Signature v4 HTTP request signer"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "aws-simple" = callPackage @@ -37222,7 +36701,6 @@ self: { description = "Bindings for AWS SNS Version 2013-03-31"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "axel" = callPackage @@ -37293,7 +36771,6 @@ self: { description = "Web EDSL for running in browsers and server nodes using transient"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "axiomatic-classes" = callPackage @@ -37334,7 +36811,6 @@ self: { description = "Interact with Azimuth from Haskell"; license = lib.licenses.mpl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "azubi" = callPackage @@ -37422,7 +36898,6 @@ self: { description = "Azure Functions Worker"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "azure-service-api" = callPackage @@ -37442,7 +36917,6 @@ self: { description = "Haskell bindings for the Microsoft Azure Service Management API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "azure-servicebus" = callPackage @@ -37461,7 +36935,6 @@ self: { description = "Haskell wrapper over Microsoft Azure ServiceBus REST API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "azurify" = callPackage @@ -37519,7 +36992,6 @@ self: { description = "Immutable disk-based B* trees"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "b9" = callPackage @@ -37593,7 +37065,6 @@ self: { description = "An implementation of a simple 2-player board game"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "backblaze-b2-hs" = callPackage @@ -37627,7 +37098,6 @@ self: { description = "A client library to access Backblaze B2 cloud storage in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "backdropper" = callPackage @@ -37646,7 +37116,6 @@ self: { description = "Rotates backdrops for X11 displays using Imagemagic"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "backprop" = callPackage @@ -37825,7 +37294,6 @@ self: { description = "Shipwire API client"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bamboo" = callPackage @@ -37847,7 +37315,6 @@ self: { description = "A blog engine on Hack"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bamboo-launcher" = callPackage @@ -37869,7 +37336,6 @@ self: { description = "bamboo-launcher"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bamboo-plugin-highlight" = callPackage @@ -37888,7 +37354,6 @@ self: { description = "A highlight middleware"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bamboo-plugin-photo" = callPackage @@ -37908,7 +37373,6 @@ self: { description = "A photo album middleware"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bamboo-theme-blueprint" = callPackage @@ -37928,7 +37392,6 @@ self: { description = "bamboo blueprint theme"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bamboo-theme-mini-html5" = callPackage @@ -37952,7 +37415,6 @@ self: { description = "bamboo mini html5 theme"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bamse" = callPackage @@ -37971,7 +37433,6 @@ self: { description = "A Windows Installer (MSI) generator framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bamstats" = callPackage @@ -37986,7 +37447,6 @@ self: { description = "A program to extract various information from BAM alignmnet files"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ban-instance" = callPackage @@ -38450,7 +37910,6 @@ self: { description = "Optics for the Base16 library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "base32" = callPackage @@ -38492,7 +37951,6 @@ self: { description = "Fast base32 and base32hex codec for ByteStrings"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "base32-lens" = callPackage @@ -38614,7 +38072,6 @@ self: { description = "Base62 encoding and decoding"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "base64" = callPackage @@ -38666,7 +38123,6 @@ self: { description = "Base64 encoding of byte sequences"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "base64-bytestring" = callPackage @@ -38867,7 +38323,6 @@ self: { description = "Baserock Definitions Schema"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "basex-client" = callPackage @@ -39047,7 +38502,6 @@ self: { description = "Batch processing toolset for Linux / Unix"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "battlenet" = callPackage @@ -39077,7 +38531,6 @@ self: { description = "Yesod integration for the battlenet package"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "battleplace" = callPackage @@ -39095,8 +38548,6 @@ self: { ]; description = "Core definitions for BattlePlace.io service"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "battleplace-api" = callPackage @@ -39110,8 +38561,6 @@ self: { ]; description = "Public API definitions of BattlePlace.io service"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "battleship-combinatorics" = callPackage @@ -39170,7 +38619,6 @@ self: { description = "A web-based implementation of battleships including an AI opponent"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bayes-stack" = callPackage @@ -39191,7 +38639,6 @@ self: { description = "Framework for inferring generative probabilistic models with Gibbs sampling"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bazel-coverage-report-renderer" = callPackage @@ -39258,7 +38705,6 @@ self: { description = "Tools for reading Big Binary Indexed files, e.g., bigBed, bigWig"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bcp47" = callPackage @@ -39278,8 +38724,6 @@ self: { ]; description = "Language tags as specified by BCP 47"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bcp47-orphans" = callPackage @@ -39299,8 +38743,6 @@ self: { ]; description = "BCP47 orphan instances"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bcrypt" = callPackage @@ -39360,7 +38802,6 @@ self: { description = "Tools for managing a content store of software packages"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) ostree;}; "bdcs-api" = callPackage @@ -39401,7 +38842,6 @@ self: { "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" ]; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) libgit2-glib;}; "bdd" = callPackage @@ -39508,7 +38948,6 @@ self: { description = "DB migration library for beam, targeting Postgres"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "beam-core" = callPackage @@ -39553,7 +38992,6 @@ self: { description = "SQL DDL support and migrations support library for Beam"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "beam-mysql" = callPackage @@ -39572,7 +39010,6 @@ self: { description = "Connection layer between beam and MySQL/MariaDB"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "beam-newtype-field" = callPackage @@ -39589,7 +39026,6 @@ self: { description = "A newtype for wrapping newtypes into beam schemas"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "beam-postgres" = callPackage @@ -39617,7 +39053,6 @@ self: { description = "Connection layer between beam and postgres"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "beam-sqlite" = callPackage @@ -39641,7 +39076,6 @@ self: { description = "Beam driver for SQLite"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "beam-th" = callPackage @@ -39664,7 +39098,6 @@ self: { description = "Template Haskell utilities for beam"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "beamable" = callPackage @@ -39720,7 +39153,6 @@ self: { description = "A pretty-printer for higher-order logic"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bech32" = callPackage @@ -39768,7 +39200,6 @@ self: { description = "Template Haskell extensions to the Bech32 library"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bed-and-breakfast" = callPackage @@ -39836,7 +39267,6 @@ self: { description = "Bein is a provenance and workflow management system for bioinformatics"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "belka" = callPackage @@ -39866,7 +39296,6 @@ self: { description = "HTTP client DSL"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bench" = callPackage @@ -39902,8 +39331,6 @@ self: { testHaskellDepends = [ base split text ]; description = "Plot and compare benchmarks"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bench-show" = callPackage @@ -40075,7 +39502,6 @@ self: { description = "An implementation of Python 3"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bert" = callPackage @@ -40223,7 +39649,6 @@ self: { description = "Bidirectionalization for Free! (POPL'09)"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bff-mono" = callPackage @@ -40257,7 +39682,6 @@ self: { description = "Implementation of the BGAPI serial protocol"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bgmax" = callPackage @@ -40502,7 +39926,6 @@ self: { description = "A parser for the Billboard chord dataset"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "billeksah-forms" = callPackage @@ -40521,7 +39944,6 @@ self: { description = "Leksah library"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "billeksah-main" = callPackage @@ -40541,7 +39963,6 @@ self: { description = "Leksah plugin base"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "billeksah-main-static" = callPackage @@ -40583,7 +40004,6 @@ self: { description = "Leksah library"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "billeksah-services" = callPackage @@ -40821,7 +40241,6 @@ self: { description = "read/write binary file"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "binary-generic" = callPackage @@ -41046,7 +40465,6 @@ self: { description = "Monad to ease implementing a binary network protocol over ZeroMQ"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "binary-search" = callPackage @@ -41136,7 +40554,6 @@ self: { description = "data serialization/deserialization io-streams library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "binary-strict" = callPackage @@ -41179,8 +40596,6 @@ self: { ]; description = "Tagged binary serialisation"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "binary-tree" = callPackage @@ -41290,8 +40705,6 @@ self: { testHaskellDepends = [ base HTF HUnit QuickCheck random ]; description = "Data Binding"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "binding-gtk" = callPackage @@ -41323,7 +40736,6 @@ self: { description = "Data Binding in WxHaskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bindings" = callPackage @@ -41427,7 +40839,6 @@ self: { description = "Low level bindings to Apache Portable Runtime Utility (APR Utility)"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {apr-util = null;}; "bindings-audiofile" = callPackage @@ -41697,6 +41108,7 @@ self: { description = "Low level bindings to the C levmar (Levenberg-Marquardt) library"; license = "unknown"; hydraPlatforms = lib.platforms.none; + broken = true; }) {inherit (pkgs) blas; liblapack = null;}; "bindings-libcddb" = callPackage @@ -41846,7 +41258,6 @@ self: { description = "bindings to Video For Linux Two (v4l2) kernel interfaces"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bindings-lxc" = callPackage @@ -41975,7 +41386,6 @@ self: { description = "PPDev bindings"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bindings-saga-cmd" = callPackage @@ -42168,7 +41578,6 @@ self: { description = "Example project using binembed to embed data in object files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bini" = callPackage @@ -42272,7 +41681,6 @@ self: { description = "Library for reading ace assembly files"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bioalign" = callPackage @@ -42285,7 +41693,6 @@ self: { description = "Data structures and helper functions for calculating alignments"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "biocore" = callPackage @@ -42313,7 +41720,6 @@ self: { description = "Library for reading fasta sequence files"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "biofastq" = callPackage @@ -42326,7 +41732,6 @@ self: { description = "A library for reading FASTQ files"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "biohazard" = callPackage @@ -42388,7 +41793,6 @@ self: { description = "A collection of bioinformatics tools"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "biophd" = callPackage @@ -42405,7 +41809,6 @@ self: { description = "Library for reading phd sequence files"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "biopsl" = callPackage @@ -42423,7 +41826,6 @@ self: { description = "Library and executables for working with PSL files"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "biosff" = callPackage @@ -42441,7 +41843,6 @@ self: { description = "Library and executables for working with SFF files"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "biostockholm" = callPackage @@ -42465,7 +41866,6 @@ self: { description = "Parsing and rendering of Stockholm files (used by Pfam, Rfam and Infernal)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bip32" = callPackage @@ -42487,7 +41887,6 @@ self: { description = "BIP-0032: Hierarchical Deterministic Wallets for Bitcoin and other cryptocurrencies"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "birch-beer" = callPackage @@ -42523,7 +41922,6 @@ self: { description = "Plot a colorful tree"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bird" = callPackage @@ -42545,7 +41943,6 @@ self: { description = "A simple, sinatra-inspired web framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "birds-of-paradise" = callPackage @@ -42644,7 +42041,6 @@ self: { description = "A bit array (aka bitset, bitmap, bit vector) API for numeric types"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bit-protocol" = callPackage @@ -42737,7 +42133,6 @@ self: { description = "Bitcoin address generation and rendering. Parsing coming soon."; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bitcoin-api" = callPackage @@ -42763,7 +42158,6 @@ self: { description = "Provides access to the RPC API of Bitcoin Core"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bitcoin-api-extra" = callPackage @@ -42787,7 +42181,6 @@ self: { description = "Higher level constructs on top of the bitcoin-api package"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bitcoin-block" = callPackage @@ -42809,7 +42202,6 @@ self: { description = "Utility functions for manipulating bitcoin blocks"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bitcoin-compact-filters" = callPackage @@ -42833,7 +42225,6 @@ self: { description = "BIP 158 compact block filters"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bitcoin-hash" = callPackage @@ -42891,7 +42282,6 @@ self: { description = "Bitcoin keys"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bitcoin-payment-channel" = callPackage @@ -42958,7 +42348,6 @@ self: { description = "Library to communicate with the Satoshi Bitcoin daemon"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bitcoin-script" = callPackage @@ -43002,7 +42391,6 @@ self: { description = "Resources for working with miniscript, and script descriptors"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bitcoin-tx" = callPackage @@ -43024,7 +42412,6 @@ self: { description = "Utility functions for manipulating bitcoin transactions"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bitcoin-types" = callPackage @@ -43045,7 +42432,6 @@ self: { description = "Provides consistent low-level types used commonly among Bitcoin implementations"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bitcoind-regtest" = callPackage @@ -43076,7 +42462,6 @@ self: { description = "A library for working with bitcoin-core regtest networks"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bitcoind-rpc" = callPackage @@ -43099,7 +42484,6 @@ self: { description = "A streamlined interface to bitcoin core using Haskoin types and Servant"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bitly-cli" = callPackage @@ -43116,7 +42500,6 @@ self: { description = "A command line tool to access bit.ly URL shortener."; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bitmap" = callPackage @@ -43156,7 +42539,6 @@ self: { description = "Bitmap library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bits" = callPackage @@ -43402,7 +42784,6 @@ self: { description = "Bittorrent protocol implementation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bittrex" = callPackage @@ -43484,8 +42865,6 @@ self: { ]; description = "Bitwise operations on bounded enumerations"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bitx-bitcoin" = callPackage @@ -43526,8 +42905,6 @@ self: { ]; description = "A lousy Prelude replacement by a lousy dude"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bizzlelude-js" = callPackage @@ -43603,7 +42980,6 @@ self: { description = "a stupid cron"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "black-jewel" = callPackage @@ -43706,7 +43082,6 @@ self: { description = "The BLAKE SHA-3 candidate hashes, in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "blank-canvas" = callPackage @@ -43836,7 +43211,6 @@ self: { description = "Library for reading Blast XML output"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "blatex" = callPackage @@ -43855,7 +43229,6 @@ self: { description = "Blog in LaTeX"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "blaze" = callPackage @@ -43927,7 +43300,6 @@ self: { description = "Enumeratees for the incremental conversion of builders to bytestrings"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "blaze-colonnade" = callPackage @@ -43947,7 +43319,6 @@ self: { description = "blaze-html backend for colonnade"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "blaze-from-html" = callPackage @@ -44198,7 +43569,6 @@ self: { description = "Bluetooth Low Energy (BLE) peripherals"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "blindpass" = callPackage @@ -44233,7 +43603,6 @@ self: { description = "Control library for blink(1) LED from ThingM"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "blip" = callPackage @@ -44253,7 +43622,6 @@ self: { description = "Python to bytecode compiler"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bliplib" = callPackage @@ -44352,7 +43720,6 @@ self: { description = "Very simple static blog software"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bloodhound" = callPackage @@ -44406,7 +43773,6 @@ self: { description = "Adds convenient Amazon ElasticSearch Service authentication to Bloodhound"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bloomfilter" = callPackage @@ -44485,7 +43851,6 @@ self: { description = "OpenGL Logic Game"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "blubber" = callPackage @@ -44504,7 +43869,6 @@ self: { description = "The blubber client; connects to the blubber server"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "blubber-server" = callPackage @@ -44618,7 +43982,6 @@ self: { description = "full-featured tiling for the GNOME desktop environment"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) gtk2;}; "bluetileutils" = callPackage @@ -44673,7 +44036,6 @@ self: { description = "Convert between pointfree and pointful expressions"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bmp" = callPackage @@ -44699,7 +44061,6 @@ self: { description = "Library for communication with the Bosch BNO055 orientation sensor"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "board-games" = callPackage @@ -44788,7 +44149,6 @@ self: { executableHaskellDepends = [ base hogre hois random ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "boilerplate" = callPackage @@ -44952,7 +44312,6 @@ self: { description = "Runtime support for BOND serialization"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bond-haskell-compiler" = callPackage @@ -44975,7 +44334,6 @@ self: { description = "Bond code generator for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bookkeeper" = callPackage @@ -45017,7 +44375,6 @@ self: { description = "Permissions for bookkeeper records"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bookkeeping" = callPackage @@ -45243,7 +44600,6 @@ self: { description = "Boomshine clone"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "boop" = callPackage @@ -45280,7 +44636,6 @@ self: { description = "Mathematically sound sound synthesis"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "boots" = callPackage @@ -45337,7 +44692,6 @@ self: { description = "Factory for quickly building a microservice"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "boots-web" = callPackage @@ -45358,7 +44712,6 @@ self: { description = "Factory for quickly building a web application"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bootstrap-types" = callPackage @@ -45414,7 +44767,6 @@ self: { description = "Metering System for OpenStack metrics provided by Vaultaire"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "boring" = callPackage @@ -45663,7 +45015,6 @@ self: { description = "audio-visual pseudo-physical simulation of colliding circles"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "box" = callPackage @@ -45692,7 +45043,6 @@ self: { description = "boxes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "box-csv" = callPackage @@ -45710,7 +45060,6 @@ self: { description = "See readme.md"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "box-socket" = callPackage @@ -45735,7 +45084,6 @@ self: { description = "Box websockets"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "box-tuples" = callPackage @@ -45909,7 +45257,6 @@ self: { description = "A simple Breakout game implementation"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "breve" = callPackage @@ -45933,8 +45280,6 @@ self: { ]; description = "a url shortener"; license = lib.licenses.gpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "brians-brain" = callPackage @@ -46056,7 +45401,6 @@ self: { description = "Bricks is a lazy functional language based on Nix"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bricks-internal" = callPackage @@ -46093,7 +45437,6 @@ self: { description = "..."; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bricks-parsec" = callPackage @@ -46115,7 +45458,6 @@ self: { description = "..."; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bricks-rendering" = callPackage @@ -46137,7 +45479,6 @@ self: { description = "..."; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bricks-syntax" = callPackage @@ -46159,7 +45500,6 @@ self: { description = "..."; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "brillig" = callPackage @@ -46389,7 +45729,6 @@ self: { description = "Streaming interface for the BronyRadioGermany API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "brotli" = callPackage @@ -46432,7 +45771,6 @@ self: { description = "Conduit interface for Brotli (RFC7932) compression"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "brotli-streams" = callPackage @@ -46454,7 +45792,6 @@ self: { description = "IO-Streams interface for Brotli (RFC7932) compression"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "browscap" = callPackage @@ -46530,8 +45867,6 @@ self: { ]; description = "BSON documents are JSON-like objects with a standard binary encoding"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bson-generic" = callPackage @@ -46569,8 +45904,6 @@ self: { libraryHaskellDepends = [ base bson lens text ]; description = "BSON lenses"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bson-mapping" = callPackage @@ -46639,7 +45972,6 @@ self: { description = "B-Tree on Unmanaged Heap"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "btree-concurrent" = callPackage @@ -46716,7 +46048,6 @@ self: { description = "Automates most of your plain text accounting data entry in ledger format"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "buffer" = callPackage @@ -46764,8 +46095,6 @@ self: { ]; description = "Library for efficiently building up buffers, one piece at a time"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "buffer-builder-aeson" = callPackage @@ -47032,7 +46361,6 @@ self: { description = "Tools for working with buildbox benchmark result files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "builder" = callPackage @@ -47087,7 +46415,6 @@ self: { description = "A library and an executable that provide an easy API for a Haskell IDE"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bullet" = callPackage @@ -47141,7 +46468,6 @@ self: { description = "Bulletproofs are short zero-knowledge proofs without a trusted setup"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bulmex" = callPackage @@ -47167,7 +46493,6 @@ self: { description = "Reflex infused with bulma (css)"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bumper" = callPackage @@ -47224,7 +46549,6 @@ self: { description = "List OP_RETURN cryptocurrency transaction outputs"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "burrito" = callPackage @@ -47274,7 +46598,6 @@ self: { description = "Haskell interface to the Bus Pirate binary interface"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "buster" = callPackage @@ -47310,7 +46633,6 @@ self: { description = "Almost but not quite entirely unlike FRP"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "buster-network" = callPackage @@ -47328,7 +46650,6 @@ self: { description = "Almost but not quite entirely unlike FRP"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bustle" = callPackage @@ -47428,7 +46749,6 @@ self: { description = "butterfly tilings"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "buttplug-hs-core" = callPackage @@ -47568,8 +46888,6 @@ self: { ]; description = "Library for creating command-line interfaces (colors, menus, etc.)"; license = lib.licenses.bsd2; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bytable" = callPackage @@ -47666,7 +46984,6 @@ self: { description = "Serialize to a small byte arrays"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bytedump" = callPackage @@ -47708,7 +47025,6 @@ self: { description = "Universal hashing of bytes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bytelog" = callPackage @@ -47725,7 +47041,6 @@ self: { description = "Fast logging"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "byteorder" = callPackage @@ -47790,8 +47105,6 @@ self: { benchmarkHaskellDepends = [ base gauge primitive ]; description = "Slicing managed and unmanaged memory"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bytesmith" = callPackage @@ -47817,7 +47130,6 @@ self: { description = "Nonresumable byte parser"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bytestring_0_11_1_0" = callPackage @@ -48115,7 +47427,6 @@ self: { description = "fast ByteString to number converting library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "bytestring-rematch" = callPackage @@ -48504,7 +47815,6 @@ self: { description = "Simple C0 Syntax Check"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "c0parser" = callPackage @@ -48677,8 +47987,6 @@ self: { ]; description = "A maintenance command of Haskell cabal packages"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cabal" = callPackage @@ -48706,8 +48014,6 @@ self: { libraryHaskellDepends = [ base Cabal filepath ]; description = "Cabal support for creating AppImage applications"; license = lib.licenses.agpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cabal-audit" = callPackage @@ -48763,7 +48069,6 @@ self: { description = "A command line program for managing the dependency versions in a cabal file"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cabal-build-programs" = callPackage @@ -48829,7 +48134,6 @@ self: { description = "CI Assistant for Haskell projects"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cabal-cargs" = callPackage @@ -48853,7 +48157,6 @@ self: { description = "A command line program for extracting compiler arguments from a cabal file"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cabal-constraints" = callPackage @@ -49488,7 +48791,6 @@ self: { description = "Helpers for quering .cabal files or hackageDB's 00-index.tar"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cabal-rpm" = callPackage @@ -49615,7 +48917,6 @@ self: { description = "Automated test tool for cabal projects"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cabal-test-bin" = callPackage @@ -49722,7 +49023,6 @@ self: { description = "Create Arch Linux packages from Cabal packages"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cabal2doap" = callPackage @@ -49926,7 +49226,6 @@ self: { description = "Create mandriva rpm from cabal package"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cabalrpmdeps" = callPackage @@ -49942,7 +49241,6 @@ self: { description = "Autogenerate rpm dependencies from cabal files"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cabalvchk" = callPackage @@ -50112,8 +49410,6 @@ self: { ]; description = "A vault-style cache implementation"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cachix" = callPackage @@ -50364,7 +49660,6 @@ self: { description = "A build-system library and driver"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cake3" = callPackage @@ -50414,7 +49709,6 @@ self: { description = "run turtle like LOGO with lojban"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cal-layout" = callPackage @@ -50460,7 +49754,6 @@ self: { description = "Examples for the Cal3d animation library"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cal3d-opengl" = callPackage @@ -50473,7 +49766,6 @@ self: { description = "OpenGL rendering for the Cal3D animation library"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "calamity" = callPackage @@ -50535,7 +49827,6 @@ self: { description = "A small compiler for arithmetic expressions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "calculator" = callPackage @@ -50558,7 +49849,6 @@ self: { description = "A calculator repl, with variables, functions & Mathematica like dynamic plots"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "caldims" = callPackage @@ -50580,7 +49870,6 @@ self: { description = "Calculation tool and library supporting units"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "caledon" = callPackage @@ -50658,7 +49947,6 @@ self: { description = "The call game engine"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "call-alloy" = callPackage @@ -50752,7 +50040,6 @@ self: { description = "CamFort - Cambridge Fortran infrastructure"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) flint;}; "camh" = callPackage @@ -50786,7 +50073,6 @@ self: { description = "Haskell implementation of the Campfire API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "can-i-haz" = callPackage @@ -50832,7 +50118,6 @@ self: { description = "Candid integration"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "canon" = callPackage @@ -50915,7 +50200,6 @@ self: { description = "Utilities for HTTP programming"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "canteven-listen-http" = callPackage @@ -51044,7 +50328,6 @@ self: { description = "CAO Compiler"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cap" = callPackage @@ -51060,7 +50343,6 @@ self: { description = "Interprets and debug the cap language"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "capability" = callPackage @@ -51218,7 +50500,6 @@ self: { description = "Simple web-server for organizing car-pooling for an event"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "caramia" = callPackage @@ -51279,7 +50560,6 @@ self: { description = "Drop emails from threads being watched into special CC folder"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cardano-coin-selection" = callPackage @@ -51301,8 +50581,6 @@ self: { ]; description = "Algorithms for coin selection and fee balancing"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cardano-transactions" = callPackage @@ -51427,7 +50705,6 @@ self: { description = "Specify Cabal files in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cas-hashable" = callPackage @@ -51573,7 +50850,6 @@ self: { description = "mid-level bindings to CasADi"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {casadi = null;}; "casadi-bindings-control" = callPackage @@ -51591,7 +50867,6 @@ self: { description = "low level bindings to casadi-control"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {casadi_control = null;}; "casadi-bindings-core" = callPackage @@ -51609,7 +50884,6 @@ self: { description = "autogenerated low level bindings to casadi"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {casadi = null;}; "casadi-bindings-internal" = callPackage @@ -51641,7 +50915,6 @@ self: { description = "low level bindings to casadi-ipopt_interface"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {casadi_ipopt_interface = null;}; "casadi-bindings-snopt-interface" = callPackage @@ -51659,7 +50932,6 @@ self: { description = "low level bindings to casadi-snopt_interface"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {casadi_snopt_interface = null;}; "cascading" = callPackage @@ -51771,8 +51043,6 @@ self: { benchmarkHaskellDepends = [ gauge mwc-random rerebase ]; description = "A converter for spinal, snake and camel cases"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cash" = callPackage @@ -51790,7 +51060,6 @@ self: { description = "the Computer Algebra SHell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "casing" = callPackage @@ -51998,7 +51267,6 @@ self: { description = "Haskell client for Cassandra's CQL protocol"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cassandra-thrift" = callPackage @@ -52198,7 +51466,6 @@ self: { description = "A high level driver for the Cassandra datastore"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cast" = callPackage @@ -52287,7 +51554,6 @@ self: { description = "Equation Manipulator"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "catalyst" = callPackage @@ -52338,7 +51604,6 @@ self: { description = "Categorical Monoids and Semirings"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "categories" = callPackage @@ -52389,7 +51654,6 @@ self: { description = "A meta-package documenting various packages inspired by category theory"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "category-printf" = callPackage @@ -52711,7 +51975,6 @@ self: { description = "High-level interface to CCTools' WorkQueue library"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {dttools = null;}; "cdeps" = callPackage @@ -52795,7 +52058,6 @@ self: { description = "Simple wrapper around cef3-raw"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ceilometer-common" = callPackage @@ -52820,7 +52082,6 @@ self: { description = "Common Haskell types and encoding for OpenStack Ceilometer"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cellrenderer-cairo" = callPackage @@ -52861,7 +52122,6 @@ self: { description = "A tool to build a novel"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cerberus" = callPackage @@ -52966,7 +52226,6 @@ self: { description = "Deserialize things with cereal and enumerator"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cereal-ieee754" = callPackage @@ -53003,7 +52262,6 @@ self: { description = "io-streams support for the cereal binary serialization library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cereal-plus" = callPackage @@ -53052,7 +52310,6 @@ self: { description = "Use cereal to encode/decode io-streams"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cereal-text" = callPackage @@ -53134,7 +52391,6 @@ self: { description = "Certificates and Key Reader/Writer"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cf" = callPackage @@ -53190,7 +52446,6 @@ self: { description = "cfipu processor for toy brainfuck-like language"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cflp" = callPackage @@ -53210,7 +52465,6 @@ self: { description = "Constraint Functional-Logic Programming in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cfopu" = callPackage @@ -53229,7 +52483,6 @@ self: { description = "cfopu processor"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cg" = callPackage @@ -53343,7 +52596,6 @@ self: { description = "Command line tool"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chain-codes" = callPackage @@ -53383,7 +52635,6 @@ self: { description = "Mining Client for Kadena Chainweb"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chakra" = callPackage @@ -53432,7 +52683,6 @@ self: { description = "A REST Web Api server template for building (micro)services"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chalk" = callPackage @@ -53476,7 +52726,6 @@ self: { description = "OpenGL based viewer for chalkboard rendered images"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chalmers-lava2000" = callPackage @@ -53625,7 +52874,6 @@ self: { description = "Rapid prototyping websites with Snap and Heist"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "charset" = callPackage @@ -53683,7 +52931,6 @@ self: { description = "Command-line utility to draw charts from input data easily"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chart-histogram" = callPackage @@ -53727,7 +52974,6 @@ self: { description = "Charting library targetting SVGs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chart-svg-various" = callPackage @@ -53752,7 +52998,6 @@ self: { description = "See readme.md"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chart-unit" = callPackage @@ -53778,7 +53023,6 @@ self: { description = "Native haskell charts"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "charter" = callPackage @@ -54034,7 +53278,6 @@ self: { description = "Initial project template from stack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "check-email" = callPackage @@ -54067,7 +53310,6 @@ self: { description = "Check whether module and package imports conform to the PVP"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "checked" = callPackage @@ -54243,8 +53485,6 @@ self: { ]; description = "Basic chess library"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chesshs" = callPackage @@ -54276,7 +53516,6 @@ self: { description = "Query interface for Chevalier"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chiasma" = callPackage @@ -54312,8 +53551,6 @@ self: { ]; description = "tmux api"; license = "BSD-2-Clause-Patent"; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chimera" = callPackage @@ -54353,8 +53590,6 @@ self: { libraryToolDepends = [ c2hs ]; description = "Haskell bindings for Chipmunk2D physics engine"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chitauri" = callPackage @@ -54375,7 +53610,6 @@ self: { description = "Helper for the Major System"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "choice" = callPackage @@ -54417,7 +53651,6 @@ self: { description = "Command-line program to choose random element from a stream"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chorale" = callPackage @@ -54455,7 +53688,6 @@ self: { description = "A module containing basic geo functions"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chp" = callPackage @@ -54485,7 +53717,6 @@ self: { description = "MTL class instances for the CHP library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chp-plus" = callPackage @@ -54503,7 +53734,6 @@ self: { description = "A set of high-level concurrency utilities built on Communicating Haskell Processes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chp-spec" = callPackage @@ -54533,7 +53763,6 @@ self: { description = "Transformers instances for the CHP library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chr-core" = callPackage @@ -54551,7 +53780,6 @@ self: { description = "Constraint Handling Rules"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chr-data" = callPackage @@ -54590,7 +53818,6 @@ self: { description = "AST + surface language around chr"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chr-parse" = callPackage @@ -54655,7 +53882,6 @@ self: { description = "neovim package manager"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chronograph" = callPackage @@ -54763,8 +53989,6 @@ self: { benchmarkHaskellDepends = [ base ]; description = "Benchmarking tool with focus on comparing results"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chs-cabal" = callPackage @@ -54813,7 +54037,6 @@ self: { description = "FFI for Chu2 Agda Web Server Interface"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chuchu" = callPackage @@ -54859,7 +54082,6 @@ self: { description = "Simple template library with static safety"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "chunky" = callPackage @@ -54946,8 +54168,6 @@ self: { ]; description = "Channel/Arrow based streaming computation library"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cielo" = callPackage @@ -55208,7 +54428,6 @@ self: { description = "Implementation of CipherSaber2 RC4 cryptography"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "circ" = callPackage @@ -55362,7 +54581,6 @@ self: { description = "convert document IDs such as DOI, ISBN, arXiv ID to bibliographic reference"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "citeproc" = callPackage @@ -55430,7 +54648,6 @@ self: { description = "A Pandoc filter for processing bibliographic references with citeproc-hs"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cityhash" = callPackage @@ -55504,8 +54721,6 @@ self: { benchmarkHaskellDepends = [ base criterion ]; description = "Clifford Algebra of three dimensional space"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cl3-hmatrix-interface" = callPackage @@ -55517,8 +54732,6 @@ self: { libraryHaskellDepends = [ base cl3 hmatrix ]; description = "Interface to/from Cl3 and HMatrix"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cl3-linear-interface" = callPackage @@ -55530,8 +54743,6 @@ self: { libraryHaskellDepends = [ base cl3 linear ]; description = "Interface to/from Cl3 and Linear"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clac" = callPackage @@ -55551,7 +54762,6 @@ self: { description = "Simple CLI RPN calculator"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clafer" = callPackage @@ -55587,7 +54797,6 @@ self: { description = "Compiles Clafer models to other formats: Alloy, JavaScript, JSON, HTML, Dot"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "claferIG" = callPackage @@ -55621,7 +54830,6 @@ self: { description = "claferIG is an interactive tool that generates instances of Clafer models"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "claferwiki" = callPackage @@ -55642,7 +54850,6 @@ self: { description = "A wiki-based IDE for literate modeling with Clafer"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clang-compilation-database" = callPackage @@ -55737,7 +54944,6 @@ self: { description = "CAES Language for Synchronous Hardware (CLaSH)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clash-ghc" = callPackage @@ -55768,7 +54974,6 @@ self: { description = "CAES Language for Synchronous Hardware"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clash-ghc_1_4_1" = callPackage @@ -55800,7 +55005,6 @@ self: { description = "Clash: a functional hardware description language - GHC frontend"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clash-lib" = callPackage @@ -55841,7 +55045,6 @@ self: { description = "CAES Language for Synchronous Hardware - As a Library"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clash-lib_1_4_1" = callPackage @@ -55885,7 +55088,6 @@ self: { description = "Clash: a functional hardware description language - As a library"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clash-multisignal" = callPackage @@ -55901,7 +55103,6 @@ self: { ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clash-prelude" = callPackage @@ -56015,7 +55216,6 @@ self: { description = "CAES Language for Synchronous Hardware - SystemVerilog backend"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clash-verilog" = callPackage @@ -56034,7 +55234,6 @@ self: { description = "CAES Language for Synchronous Hardware - Verilog backend"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clash-vhdl" = callPackage @@ -56053,7 +55252,6 @@ self: { description = "CAES Language for Synchronous Hardware - VHDL backend"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "classify" = callPackage @@ -56097,7 +55295,6 @@ self: { description = "Classify sounds produced by Xenopus laevis"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "classy-influxdb-simple" = callPackage @@ -56137,7 +55334,6 @@ self: { description = "Typeclass based support for Miso, the Tasty Web Framework for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "classy-parallel" = callPackage @@ -56282,7 +55478,6 @@ self: { description = "A secure, reliable content management system (CMS) and blogging platform"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) openssl;}; "clckwrks-cli" = callPackage @@ -56306,7 +55501,6 @@ self: { description = "a command-line interface for adminstrating some aspects of clckwrks"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clckwrks-dot-com" = callPackage @@ -56329,7 +55523,6 @@ self: { description = "clckwrks.com"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clckwrks-plugin-bugs" = callPackage @@ -56356,7 +55549,6 @@ self: { description = "bug tracking plugin for clckwrks"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clckwrks-plugin-ircbot" = callPackage @@ -56381,7 +55573,6 @@ self: { description = "ircbot plugin for clckwrks"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clckwrks-plugin-mailinglist" = callPackage @@ -56407,7 +55598,6 @@ self: { description = "mailing list plugin for clckwrks"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clckwrks-plugin-media" = callPackage @@ -56431,7 +55621,6 @@ self: { description = "media plugin for clckwrks"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clckwrks-plugin-page" = callPackage @@ -56458,7 +55647,6 @@ self: { description = "support for CMS/Blogging in clckwrks"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clckwrks-plugin-redirect" = callPackage @@ -56484,7 +55672,6 @@ self: { description = "support redirects for CMS/Blogging in clckwrks"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clckwrks-theme-bootstrap" = callPackage @@ -56503,7 +55690,6 @@ self: { description = "simple bootstrap based template for clckwrks"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clckwrks-theme-clckwrks" = callPackage @@ -56522,7 +55708,6 @@ self: { description = "simple bootstrap based template for clckwrks"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clckwrks-theme-geo-bootstrap" = callPackage @@ -56536,7 +55721,6 @@ self: { description = "geo bootstrap based template for clckwrks"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cld2" = callPackage @@ -56599,7 +55783,6 @@ self: { description = "Colorized LESS"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clevercss" = callPackage @@ -56682,8 +55865,6 @@ self: { ]; description = "Miscellaneous utilities for building and working with command line interfaces"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cli-git" = callPackage @@ -56700,8 +55881,6 @@ self: { ]; description = "Bindings to the git command-line interface"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cli-nix" = callPackage @@ -56718,8 +55897,6 @@ self: { ]; description = "Bindings to the nix command-line interface"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cli-setup" = callPackage @@ -56865,7 +56042,6 @@ self: { description = "A Clifford algebra library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clifm" = callPackage @@ -56982,7 +56158,6 @@ self: { description = "A parser/generator for Kindle-format clipping files (`My Clippings.txt`),"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clisparkline" = callPackage @@ -57106,7 +56281,6 @@ self: { description = "timer functionality to clock IO commands"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {QtCore = null;}; "clogparse" = callPackage @@ -57219,7 +56393,6 @@ self: { description = "The Cloud Haskell Application Platform"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cloud-seeder" = callPackage @@ -57249,7 +56422,6 @@ self: { description = "A tool for interacting with AWS CloudFormation"; license = lib.licenses.isc; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cloudfront-signer" = callPackage @@ -57439,7 +56611,6 @@ self: { description = "C to Lua data wrapper generator"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clumpiness" = callPackage @@ -57510,7 +56681,6 @@ self: { description = "Tools for manipulating sequence clusters"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "clutterhs" = callPackage @@ -57529,7 +56699,6 @@ self: { description = "Bindings to the Clutter animation library"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) clutter; inherit (pkgs) pango;}; "cmaes" = callPackage @@ -57696,7 +56865,6 @@ self: { description = "Data model, parser, serialiser and transformations for Content MathML 3"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cmd-item" = callPackage @@ -57863,7 +57031,6 @@ self: { description = "Compare types of any kinds"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cmt" = callPackage @@ -57935,7 +57102,6 @@ self: { description = "Detailed visualization of CMs, HMMs and their comparisions"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cnc-spec-compiler" = callPackage @@ -57958,7 +57124,6 @@ self: { description = "Compiler/Translator for CnC Specification Files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cndict" = callPackage @@ -58076,7 +57241,6 @@ self: { description = "A Polysemy logging effect for high quality (unstructured) logs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "co-log-sys" = callPackage @@ -58258,7 +57422,6 @@ self: { description = "Simple bidirectional serialization"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "codec-beam" = callPackage @@ -58334,7 +57497,6 @@ self: { description = "A library for manipulating RPM files"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "codecov-haskell" = callPackage @@ -58379,7 +57541,6 @@ self: { description = "Tool that automatically runs arbitrary commands when files change on disk"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "codepad" = callPackage @@ -58521,8 +57682,6 @@ self: { benchmarkHaskellDepends = [ base gauge ]; description = "Utility functions for Coercible types"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "coercion-extras" = callPackage @@ -58675,7 +57834,6 @@ self: { description = "Connector library for the coinbase exchange"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "coinbase-pro" = callPackage @@ -58754,7 +57912,6 @@ self: { description = "Colada implements incremental word class class induction using online LDA"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "colchis" = callPackage @@ -58842,7 +57999,6 @@ self: { description = "Collapse the duplication output into clones and return their frequencies"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "collapse-util" = callPackage @@ -58892,7 +58048,6 @@ self: { description = "Collection+JSON—Hypermedia Type Tools"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "collections" = callPackage @@ -58939,7 +58094,6 @@ self: { description = "Useful standard collections types and related functions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "colock" = callPackage @@ -58999,7 +58153,6 @@ self: { description = "Count colors in images"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "colorful-monoids" = callPackage @@ -59067,7 +58220,6 @@ self: { description = "Http Client addon for Colorless"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "colorless-scotty" = callPackage @@ -59082,7 +58234,6 @@ self: { description = "Scotty server add-on for Colorless"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "colors" = callPackage @@ -59142,7 +58293,6 @@ self: { description = "Instances of the manifold-classes for colour types"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "colourista" = callPackage @@ -59198,7 +58348,6 @@ self: { description = "Enhanced serialization using seeking"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "columnar" = callPackage @@ -59216,8 +58365,6 @@ self: { ]; description = "A CSV toolkit based on cassava and enum-text"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "com" = callPackage @@ -59332,8 +58479,6 @@ self: { ]; description = "Generate and manipulate various combinatorial objects"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "combinat-compat" = callPackage @@ -59515,7 +58660,6 @@ self: { description = "A format for describing comics"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "comma" = callPackage @@ -59743,7 +58887,6 @@ self: { description = "Key agreement for commsec"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "commutative" = callPackage @@ -59891,7 +59034,6 @@ self: { description = "Mutable arrays living on the compact heap"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "compact-mutable-vector" = callPackage @@ -59985,8 +59127,6 @@ self: { ]; description = "Small vectors of small integers stored very compactly"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "compactable" = callPackage @@ -60050,8 +59190,6 @@ self: { ]; description = "Compositional Data Types"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "compdata-automata" = callPackage @@ -60067,8 +59205,6 @@ self: { ]; description = "Tree automata on Compositional Data Types"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "compdata-dags" = callPackage @@ -60180,8 +59316,6 @@ self: { ]; description = "Client for the Compendium schema server"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "compensated" = callPackage @@ -60285,7 +59419,6 @@ self: { description = "Empirical algorithmic complexity"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "componentm" = callPackage @@ -60576,8 +59709,6 @@ self: { ]; description = "Swagger for Vinyl records"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "composite-tuple" = callPackage @@ -60816,7 +59947,6 @@ self: { description = "Well-kinded computational algebra library, currently supporting Groebner basis"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "computational-geometry" = callPackage @@ -60926,7 +60056,6 @@ self: { description = "Morphological disambiguation based on constrained CRFs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "concraft-hr" = callPackage @@ -60949,7 +60078,6 @@ self: { description = "Part-of-speech tagger for Croatian"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "concraft-pl" = callPackage @@ -60979,7 +60107,6 @@ self: { description = "Morphological tagger for Polish"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "concrete-haskell" = callPackage @@ -61024,7 +60151,6 @@ self: { description = "Library for the Concrete data format"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "concrete-haskell-autogen" = callPackage @@ -61042,7 +60168,6 @@ self: { description = "Automatically generated Thrift definitions for the Concrete data format"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "concrete-relaxng-parser" = callPackage @@ -61138,8 +60263,6 @@ self: { ]; description = "Benchmarks to compare concurrency APIs"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "concurrent-barrier" = callPackage @@ -61271,8 +60394,6 @@ self: { benchmarkHaskellDepends = [ base machines time ]; description = "Concurrent networked stream transducers"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "concurrent-output" = callPackage @@ -61431,7 +60552,6 @@ self: { description = "Information retrieval library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "condorcet" = callPackage @@ -61486,7 +60606,6 @@ self: { description = "a library with examples of using Conductive with hsc3"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "conductive-song" = callPackage @@ -61499,7 +60618,6 @@ self: { description = "a library of functions which are useful for composing music"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "conduino" = callPackage @@ -61951,7 +61069,6 @@ self: { description = "Zip archive interface for the Conduit Virtual File System"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "conduit-zstd" = callPackage @@ -62040,7 +61157,6 @@ self: { ]; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "conferer" = callPackage @@ -62104,8 +61220,6 @@ self: { ]; description = "Configuration for reading dhall files"; license = lib.licenses.mpl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "conferer-hedis" = callPackage @@ -62151,7 +61265,6 @@ self: { description = "Configuration for reading dhall files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "conferer-provider-json" = callPackage @@ -62193,7 +61306,6 @@ self: { description = "Configuration for reading yaml files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "conferer-snap" = callPackage @@ -62237,7 +61349,6 @@ self: { description = "Configuration for reading dhall files"; license = lib.licenses.mpl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "conferer-source-json" = callPackage @@ -62278,7 +61389,6 @@ self: { description = "Configuration for reading yaml files"; license = lib.licenses.mpl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "conferer-warp" = callPackage @@ -62347,7 +61457,6 @@ self: { description = "A .conf file formatter"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "confide" = callPackage @@ -62455,7 +61564,6 @@ self: { description = "A small program for swapping out dot files"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "config-value" = callPackage @@ -62517,7 +61625,6 @@ self: { description = "parser for config files, shell variables, command line args"; license = lib.licenses.agpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "configuration" = callPackage @@ -62627,7 +61734,6 @@ self: { description = "The next generation of configuration management"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "configurator-pg" = callPackage @@ -62818,8 +61924,6 @@ self: { testHaskellDepends = [ base hedgehog ]; description = "Orders, Galois connections, and lattices"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "consistent" = callPackage @@ -63079,7 +62183,6 @@ self: { description = "Some conviencience type functions for manipulating constraints"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "constraint-reflection" = callPackage @@ -63225,7 +62328,6 @@ self: { description = "Exact computation with constructible real numbers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "constructive-algebra" = callPackage @@ -63292,7 +62394,6 @@ self: { description = "Concurrent PostgreSQL data consumers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "container" = callPackage @@ -63307,7 +62408,6 @@ self: { description = "Containers abstraction and utilities"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "container-builder" = callPackage @@ -63591,8 +62691,6 @@ self: { ]; description = "Unified interface for primitive arrays"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "contiguous-checked" = callPackage @@ -63617,8 +62715,6 @@ self: { libraryHaskellDepends = [ base contiguous primitive semirings ]; description = "dft of contiguous memory structures"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "continue" = callPackage @@ -63684,7 +62780,6 @@ self: { ]; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "continuum-client" = callPackage @@ -63700,7 +62795,6 @@ self: { ]; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "contra-tracer" = callPackage @@ -63772,7 +62866,6 @@ self: { description = "Class of monad transformers which control operations can be lifted thru"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "control-bool" = callPackage @@ -63854,7 +62947,6 @@ self: { description = "Monad transformer for attempt. (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "control-monad-exception" = callPackage @@ -63887,7 +62979,6 @@ self: { description = "Monads-fd instances for the EMT exceptions monad transformer"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "control-monad-exception-monadstf" = callPackage @@ -64116,7 +63207,6 @@ self: { description = "Injective explicit total and partial conversions"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "convert" = callPackage @@ -64135,7 +63225,6 @@ self: { description = "Safe and unsafe data conversion utilities with strong type-level operation. checking."; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "convert-annotation" = callPackage @@ -64195,7 +63284,6 @@ self: { description = "convertible instances for ascii"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "convertible-text" = callPackage @@ -64217,7 +63305,6 @@ self: { description = "Typeclasses and instances for converting between types (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cookbook" = callPackage @@ -64262,8 +63349,6 @@ self: { ]; description = "web cookies"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "coordinate" = callPackage @@ -64277,7 +63362,6 @@ self: { description = "A representation of latitude and longitude"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "copilot" = callPackage @@ -64298,7 +63382,6 @@ self: { description = "A stream DSL for writing embedded C programs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "copilot-c99" = callPackage @@ -64322,7 +63405,6 @@ self: { description = "A compiler for Copilot targeting C99"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "copilot-cbmc" = callPackage @@ -64340,7 +63422,6 @@ self: { description = "Copilot interface to a C model-checker"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "copilot-core" = callPackage @@ -64369,7 +63450,6 @@ self: { description = "A Haskell-embedded DSL for monitoring hard real-time distributed systems"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "copilot-libraries" = callPackage @@ -64386,7 +63466,6 @@ self: { description = "Libraries for the Copilot language"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "copilot-sbv" = callPackage @@ -64424,7 +63503,6 @@ self: { description = "k-induction for Copilot"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "copr" = callPackage @@ -64641,8 +63719,6 @@ self: { librarySystemDepends = [ rocksdb ]; description = "Launches CoreNLP and parses the JSON output"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) rocksdb;}; "cornea" = callPackage @@ -64676,7 +63752,6 @@ self: { description = "Bridge between the monad-coroutine and enumerator packages"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "coroutine-iteratee" = callPackage @@ -64689,7 +63764,6 @@ self: { description = "Bridge between the monad-coroutine and iteratee packages"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "coroutine-object" = callPackage @@ -64809,7 +63883,6 @@ self: { description = "Couch DB client library using http-enumerator and aeson"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "count" = callPackage @@ -64853,8 +63926,6 @@ self: { testHaskellDepends = [ base hspec QuickCheck text ]; description = "Countable Text Inflections"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "counter" = callPackage @@ -64904,8 +63975,6 @@ self: { testHaskellDepends = [ aeson base HTF HUnit ]; description = "ISO 3166 country codes and i18n names"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "courier" = callPackage @@ -65049,8 +64118,6 @@ self: { testHaskellDepends = [ base hspec hspec-megaparsec megaparsec ]; description = "Build tool for C"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cplex-hs" = callPackage @@ -65152,7 +64219,6 @@ self: { description = "Run random effect using cprng-aes, a crypto pseudo number generator"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cps-except" = callPackage @@ -65311,7 +64377,6 @@ self: { description = "Tinylog integration for cql-io"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cqrs" = callPackage @@ -65364,7 +64429,6 @@ self: { description = "Example for cqrs package"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cqrs-memory" = callPackage @@ -65382,7 +64446,6 @@ self: { description = "Memory backend for the cqrs package"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cqrs-postgresql" = callPackage @@ -65407,7 +64470,6 @@ self: { description = "PostgreSQL backend for the cqrs package"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cqrs-sqlite3" = callPackage @@ -65429,7 +64491,6 @@ self: { description = "SQLite3 backend for the cqrs package"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cqrs-test" = callPackage @@ -65447,7 +64508,6 @@ self: { description = "Command-Query Responsibility Segregation Test Support"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cqrs-testkit" = callPackage @@ -65466,7 +64526,6 @@ self: { description = "Command-Query Responsibility Segregation Test Support"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cqrs-types" = callPackage @@ -65577,7 +64636,6 @@ self: { description = "A UNIX configuration management library in Haskell"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "craftwerk" = callPackage @@ -65605,7 +64663,6 @@ self: { description = "Cairo backend for Craftwerk"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "craftwerk-gtk" = callPackage @@ -65624,7 +64681,6 @@ self: { description = "Gtk UI for Craftwerk"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "crawlchain" = callPackage @@ -65680,7 +64736,6 @@ self: { description = "HTTP Racing Library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "crc" = callPackage @@ -65757,8 +64812,6 @@ self: { ]; description = "Conflict-free replicated data types"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "crdt-event-fold" = callPackage @@ -65891,7 +64944,6 @@ self: { description = "First-order, linear-chain conditional random fields"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "crf-chain1-constrained" = callPackage @@ -65912,7 +64964,6 @@ self: { description = "First-order, constrained, linear-chain conditional random fields"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "crf-chain2-generic" = callPackage @@ -65931,7 +64982,6 @@ self: { description = "Second-order, generic, constrained, linear conditional random fields"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "crf-chain2-tiers" = callPackage @@ -65951,7 +65001,6 @@ self: { description = "Second-order, tiered, constrained, linear conditional random fields"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "critbit" = callPackage @@ -66039,8 +65088,6 @@ self: { ]; description = "A simple tool for comparing in Criterion benchmark results"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "criterion-compare" = callPackage @@ -66145,7 +65192,6 @@ self: { description = "CRIU RPC client"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "criu-rpc-types" = callPackage @@ -66190,7 +65236,6 @@ self: { description = "An implementation of Douglas Crockford's base32 encoding"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "crocodile" = callPackage @@ -66255,7 +65300,6 @@ self: { description = "Cron datatypes and Attoparsec parser"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cronus" = callPackage @@ -66328,8 +65372,6 @@ self: { ]; description = "Pure Haskell implelementation for GNU SHA512 crypt algorithm"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "crypto-api" = callPackage @@ -66459,7 +65501,6 @@ self: { description = "Conduit interface for cryptographic operations (from crypto-api)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "crypto-enigma" = callPackage @@ -66743,7 +65784,6 @@ self: { description = "Symmetrical block and stream ciphers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cryptocompare" = callPackage @@ -66947,7 +65987,6 @@ self: { description = "Reversable and secure encoding of object ids as a bytestring"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cryptoids-class" = callPackage @@ -66962,7 +66001,6 @@ self: { description = "Typeclass-based interface to cryptoids"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cryptoids-types" = callPackage @@ -67020,7 +66058,6 @@ self: { description = "Cryptol: The Language of Cryptography"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cryptonite" = callPackage @@ -67142,7 +66179,6 @@ self: { description = "Control Crystalfontz LCD displays"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "csa" = callPackage @@ -67204,7 +66240,6 @@ self: { description = "Analytical CSG (Constructive Solid Geometry) library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "csound-catalog" = callPackage @@ -67344,7 +66379,6 @@ self: { description = "A command line type checker for CSPM files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cspretty" = callPackage @@ -67502,7 +66536,6 @@ self: { description = "A flexible, fast, enumerator-based CSV parser library for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "csv-nptools" = callPackage @@ -67598,7 +66631,6 @@ self: { description = "A programming language for text modification"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ctrie" = callPackage @@ -67640,7 +66672,6 @@ self: { description = "Cubic DSL for 3D printing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cubical" = callPackage @@ -67994,8 +67025,6 @@ self: { testHaskellDepends = [ aeson base bson hspec QuickCheck ]; description = "ISO-4217 Currency Codes"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "currency-convert" = callPackage @@ -68166,7 +67195,6 @@ self: { description = "Terminal tool for viewing tabular data"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cursor" = callPackage @@ -68234,8 +67262,6 @@ self: { base criterion cursor-fuzzy-time genvalidity-criterion QuickCheck ]; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cursor-gen" = callPackage @@ -68421,7 +67447,6 @@ self: { description = "Functional Combinators for Computer Vision"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "cve" = callPackage @@ -68471,7 +67496,6 @@ self: { description = "Haskell bindings for the neo4j \"cypher\" query language"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "czipwith" = callPackage @@ -68715,7 +67739,6 @@ self: { description = "Prints a series of dates"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "darcs" = callPackage @@ -68788,7 +67811,6 @@ self: { description = "Comparative benchmark suite for darcs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "darcs-beta" = callPackage @@ -68821,7 +67843,6 @@ self: { description = "a distributed, interactive, smart revision control system"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) curl;}; "darcs-buildpackage" = callPackage @@ -68886,7 +67907,6 @@ self: { description = "Import/export git fast-import streams to/from darcs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "darcs-graph" = callPackage @@ -68986,7 +68006,6 @@ self: { description = "Darcs repository UI and hosting/collaboration app (hub.darcs.net branch)."; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "darcswatch" = callPackage @@ -69010,7 +68029,6 @@ self: { description = "Track application of Darcs patches"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "darkplaces-demo" = callPackage @@ -69039,7 +68057,6 @@ self: { description = "Utility and parser for DarkPlaces demo files"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "darkplaces-rcon" = callPackage @@ -69088,7 +68105,6 @@ self: { description = "Darplaces rcon utility"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "darkplaces-text" = callPackage @@ -69129,7 +68145,6 @@ self: { description = "Convert package Haddock to Dash docsets (IDE docs)"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "data-accessor" = callPackage @@ -69167,7 +68182,6 @@ self: { description = "Use Accessor to access state in monads-fd State monad class"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "data-accessor-monads-tf" = callPackage @@ -69298,7 +68312,6 @@ self: { description = "A database library with a focus on ease of use, type safety and useful error messages"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "data-binary-ieee754" = callPackage @@ -69474,7 +68487,6 @@ self: { description = "a cyclic doubly linked list"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "data-default" = callPackage @@ -69780,7 +68792,6 @@ self: { description = "Executable and Linkable Format (ELF) data structures"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "data-embed" = callPackage @@ -70099,8 +69110,6 @@ self: { ]; description = "Interval datatype, interval arithmetic and interval-based containers"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "data-inttrie" = callPackage @@ -70169,7 +69178,6 @@ self: { description = "Data layering utilities. Layer is a data-type which wrapps other one, but keeping additional information. If you want to access content of simple newtype object, use Lens.Wrapper instead."; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "data-layout" = callPackage @@ -70212,7 +69220,6 @@ self: { description = "Lenses"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "data-lens-ixset" = callPackage @@ -70226,7 +69233,6 @@ self: { description = "A Lens for IxSet"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "data-lens-light" = callPackage @@ -70250,7 +69256,6 @@ self: { description = "Utilities for Data.Lens"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "data-list-sequences" = callPackage @@ -70394,7 +69399,6 @@ self: { description = "Serialize JSON data to/from Haskell using the data-object library. (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "data-object-yaml" = callPackage @@ -70414,7 +69418,6 @@ self: { description = "Serialize data to and from Yaml files (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "data-or" = callPackage @@ -70564,7 +69567,6 @@ self: { description = "Data types for returning results distinguishable by types"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "data-rev" = callPackage @@ -70603,7 +69605,6 @@ self: { description = "Recursive tuple data structure. It is very usefull when implementing some lo-level operations, allowing to traverse different elements using Haskell's type classes."; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "data-serializer" = callPackage @@ -70759,7 +69760,6 @@ self: { description = "Program that infers the fastest data structure available for your program"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "data-sword" = callPackage @@ -71055,7 +70055,6 @@ self: { description = "Datadog tracing client and mock agent"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dataenc" = callPackage @@ -71127,7 +70126,6 @@ self: { description = "Generate Graphviz documents from a Haskell representation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dataflower" = callPackage @@ -71244,8 +70242,6 @@ self: { ]; description = "Classical data sets for statistics and machine learning"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dataurl" = callPackage @@ -71264,8 +70260,6 @@ self: { ]; description = "Handle data-urls"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "date-cache" = callPackage @@ -71290,7 +70284,6 @@ self: { description = "Date conversions"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dates" = callPackage @@ -71452,7 +70445,6 @@ self: { description = "Decompiler Bytecode Java"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dbm" = callPackage @@ -71629,7 +70621,6 @@ self: { description = "Monadic and object-oriented interfaces to DBus"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dbus-core" = callPackage @@ -71788,7 +70779,6 @@ self: { description = "Discordian Date Types for Haskell"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ddc-base" = callPackage @@ -71826,7 +70816,6 @@ self: { description = "Disciplined Disciple Compiler build framework"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ddc-code" = callPackage @@ -71858,7 +70847,6 @@ self: { description = "Disciplined Disciple Compiler core language and type checker"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ddc-core-babel" = callPackage @@ -71873,7 +70861,6 @@ self: { description = "Disciplined Disciple Compiler PHP code generator"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ddc-core-eval" = callPackage @@ -71890,7 +70877,6 @@ self: { description = "Disciplined Disciple Compiler semantic evaluator for the core language"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ddc-core-flow" = callPackage @@ -71909,7 +70895,6 @@ self: { description = "Disciplined Disciple Compiler data flow compiler"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ddc-core-llvm" = callPackage @@ -71927,7 +70912,6 @@ self: { description = "Disciplined Disciple Compiler LLVM code generator"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ddc-core-salt" = callPackage @@ -71944,7 +70928,6 @@ self: { description = "Disciplined Disciple Compiler C code generator"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ddc-core-simpl" = callPackage @@ -71961,7 +70944,6 @@ self: { description = "Disciplined Disciple Compiler code transformations"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ddc-core-tetra" = callPackage @@ -71979,7 +70961,6 @@ self: { description = "Disciplined Disciple Compiler intermediate language"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ddc-driver" = callPackage @@ -72000,7 +70981,6 @@ self: { description = "Disciplined Disciple Compiler top-level driver"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ddc-interface" = callPackage @@ -72013,7 +70993,6 @@ self: { description = "Disciplined Disciple Compiler user interface support"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ddc-source-tetra" = callPackage @@ -72031,7 +71010,6 @@ self: { description = "Disciplined Disciple Compiler source language"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ddc-tools" = callPackage @@ -72055,7 +71033,6 @@ self: { description = "Disciplined Disciple Compiler command line tools"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ddc-war" = callPackage @@ -72074,7 +71051,6 @@ self: { description = "Disciplined Disciple Compiler test driver and buildbot"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ddci-core" = callPackage @@ -72094,7 +71070,6 @@ self: { description = "Disciple Core language interactive interpreter"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dde" = callPackage @@ -72255,7 +71230,6 @@ self: { description = "Simple trace-based debugger"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "debug-diff" = callPackage @@ -72350,7 +71324,6 @@ self: { description = "You do not have to write variable names twice in Debug.Trace"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "debug-tracy" = callPackage @@ -72419,7 +71392,6 @@ self: { description = "Combinators for manipulating dependently-typed predicates"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "decimal-arithmetic" = callPackage @@ -72435,7 +71407,6 @@ self: { description = "An implementation of the General Decimal Arithmetic Specification"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "decimal-literals" = callPackage @@ -72523,7 +71494,6 @@ self: { description = "A type-checker for the λΠ-modulo calculus"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "deep-transformations" = callPackage @@ -72613,7 +71583,6 @@ self: { description = "Deep Learning in Haskell"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "deepseq_1_4_5_0" = callPackage @@ -72724,7 +71693,6 @@ self: { description = "A DeepZoom image slicer. Only known to work on 32bit Linux"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "defargs" = callPackage @@ -72737,7 +71705,6 @@ self: { description = "default arguments in haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "deferred-folds" = callPackage @@ -72944,7 +71911,6 @@ self: { description = "Tests for deka, decimal floating point arithmetic"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "delaunay" = callPackage @@ -72962,7 +71928,6 @@ self: { description = "Build a Delaunay triangulation of a set of points"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "delay" = callPackage @@ -72994,7 +71959,6 @@ self: { description = "Accessing the del.icio.us APIs from Haskell (v2)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "delimited-text" = callPackage @@ -73011,7 +71975,6 @@ self: { description = "Parse character delimited textual data"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "delimiter-separated" = callPackage @@ -73025,7 +71988,6 @@ self: { description = "Library for dealing with tab and/or comma (or other) separated files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "delta" = callPackage @@ -73050,7 +72012,6 @@ self: { description = "A library for detecting file changes"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "delta-h" = callPackage @@ -73073,7 +72034,6 @@ self: { description = "Online entropy-based model of lexical category acquisition"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "delude" = callPackage @@ -73141,8 +72101,6 @@ self: { ]; description = "Mutable and immutable dense multidimensional arrays"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dense-int-set" = callPackage @@ -73226,7 +72184,6 @@ self: { description = "Giving good advice to functions in a DepT environment"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dependency" = callPackage @@ -73325,7 +72282,6 @@ self: { description = "Control structure similar to Control.Monad.State, allowing multiple nested states, distinguishable by provided phantom types."; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dependent-sum_0_4" = callPackage @@ -73425,7 +72381,6 @@ self: { description = "Analyze quality of nucleotide sequences"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "depq" = callPackage @@ -73474,7 +72429,6 @@ self: { description = "DepTrack applied to DevOps"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "deptrack-dot" = callPackage @@ -73488,7 +72442,6 @@ self: { description = "Facilitate Graphviz representations of DepTrack dependencies"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "deque" = callPackage @@ -73522,7 +72475,6 @@ self: { description = "A typeclass and an implementation for double-ended queues"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "derangement" = callPackage @@ -73585,7 +72537,6 @@ self: { description = "Macro to derive instances for Instant-Generics using Template Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "derive-enumerable" = callPackage @@ -73992,7 +72943,6 @@ self: { description = "JSON and CSV encoding for quantities"; license = lib.licenses.mpl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "detrospector" = callPackage @@ -74068,7 +73018,6 @@ self: { description = "Haskell development tool agregate"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dewdrop" = callPackage @@ -74083,7 +73032,6 @@ self: { description = "Find gadgets for return-oriented programming on x86"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "df1" = callPackage @@ -74159,7 +73107,6 @@ self: { description = "A generic data integrity layer"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) leveldb;}; "dfrac" = callPackage @@ -74396,7 +73343,6 @@ self: { description = "Generate HTML docs from a dhall package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dhall-fly" = callPackage @@ -74531,8 +73477,6 @@ self: { ]; description = "Dhall to Nix compiler"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dhall-nixpkgs" = callPackage @@ -74554,8 +73498,6 @@ self: { ]; description = "Convert Dhall projects to Nix packages"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dhall-openapi" = callPackage @@ -74600,8 +73542,6 @@ self: { ]; description = "Convert recursive ADTs from and to Dhall"; license = lib.licenses.cc0; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dhall-text" = callPackage @@ -74698,7 +73638,6 @@ self: { description = "Parse a DHCP lease file"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dhrun" = callPackage @@ -74861,7 +73800,6 @@ self: { description = "An EDSL for teaching Haskell with diagrams - functions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "diagrams" = callPackage @@ -74919,7 +73857,6 @@ self: { description = "Braille diagrams with plain text"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "diagrams-builder" = callPackage @@ -74949,7 +73886,6 @@ self: { description = "hint-based build service for the diagrams graphics EDSL"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "diagrams-cairo" = callPackage @@ -75104,7 +74040,6 @@ self: { description = "Preprocessor for embedding diagrams in Haddock documentation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "diagrams-hsqml" = callPackage @@ -75141,7 +74076,6 @@ self: { description = "HTML5 canvas backend for diagrams drawing EDSL"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "diagrams-lib" = callPackage @@ -75201,7 +74135,6 @@ self: { description = "A Pandoc filter to express diagrams inline using the Haskell EDSL _Diagrams_"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "diagrams-pdf" = callPackage @@ -75241,7 +74174,6 @@ self: { description = "PGF backend for diagrams drawing EDSL"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "diagrams-postscript" = callPackage @@ -75335,8 +74267,6 @@ self: { ]; description = "Library for drawing the Rubik's Cube"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "diagrams-solve" = callPackage @@ -75407,7 +74337,6 @@ self: { description = "Backend for rendering diagrams in wxWidgets"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dialog" = callPackage @@ -75738,7 +74667,6 @@ self: { ]; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "differential" = callPackage @@ -75844,6 +74772,7 @@ self: { description = "Pure hash functions for bytestrings"; license = "unknown"; hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "digest-sig" = callPackage @@ -75999,7 +74928,6 @@ self: { description = "HSP support for digestive-functors"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "digestive-functors-lucid" = callPackage @@ -76178,8 +75106,6 @@ self: { libraryHaskellDepends = [ base dimensional numtype-dk ]; description = "CODATA Recommended Physical Constants with Dimensional Types"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dimensional-tf" = callPackage @@ -76232,7 +75158,6 @@ self: { description = "Dingo is a Rich Internet Application platform based on the Warp web server"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dingo-example" = callPackage @@ -76253,7 +75178,6 @@ self: { description = "Dingo Example"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dingo-widgets" = callPackage @@ -76273,7 +75197,6 @@ self: { description = "Dingo Widgets"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dino" = callPackage @@ -76351,7 +75274,6 @@ self: { description = "Diplomacy board game"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "diplomacy-server" = callPackage @@ -76376,7 +75298,6 @@ self: { description = "Play Diplomacy over HTTP"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dir-traverse" = callPackage @@ -76650,7 +75571,6 @@ self: { ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dirichlet" = callPackage @@ -76741,7 +75661,6 @@ self: { description = "Client for Discogs REST API"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "discokitty" = callPackage @@ -76771,7 +75690,6 @@ self: { description = "An API wrapper for Discord in Haskell"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "discord-haskell" = callPackage @@ -76812,7 +75730,6 @@ self: { description = "An API wrapper for Discord in Haskell"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "discord-register" = callPackage @@ -76845,7 +75762,6 @@ self: { description = "Discord verification bot"; license = lib.licenses.mpl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "discord-rest" = callPackage @@ -76866,7 +75782,6 @@ self: { description = "An API wrapper for Discord in Haskell"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "discord-types" = callPackage @@ -77271,7 +76186,6 @@ self: { description = "Cloud Haskell Async API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributed-process-azure" = callPackage @@ -77295,7 +76209,6 @@ self: { description = "Microsoft Azure backend for Cloud Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributed-process-client-server" = callPackage @@ -77326,7 +76239,6 @@ self: { description = "The Cloud Haskell Application Platform"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributed-process-ekg" = callPackage @@ -77343,7 +76255,6 @@ self: { description = "Collect node stats for EKG"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributed-process-execution" = callPackage @@ -77380,7 +76291,6 @@ self: { description = "Execution Framework for The Cloud Haskell Application Platform"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributed-process-extras" = callPackage @@ -77412,7 +76322,6 @@ self: { description = "Cloud Haskell Extras"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributed-process-fsm" = callPackage @@ -77446,7 +76355,6 @@ self: { description = "The Cloud Haskell implementation of Erlang/OTP gen_statem"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributed-process-lifted" = callPackage @@ -77473,7 +76381,6 @@ self: { description = "monad-control style typeclass and transformer instances for Process monad"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributed-process-monad-control" = callPackage @@ -77491,7 +76398,6 @@ self: { description = "Orphan instances for MonadBase and MonadBaseControl"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributed-process-p2p" = callPackage @@ -77513,7 +76419,6 @@ self: { description = "Peer-to-peer node discovery for Cloud Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributed-process-platform" = callPackage @@ -77545,7 +76450,6 @@ self: { description = "The Cloud Haskell Application Platform"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributed-process-registry" = callPackage @@ -77579,7 +76483,6 @@ self: { description = "Cloud Haskell Extended Process Registry"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributed-process-simplelocalnet" = callPackage @@ -77603,7 +76506,6 @@ self: { description = "Simple zero-configuration backend for Cloud Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributed-process-supervisor" = callPackage @@ -77636,7 +76538,6 @@ self: { description = "Supervisors for The Cloud Haskell Application Platform"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributed-process-systest" = callPackage @@ -77657,7 +76558,6 @@ self: { description = "Cloud Haskell Test Support"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributed-process-task" = callPackage @@ -77695,7 +76595,6 @@ self: { description = "Task Framework for The Cloud Haskell Application Platform"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributed-process-tests" = callPackage @@ -77720,7 +76619,6 @@ self: { description = "Tests and test support tools for distributed-process"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributed-process-zookeeper" = callPackage @@ -77750,7 +76648,6 @@ self: { description = "A Zookeeper back-end for Cloud Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributed-static" = callPackage @@ -77837,7 +76734,6 @@ self: { description = "Easily plot distributions from the distribution package.."; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "distributive" = callPackage @@ -77899,8 +76795,6 @@ self: { ]; description = "Quantify the diversity of a population"; license = lib.licenses.gpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dixi" = callPackage @@ -77939,7 +76833,6 @@ self: { description = "A wiki implemented with a firm theoretical foundation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "djembe" = callPackage @@ -78038,7 +76931,6 @@ self: { description = "Fedora image download tool"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dlist" = callPackage @@ -78176,7 +77068,6 @@ self: { description = "dmenu script for killing applications. Sortable by process id or CPU/MEM usage."; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dmenu-pmount" = callPackage @@ -78195,7 +77086,6 @@ self: { description = "Mounting and unmounting linux devices as user with dmenu and pmount"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dmenu-search" = callPackage @@ -78214,7 +77104,6 @@ self: { description = "dmenu script for searching the web with customizable search engines"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dns" = callPackage @@ -78530,7 +77419,6 @@ self: { description = "Document review Web application, like http://book.realworldhaskell.org/"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "doccheck" = callPackage @@ -78997,8 +77885,6 @@ self: { ]; description = "Low-level bindings to the DocuSign API"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "docusign-base-minimal" = callPackage @@ -79015,8 +77901,6 @@ self: { ]; description = "Low-level bindings to the DocuSign API (only what is necessary for docusign-client)"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "docusign-client" = callPackage @@ -79036,8 +77920,6 @@ self: { ]; description = "Client bindings for the DocuSign API"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "docusign-example" = callPackage @@ -79115,7 +77997,6 @@ self: { description = "Automatic Bibtex and fulltext of scientific articles"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "doldol" = callPackage @@ -79239,7 +78120,6 @@ self: { description = "Codegen helping you define domain models"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "domain-auth" = callPackage @@ -79275,7 +78155,6 @@ self: { description = "Low-level API of \"domain\""; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "domain-optics" = callPackage @@ -79295,7 +78174,6 @@ self: { description = "Integration of domain with optics"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dominion" = callPackage @@ -79646,7 +78524,6 @@ self: { description = "Dungeons of Wor"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "download" = callPackage @@ -79690,7 +78567,6 @@ self: { description = "Simple tool to download images from RSS feeds (e.g. Flickr, Picasa)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "downloader" = callPackage @@ -79777,7 +78653,6 @@ self: { description = "Data Parallel Haskell example programs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dph-lifted-base" = callPackage @@ -79795,7 +78670,6 @@ self: { description = "Data Parallel Haskell common definitions used by other dph-lifted packages"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dph-lifted-copy" = callPackage @@ -79812,7 +78686,6 @@ self: { description = "Data Parallel Haskell lifted array combinators. (deprecated version)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dph-lifted-vseg" = callPackage @@ -79830,7 +78703,6 @@ self: { description = "Data Parallel Haskell lifted array combinators"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dph-par" = callPackage @@ -79854,7 +78726,6 @@ self: { description = "Data Parallel Haskell segmented arrays. (abstract interface)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dph-prim-par" = callPackage @@ -79872,7 +78743,6 @@ self: { description = "Data Parallel Haskell segmented arrays. (production version)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dph-prim-seq" = callPackage @@ -79889,7 +78759,6 @@ self: { description = "Data Parallel Haskell segmented arrays. (sequential implementation)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dph-seq" = callPackage @@ -80085,8 +78954,6 @@ self: { ]; description = "Simple schema management for arbitrary databases"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "drifter-postgresql" = callPackage @@ -80128,8 +78995,6 @@ self: { ]; description = "SQLite support for the drifter schema migraiton tool"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "drinkery" = callPackage @@ -80204,8 +79069,6 @@ self: { ]; description = "Dropbox API client"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dropbox-sdk" = callPackage @@ -80228,7 +79091,6 @@ self: { description = "A library to access the Dropbox HTTP API"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dropsolve" = callPackage @@ -80248,7 +79110,6 @@ self: { description = "A command line tool for resolving dropbox conflicts. Deprecated! Please use confsolve."; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "drunken-bishop" = callPackage @@ -80329,7 +79190,6 @@ self: { description = "SQL backend for Database Supported Haskell (DSH)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dsmc" = callPackage @@ -80369,7 +79229,6 @@ self: { description = "DSMC toolkit for rarefied gas dynamics"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dson" = callPackage @@ -80485,7 +79344,6 @@ self: { description = "Parse and render DTD files (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dtd-text" = callPackage @@ -80718,7 +79576,6 @@ self: { description = "A computer “algebra” system that knows nothing about algebra, at the core"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dump" = callPackage @@ -80938,7 +79795,6 @@ self: { description = "Efficient automatic differentiation and code generation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dvdread" = callPackage @@ -81150,7 +80006,6 @@ self: { description = "Access the functions from the Cabal library without depending on it"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dynamic-graph" = callPackage @@ -81283,7 +80138,6 @@ self: { description = "Interactive diagram windows"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dynamic-pp" = callPackage @@ -81396,7 +80250,6 @@ self: { description = "your dynamic optimization buddy"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "dyre" = callPackage @@ -81723,8 +80576,6 @@ self: { ]; description = "Pure, type-indexed haskell vector, matrix, and tensor library"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "easytensor-vulkan" = callPackage @@ -81736,8 +80587,6 @@ self: { libraryHaskellDepends = [ base dimensions easytensor vulkan-api ]; description = "Use easytensor with vulkan-api"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "easytest" = callPackage @@ -81830,8 +80679,6 @@ self: { ]; description = "A handy tool for uploading unikernels to Amazon's EC2"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "eccrypto" = callPackage @@ -81864,7 +80711,6 @@ self: { description = "provides \"ed25519\" API using \"eccrypto\""; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ecdsa" = callPackage @@ -82056,7 +80902,6 @@ self: { description = "Semi-explicit parallel programming skeleton library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "edentv" = callPackage @@ -82078,7 +80923,6 @@ self: { description = "A Tool to Visualize Parallel Functional Program Executions"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "edf" = callPackage @@ -82109,7 +80953,6 @@ self: { description = "Top view space combat arcade game"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "edges" = callPackage @@ -82138,7 +80981,6 @@ self: { description = "Tools for efficient immutable graphs"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "edis" = callPackage @@ -82272,7 +81114,6 @@ self: { description = "Interactive editors for Generics"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "editline" = callPackage @@ -82504,7 +81345,6 @@ self: { description = "Programming language with non-linear pattern-matching against non-free data"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "egison-pattern-src" = callPackage @@ -82548,7 +81388,6 @@ self: { description = "Parser and pretty printer for Egison pattern expressions in Haskell source code"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "egison-pattern-src-th-mode" = callPackage @@ -82572,7 +81411,6 @@ self: { description = "Parser and pretty printer for Egison pattern expressions to use with TH"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "egison-quote" = callPackage @@ -82587,7 +81425,6 @@ self: { description = "A quasi quotes for using Egison expression in Haskell code"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "egison-tutorial" = callPackage @@ -82607,7 +81444,6 @@ self: { description = "A tutorial program for the Egison programming language"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "egyptian-fractions" = callPackage @@ -82763,8 +81599,6 @@ self: { testHaskellDepends = [ base doctest ]; description = "Functions involving lists of Either"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "either-result" = callPackage @@ -82902,8 +81736,6 @@ self: { ]; description = "An ekg backend for Amazon Cloudwatch"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ekg-core" = callPackage @@ -83169,7 +82001,6 @@ self: { description = "Example applications for Elerea"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "elerea-sdl" = callPackage @@ -83288,7 +82119,6 @@ self: { description = "Elliptic curve library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "elm-bridge" = callPackage @@ -83780,7 +82610,6 @@ self: { description = "A tiny language for understanding the lambda-calculus"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "elynx" = callPackage @@ -83798,8 +82627,6 @@ self: { ]; description = "Validate and (optionally) redo ELynx analyses"; license = lib.licenses.gpl3Plus; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "elynx-markov" = callPackage @@ -83900,8 +82727,6 @@ self: { ]; description = "Handle phylogenetic trees"; license = lib.licenses.gpl3Plus; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ema" = callPackage @@ -83951,7 +82776,6 @@ self: { description = "library to parse emacs style keybinding into the modifiers and the chars"; license = lib.licenses.isc; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "emacs-module" = callPackage @@ -83990,7 +82814,6 @@ self: { description = "Sending eMail in Haskell made easy"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "email-header" = callPackage @@ -84128,7 +82951,6 @@ self: { description = "An email parser that will parse everything"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "embeddock" = callPackage @@ -84146,7 +82968,6 @@ self: { description = "Embed the values in scope in the haddock documentation of the module"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "embeddock-example" = callPackage @@ -84159,7 +82980,6 @@ self: { description = "Example of using embeddock"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "embla" = callPackage @@ -84192,7 +83012,6 @@ self: { description = "support for embroidery formats in haskell"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "emd" = callPackage @@ -84462,8 +83281,6 @@ self: { ]; description = "A Haskell implementation of Engine.IO"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "engine-io-growler" = callPackage @@ -84483,7 +83300,6 @@ self: { ]; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "engine-io-snap" = callPackage @@ -84568,7 +83384,6 @@ self: { description = "An application (and library) to convert quipper circuits into Qpmc models"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "entropy" = callPackage @@ -84646,8 +83461,6 @@ self: { ]; description = "A text rendering and parsing toolkit for enumerated types"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "enum-text-rio" = callPackage @@ -84664,8 +83477,6 @@ self: { ]; description = "Making fmt available with rio"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "enum-types" = callPackage @@ -84726,7 +83537,6 @@ self: { description = "enumerate all the values in a finite type (automatically)"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "enumerate-function" = callPackage @@ -84748,7 +83558,6 @@ self: { description = "simple package for inverting functions and testing totality, via brute enumeration of the domain"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "enumeration" = callPackage @@ -84795,7 +83604,6 @@ self: { description = "Enumerator instances for monads-fd classes"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "enumerator-tf" = callPackage @@ -84808,7 +83616,6 @@ self: { description = "Enumerator instances for monads-tf classes"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "enumfun" = callPackage @@ -84922,8 +83729,6 @@ self: { ]; description = "Safe helpers for accessing and modifying environment variables"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "env-locale" = callPackage @@ -85091,7 +83896,6 @@ self: { description = "See readme.md"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "epi-sim" = callPackage @@ -85110,8 +83914,6 @@ self: { ]; description = "A library for simulating epidemics as birth-death processes"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "epic" = callPackage @@ -85389,7 +84191,6 @@ self: { description = "Native Haskell implementation of the interface from the erf package"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "erlang" = callPackage @@ -85461,7 +84262,6 @@ self: { description = "DEPRECATED in favor of eros-http"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "eros-http" = callPackage @@ -85482,7 +84282,6 @@ self: { description = "JSON HTTP interface to Eros"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "errata" = callPackage @@ -85501,6 +84300,8 @@ self: { testToolDepends = [ hspec-discover ]; description = "Source code error pretty printing"; license = lib.licenses.mit; + hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "errno" = callPackage @@ -85536,8 +84337,6 @@ self: { testHaskellDepends = [ base ]; description = "Error code functions"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "error-context" = callPackage @@ -85628,7 +84427,6 @@ self: { description = "Composable error messages"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "error-or" = callPackage @@ -85711,7 +84509,6 @@ self: { description = "`bracket`-like functions for `ExceptT` over `IO` monad"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ersaconcat" = callPackage @@ -85781,7 +84578,6 @@ self: { description = "toysat driver as backend for ersatz"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ert" = callPackage @@ -85897,7 +84693,6 @@ self: { description = "Esotericbot is a sophisticated, lightweight IRC bot"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "espial" = callPackage @@ -86212,7 +85007,6 @@ self: { description = "Repeats from ESTs"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "etc" = callPackage @@ -86288,7 +85082,6 @@ self: { description = "Native event-sourcing database"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "eternity-timestamped" = callPackage @@ -86307,7 +85100,6 @@ self: { description = "Automatic timestamping for Eternity"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ether" = callPackage @@ -86337,7 +85129,6 @@ self: { description = "Monad transformers and classes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ethereum-analyzer" = callPackage @@ -86362,7 +85153,6 @@ self: { description = "A Ethereum contract analyzer"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ethereum-analyzer-cli" = callPackage @@ -86391,7 +85181,6 @@ self: { description = "A CLI frontend for ethereum-analyzer"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ethereum-analyzer-deps" = callPackage @@ -86438,7 +85227,6 @@ self: { description = "A web frontend for ethereum-analyzer"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ethereum-client-haskell" = callPackage @@ -86468,7 +85256,6 @@ self: { description = "A Haskell version of an Ethereum client"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ethereum-merkle-patricia-db" = callPackage @@ -86494,7 +85281,6 @@ self: { description = "A modified Merkle Patricia DB"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ethereum-rlp" = callPackage @@ -86676,7 +85462,6 @@ self: { description = "Bridge for working with evdev and streamly"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "eve" = callPackage @@ -86799,7 +85584,6 @@ self: { description = "Event-graph simulation monad transformer"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "event-transformer" = callPackage @@ -86904,7 +85688,6 @@ self: { description = "Postgres implementations for eventful"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "eventful-sql-common" = callPackage @@ -86948,7 +85731,6 @@ self: { description = "SQLite implementations for eventful"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "eventful-test-helpers" = callPackage @@ -87053,7 +85835,6 @@ self: { description = "GetEventStore store implementation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "eventsource-store-specs" = callPackage @@ -87209,7 +85990,6 @@ self: { description = "A functional pearl on encoding and decoding using question-and-answer strategies"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ewe" = callPackage @@ -87391,7 +86171,6 @@ self: { description = "Exception monad transformer instances for monads-fd classes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "exception-monads-tf" = callPackage @@ -87627,7 +86406,6 @@ self: { description = "Tool to search/generate (haskell) expressions with a given type"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "exh" = callPackage @@ -88073,7 +86851,6 @@ self: { description = "Extensible Pandoc"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "expat-enumerator" = callPackage @@ -88090,7 +86867,6 @@ self: { description = "Enumerator-based API for Expat"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "experimenter" = callPackage @@ -88165,7 +86941,6 @@ self: { description = "Expiring containers"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "expiring-mvar" = callPackage @@ -88261,7 +87036,6 @@ self: { description = "Extends explicit-iomodes with ByteString operations"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "explicit-iomodes-text" = callPackage @@ -88274,7 +87048,6 @@ self: { description = "Extends explicit-iomodes with Text operations"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "explicit-sharing" = callPackage @@ -88289,7 +87062,6 @@ self: { description = "Explicit Sharing of Monadic Effects"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "explore" = callPackage @@ -88304,7 +87076,6 @@ self: { description = "Experimental Plot data Reconstructor"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "exploring-interpreters" = callPackage @@ -88402,7 +87173,6 @@ self: { description = "Encode and Decode expressions from Z3 ASTs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "expresso" = callPackage @@ -88475,7 +87245,6 @@ self: { description = "automated printing for extemp speakers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "extend-record-data-th" = callPackage @@ -88579,7 +87348,6 @@ self: { description = "Sums/products/lists/trees which can be extended in other modules"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "extensible-effects" = callPackage @@ -88764,7 +87532,6 @@ self: { description = "Given a hackage package outputs the list of its dependencies"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "extractable-singleton" = callPackage @@ -88960,8 +87727,6 @@ self: { ]; description = "Rational arithmetic in an irrational world"; license = "GPL"; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "facts" = callPackage @@ -88995,7 +87760,6 @@ self: { description = "A driver for the Factual API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fad" = callPackage @@ -89027,8 +87791,6 @@ self: { ]; description = "Minimal library for music generation and notation"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fadno-braids" = callPackage @@ -89046,7 +87808,6 @@ self: { description = "Braid representations in Haskell"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fadno-xml" = callPackage @@ -89061,8 +87822,6 @@ self: { ]; description = "XML/XSD combinators/schemas/codegen"; license = lib.licenses.bsd2; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fail" = callPackage @@ -89172,8 +87931,6 @@ self: { testHaskellDepends = [ base hspec lens random text time ]; description = "Randomly generated fake data"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fake-type" = callPackage @@ -89346,7 +88103,6 @@ self: { description = "Falling sand game/cellular automata simulation using regular parallel arrays"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fallingblocks" = callPackage @@ -89366,7 +88122,6 @@ self: { description = "A fun falling blocks game"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "familiar-reflection" = callPackage @@ -89395,7 +88150,6 @@ self: { description = "A family tree library for the Haskell programming language"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "farmhash" = callPackage @@ -89427,8 +88181,6 @@ self: { doHaddock = false; description = "Fast functions on integers"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fast-builder" = callPackage @@ -89488,7 +88240,6 @@ self: { description = "Integer-to-digits conversion"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fast-downward" = callPackage @@ -89630,8 +88381,6 @@ self: { ]; description = "A simple, mindless parser for fasta files"; license = lib.licenses.gpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fastbayes" = callPackage @@ -89697,7 +88446,6 @@ self: { description = "Fast Internet Relay Chat (IRC) library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fastly" = callPackage @@ -89778,8 +88526,6 @@ self: { ]; description = "A fast open-union type suitable for 100+ contained alternatives"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fathead-util" = callPackage @@ -89808,7 +88554,6 @@ self: { description = "A fault tree analysis library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fay" = callPackage @@ -90085,7 +88830,6 @@ self: { description = "Build and create Fedora package repos and branches"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fca" = callPackage @@ -90142,7 +88886,6 @@ self: { description = "A faster way to navigate directories using the command line"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fcf-containers" = callPackage @@ -90158,8 +88901,6 @@ self: { testHaskellDepends = [ base doctest first-class-families Glob ]; description = "Data structures and algorithms for first-class-families"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fcg" = callPackage @@ -90349,7 +89090,6 @@ self: { description = "A minimally obtrusive feature flag library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fec" = callPackage @@ -90412,7 +89152,6 @@ self: { description = "Fedora image download tool"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fedora-packages" = callPackage @@ -90572,7 +89311,6 @@ self: { description = "CI service around gipeda"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "feed-translator" = callPackage @@ -90595,7 +89333,6 @@ self: { description = "Translate syndication feeds"; license = lib.licenses.agpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "feed2lj" = callPackage @@ -90615,7 +89352,6 @@ self: { description = "(unsupported)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "feed2twitter" = callPackage @@ -90633,7 +89369,6 @@ self: { description = "Send posts from a feed to Twitter"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fei-base" = callPackage @@ -90662,7 +89397,6 @@ self: { description = "FFI to MXNet"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) mxnet;}; "fei-cocoapi" = callPackage @@ -90691,7 +89425,6 @@ self: { description = "Cocodataset with cocoapi"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fei-dataiter" = callPackage @@ -90719,7 +89452,6 @@ self: { description = "mxnet dataiters"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) mxnet;}; "fei-datasets" = callPackage @@ -90750,7 +89482,6 @@ self: { description = "Some datasets"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fei-examples" = callPackage @@ -90772,7 +89503,6 @@ self: { description = "fei examples"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fei-modelzoo" = callPackage @@ -90790,7 +89520,6 @@ self: { description = "A collection of standard models"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fei-nn" = callPackage @@ -90813,7 +89542,6 @@ self: { description = "Train a neural network with MXNet in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "feldspar-compiler" = callPackage @@ -90843,7 +89571,6 @@ self: { description = "Compiler for the Feldspar language"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {gcc_s = null;}; "feldspar-language" = callPackage @@ -90868,7 +89595,6 @@ self: { description = "A functional embedded language for DSP and parallelism"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "feldspar-signal" = callPackage @@ -91001,7 +89727,6 @@ self: { description = "Remote multi-db SQLCipher server"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fez-conf" = callPackage @@ -91105,7 +89830,6 @@ self: { description = "Tutorials on ffmpeg usage to play video/audio"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fft" = callPackage @@ -91275,7 +89999,6 @@ self: { description = "update statically hosted file in a push stule through socketed"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fields" = callPackage @@ -91292,7 +90015,6 @@ self: { description = "First-class record field combinators with infix record field syntax"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fields-json" = callPackage @@ -91517,8 +90239,6 @@ self: { ]; description = "A cache system associating values to files"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "filediff" = callPackage @@ -91629,7 +90349,6 @@ self: { description = "Reversable and secure encoding of object ids as filepaths"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "filepath-io-access" = callPackage @@ -91642,7 +90361,6 @@ self: { description = "IO Access for filepath"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "filepather" = callPackage @@ -91660,7 +90378,6 @@ self: { description = "Functions on System.FilePath"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "filepattern" = callPackage @@ -91689,8 +90406,6 @@ self: { ]; description = "Library to process and search large files or a collection of files"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "filestore" = callPackage @@ -91769,7 +90484,6 @@ self: { description = "Enumerator-based API for manipulating the filesystem"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "filesystem-trees" = callPackage @@ -91934,7 +90648,6 @@ self: { description = "Find the clumpiness of labels in a tree"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "find-conduit" = callPackage @@ -92003,7 +90716,6 @@ self: { description = "List http/html files"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fingertree" = callPackage @@ -92337,7 +91049,6 @@ self: { description = "Defunctionalisation for Yhc Core"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fishfood" = callPackage @@ -92361,8 +91072,6 @@ self: { ]; description = "Calculates file-size frequency-distribution"; license = "GPL"; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fit" = callPackage @@ -92462,8 +91171,6 @@ self: { ]; description = "Program to manage the imports of a haskell module"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fix-parser-simple" = callPackage @@ -92478,7 +91185,6 @@ self: { description = "Simple fix-expression parser"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fix-symbols-gitit" = callPackage @@ -92571,7 +91277,6 @@ self: { description = "Unbox instances for the fixed-point package"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fixed-point-vector-space" = callPackage @@ -92584,7 +91289,6 @@ self: { description = "vector-space instances for the fixed-point package"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fixed-precision" = callPackage @@ -92824,7 +91528,6 @@ self: { description = "FIX (co)parser"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fixie" = callPackage @@ -92978,7 +91681,6 @@ self: { description = "Support for writing picture to FLAC metadata blocks with JuicyPixels"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "flaccuraterip" = callPackage @@ -93090,7 +91792,6 @@ self: { description = "Generate language learning flashcards from video"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "flat" = callPackage @@ -93198,7 +91899,6 @@ self: { description = "Haskell implementation of the FlatBuffers protocol"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "flatparse" = callPackage @@ -93289,7 +91989,6 @@ self: { description = "Flexible wrappers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "flexiwrap-smallcheck" = callPackage @@ -93304,7 +92003,6 @@ self: { description = "SmallCheck (Serial) instances for flexiwrap"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "flick-duration" = callPackage @@ -93371,6 +92069,8 @@ self: { ]; description = "Parsing of pilot tracklogs dumped as KML"; license = lib.licenses.mpl20; + hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "flink-statefulfun" = callPackage @@ -93437,7 +92137,6 @@ self: { description = "f-lite compiler, interpreter and libraries"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "flo" = callPackage @@ -93666,7 +92365,6 @@ self: { description = "API integration with Flowdock"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "flowdock-rest" = callPackage @@ -93714,7 +92412,6 @@ self: { description = "Analyze 454 flowgrams (.SFF files)"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "flowlocks-framework" = callPackage @@ -93748,7 +92445,6 @@ self: { description = "Simulate 454 pyrosequencing"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "flp" = callPackage @@ -93855,7 +92551,6 @@ self: { description = "Fltkhs Fluid Examples"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fltkhs-hello-world" = callPackage @@ -93914,7 +92609,6 @@ self: { description = "A structured logger for Fluentd (Haskell)"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fluent-logger-conduit" = callPackage @@ -94142,8 +92836,6 @@ self: { libraryHaskellDepends = [ base enum-text-rio ]; description = "Adaptor for getting fmt to work with rio"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fmt-terminal-colors" = callPackage @@ -94156,8 +92848,6 @@ self: { testHaskellDepends = [ ansi-terminal base fmt ]; description = "ANSI terminal colors formatters for fmt library"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fn" = callPackage @@ -94433,7 +93123,6 @@ self: { description = "Attoparsec and foldl-transduce integration"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "folds" = callPackage @@ -94560,7 +93249,6 @@ self: { description = "Follow Tweets anonymously"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "foma" = callPackage @@ -94573,8 +93261,6 @@ self: { librarySystemDepends = [ foma ]; description = "Simple Haskell bindings for Foma"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) foma;}; "font-awesome-type" = callPackage @@ -94618,7 +93304,6 @@ self: { description = "Paper soccer, an OpenGL game"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "foobar" = callPackage @@ -94892,7 +93577,6 @@ self: { description = "A statically typed, functional programming language"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "format" = callPackage @@ -94906,7 +93590,6 @@ self: { description = "Rendering from and scanning to format strings"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "format-numbers" = callPackage @@ -94937,7 +93620,6 @@ self: { description = "A utility for writing the date to dzen2"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "formatn" = callPackage @@ -95044,7 +93726,6 @@ self: { description = "A statically typed, functional programming language"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "formlets" = callPackage @@ -95062,7 +93743,6 @@ self: { description = "Formlets implemented in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "formlets-hsp" = callPackage @@ -95080,7 +93760,6 @@ self: { description = "HSP support for Formlets"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "formura" = callPackage @@ -95161,7 +93840,6 @@ self: { description = "A simple eDSL for generating arrayForth code"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fortran-src" = callPackage @@ -95213,7 +93891,6 @@ self: { description = "Common functions and utils for fortran-src"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fortytwo" = callPackage @@ -95261,7 +93938,6 @@ self: { description = "Foscam File format"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "foscam-filename" = callPackage @@ -95310,7 +93986,6 @@ self: { description = "Foscam File format"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "foundation" = callPackage @@ -95395,7 +94070,6 @@ self: { description = "IEEE 754-2019 compliant operations"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fpco-api" = callPackage @@ -95480,7 +94154,6 @@ self: { description = "Haskell bindings to "; license = lib.licenses.lgpl21Plus; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) fplll;}; "fpnla" = callPackage @@ -95517,7 +94190,6 @@ self: { description = "Example implementations for FPNLA library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fptest" = callPackage @@ -95656,7 +94328,6 @@ self: { description = "A markdown to Frame GUI writer for Pandoc"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "franchise" = callPackage @@ -95797,8 +94468,6 @@ self: { ]; description = "Free algebras"; license = lib.licenses.mpl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "free-categories" = callPackage @@ -95827,8 +94496,6 @@ self: { benchmarkHaskellDepends = [ base criterion ]; description = "efficient data types for free categories and arrows"; license = lib.licenses.mpl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "free-concurrent" = callPackage @@ -95967,7 +94634,6 @@ self: { description = "Automatically Generating Counterexamples to Naive Free Theorems"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "free-theorems-seq" = callPackage @@ -95986,7 +94652,6 @@ self: { description = "Taming Selective Strictness"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "free-theorems-seq-webui" = callPackage @@ -96006,7 +94671,6 @@ self: { description = "Taming Selective Strictness"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "free-theorems-webui" = callPackage @@ -96027,7 +94691,6 @@ self: { description = "CGI-based web interface for the free-theorems package"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "free-v-bucks-generator-no-survey" = callPackage @@ -96118,7 +94781,6 @@ self: { description = "A soccer game"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "freelude" = callPackage @@ -96139,7 +94801,6 @@ self: { description = "A generalisation of the Category->Functor->Applicative->Monad hierarchy and more"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "freenect" = callPackage @@ -96195,7 +94856,6 @@ self: { description = "Handle effects conversely using monadic conversation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "freer-effects" = callPackage @@ -96628,8 +95288,6 @@ self: { ]; description = "A reactive frontend web framework"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "frontmatter" = callPackage @@ -96720,7 +95378,6 @@ self: { description = "Program awesome stuff with Gloss and frpnow!"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "frpnow-gtk" = callPackage @@ -96738,7 +95395,6 @@ self: { description = "Program GUIs with GTK and frpnow!"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "frpnow-gtk3" = callPackage @@ -96753,7 +95409,6 @@ self: { description = "Program GUIs with GTK3 and frpnow!"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "frpnow-vty" = callPackage @@ -96769,7 +95424,6 @@ self: { description = "Program terminal applications with vty and frpnow!"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "frquotes" = callPackage @@ -97012,7 +95666,6 @@ self: { description = "A thin layer over USB to communicate with FTDI chips"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ftp-client" = callPackage @@ -97049,7 +95702,6 @@ self: { description = "Transfer file with FTP and FTPS with Conduit"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ftp-conduit" = callPackage @@ -97099,7 +95751,6 @@ self: { description = "Depth-typed functor-based trees, both top-down and bottom-up"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ftshell" = callPackage @@ -97119,7 +95770,6 @@ self: { description = "Shell interface to the FreeTheorems library"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fugue" = callPackage @@ -97212,7 +95862,6 @@ self: { description = "IRC bot for fun, learning, creativity and collaboration"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "funbot-client" = callPackage @@ -97264,7 +95913,6 @@ self: { description = "Git hook which sends events to FunBot"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "funcmp" = callPackage @@ -97317,7 +95965,6 @@ self: { description = "call-by-value lambda-calculus with meta-programming"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "funcons-simple" = callPackage @@ -97334,7 +95981,6 @@ self: { description = "A modular interpreter for executing SIMPLE funcons"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "funcons-tools" = callPackage @@ -97362,7 +96008,6 @@ self: { description = "A modular interpreter for executing funcons"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "funcons-values" = callPackage @@ -97404,7 +96049,6 @@ self: { description = "Combining functions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "function-instances-algebra" = callPackage @@ -97430,7 +96074,6 @@ self: { description = "Combinators that allow for a more functional/monadic style of Arrow programming"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "functional-kmp" = callPackage @@ -97529,7 +96172,6 @@ self: { description = "Functor combinators with tries & zippers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "functor-friends" = callPackage @@ -97682,7 +96324,6 @@ self: { description = "Utility functions for using funflow with nix"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fungll-combinators" = callPackage @@ -97717,7 +96358,6 @@ self: { description = "A unioning file-system using HFuse"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "funnyprint" = callPackage @@ -97734,7 +96374,6 @@ self: { description = "funnyPrint function to colorize GHCi output"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "funpat" = callPackage @@ -97770,7 +96409,6 @@ self: { description = "A modern DPLL-style SAT solver"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "funspection" = callPackage @@ -97925,7 +96563,6 @@ self: { description = "A fused-effects adapter for squeal-postgresql"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fused-effects-th" = callPackage @@ -97942,8 +96579,6 @@ self: { ]; description = "Template Haskell helpers for fused-effects"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fusion" = callPackage @@ -98191,8 +96826,6 @@ self: { base criterion fuzzy-time genvalidity-criterion ]; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fuzzy-timings" = callPackage @@ -98317,7 +96950,6 @@ self: { description = "FWGL GLFW backend"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fwgl-javascript" = callPackage @@ -98334,7 +96966,6 @@ self: { description = "FWGL GHCJS backend"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "fx" = callPackage @@ -98358,7 +96989,6 @@ self: { description = "Interface to the FXPak/FXPak Pro USB interface"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "g-npm" = callPackage @@ -98407,7 +97037,6 @@ self: { description = "Haskell symbolic execution engine"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "g2q" = callPackage @@ -98420,7 +97049,6 @@ self: { description = "G2Q allows constraint programming, via writing Haskell predicates"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "g4ip" = callPackage @@ -98470,7 +97098,6 @@ self: { description = "General Alignment Clustering Tool"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "galois-fft" = callPackage @@ -98498,7 +97125,6 @@ self: { description = "FFTs over finite fields"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "galois-field" = callPackage @@ -98727,7 +97353,6 @@ self: { description = "Connect to gargoyle-managed postgresql instances"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gargoyle-postgresql-nix" = callPackage @@ -98845,7 +97470,6 @@ self: { description = "planar graph embedding into a plane"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gc" = callPackage @@ -98979,7 +97603,6 @@ self: { description = "API Wrapping for Coinbase's GDAX exchange"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gdelt" = callPackage @@ -99021,7 +97644,6 @@ self: { description = "Generic diff for the instant-generics library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gdiff-th" = callPackage @@ -99105,7 +97727,6 @@ self: { description = "Parser for the GEDCOM genealogy file format"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "geek" = callPackage @@ -99127,7 +97748,6 @@ self: { description = "Geek blog engine"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "geek-server" = callPackage @@ -99152,7 +97772,6 @@ self: { description = "Geek blog engine server"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gegl" = callPackage @@ -99213,7 +97832,6 @@ self: { description = "FreeType2 based text rendering for the gelatin realtime rendering system"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gelatin-fruity" = callPackage @@ -99226,7 +97844,6 @@ self: { description = "Gelatin's support for rendering TTF outlines, using FontyFruity"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gelatin-gl" = callPackage @@ -99249,7 +97866,6 @@ self: { description = "OpenGL rendering routines for the gelatin-picture graphics EDSL"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gelatin-sdl2" = callPackage @@ -99268,7 +97884,6 @@ self: { description = "An SDL2 backend for the gelatin renderer"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gelatin-shaders" = callPackage @@ -99282,7 +97897,6 @@ self: { description = "Gelatin's OpenGL shaders"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gemini-router" = callPackage @@ -99336,8 +97950,6 @@ self: { ]; description = "A barebones textboard for the Gemini protocol"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gemstone" = callPackage @@ -100122,7 +98734,6 @@ self: { description = "Reimplementation of the gdiff algorithm for generics-mrsop"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "generics-sop" = callPackage @@ -100197,7 +98808,6 @@ self: { description = "Opinionated bootstrapping for Haskell web services"; license = lib.licenses.isc; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "genesis-test" = callPackage @@ -100222,7 +98832,6 @@ self: { description = "Opinionated bootstrapping for Haskell web services"; license = lib.licenses.isc; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "genetics" = callPackage @@ -100262,7 +98871,6 @@ self: { description = "GenI graphical user interface"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "geni-util" = callPackage @@ -100287,7 +98895,6 @@ self: { description = "Companion tools for use with the GenI surface realiser"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "geniconvert" = callPackage @@ -100308,7 +98915,6 @@ self: { description = "Conversion utility for the GenI generator"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "genifunctors" = callPackage @@ -100367,7 +98973,6 @@ self: { description = "Simple HTTP server for GenI results"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "genprog" = callPackage @@ -101082,7 +99687,6 @@ self: { description = "Geodetic calculations"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "geodetic-types" = callPackage @@ -101195,7 +99799,6 @@ self: { description = "Geolite CSV Parser"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "geom2d" = callPackage @@ -101251,7 +99854,6 @@ self: { description = "Fetch from emusic using .emx files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "getflag" = callPackage @@ -101609,8 +100211,6 @@ self: { ]; description = "An AST and compiler plugin for dumping GHC's Core representation"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ghc-dump-tree" = callPackage @@ -101659,8 +100259,6 @@ self: { ]; description = "Handy tools for working with ghc-dump dumps"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ghc-dup" = callPackage @@ -101872,7 +100470,6 @@ self: { description = "Find the Haddock documentation for a symbol"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ghc-instances" = callPackage @@ -101895,7 +100492,6 @@ self: { description = "Easily import all instances contained in GHC distributed libraries"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ghc-justdoit" = callPackage @@ -102107,7 +100703,6 @@ self: { description = "Happy Haskell Hacking"; license = lib.licenses.agpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ghc-mtl" = callPackage @@ -102534,7 +101129,6 @@ self: { description = "A compiler plugin which generates tags file from GHC parsed syntax tree"; license = lib.licenses.mpl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ghc-tcplugins-extra_0_3_2" = callPackage @@ -102722,7 +101316,6 @@ self: { description = "Live visualization of data structures in GHCi"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ghcflags" = callPackage @@ -102778,8 +101371,6 @@ self: { ]; description = "ghci-dap is a GHCi having DAP interface"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ghci-diagrams" = callPackage @@ -102887,7 +101478,6 @@ self: { description = "colored pretty-printing within ghci"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ghci-websockets" = callPackage @@ -103100,7 +101690,9 @@ self: { ]; description = "GHCJS DOM Hello World, an example package"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; + platforms = [ + "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" + ]; }) {}; "ghcjs-dom-jsaddle" = callPackage @@ -103176,7 +101768,6 @@ self: { description = "Client-side web EDSL for transient nodes running in the web browser"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ghcjs-perch" = callPackage @@ -103353,7 +101944,6 @@ self: { description = "ghc toolchain installer"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ghczdecode" = callPackage @@ -103403,7 +101993,6 @@ self: { description = "Trivial routines for inspecting git repositories"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gi-atk" = callPackage @@ -103506,7 +102095,6 @@ self: { description = "Bridge between packages gi-* and cairo-core"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gi-cairo-connector" = callPackage @@ -104070,7 +102658,6 @@ self: { description = "Gsk bindings"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) gtk4;}; "gi-gst" = callPackage @@ -104111,8 +102698,6 @@ self: { libraryPkgconfigDepends = [ gst-plugins-base ]; description = "GStreamerAudio bindings"; license = lib.licenses.lgpl21Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs.gst_all_1) gst-plugins-base;}; "gi-gstbase" = callPackage @@ -104159,7 +102744,6 @@ self: { description = "GStreamer Plugins Base Utils bindings"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {gstreamer-pbutils = null;}; "gi-gsttag" = callPackage @@ -104539,7 +103123,6 @@ self: { libraryPkgconfigDepends = [ webkitgtk ]; description = "JavaScriptCore bindings"; license = lib.licenses.lgpl21Only; - hydraPlatforms = lib.platforms.none; }) {inherit (pkgs) webkitgtk;}; "gi-javascriptcore_4_0_23" = callPackage @@ -104703,8 +103286,6 @@ self: { libraryPkgconfigDepends = [ poppler_gi ]; description = "Poppler bindings"; license = lib.licenses.lgpl21Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) poppler_gi;}; "gi-secret" = callPackage @@ -104864,7 +103445,6 @@ self: { libraryPkgconfigDepends = [ webkitgtk ]; description = "WebKit2 bindings"; license = lib.licenses.lgpl21Only; - hydraPlatforms = lib.platforms.none; }) {inherit (pkgs) webkitgtk;}; "gi-webkit2_4_0_27" = callPackage @@ -104914,7 +103494,6 @@ self: { libraryPkgconfigDepends = [ webkitgtk ]; description = "WebKit2-WebExtension bindings"; license = lib.licenses.lgpl21Only; - hydraPlatforms = lib.platforms.none; }) {inherit (pkgs) webkitgtk;}; "gi-wnck" = callPackage @@ -105442,7 +104021,6 @@ self: { description = "Custom git command for formatting code"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "git-freq" = callPackage @@ -105486,7 +104064,6 @@ self: { description = "More intelligent push-to-GitHub utility"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "git-jump" = callPackage @@ -105559,8 +104136,6 @@ self: { ]; description = "Passively snapshots working tree changes efficiently"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "git-object" = callPackage @@ -105578,7 +104153,6 @@ self: { description = "Git object and its parser"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "git-remote-ipfs" = callPackage @@ -105611,7 +104185,6 @@ self: { description = "Git remote helper to store git objects on IPFS"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "git-repair" = callPackage @@ -106007,7 +104580,6 @@ self: { description = "GitHub WebHook Handler implementation for Snap"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "github-webhooks" = callPackage @@ -106167,8 +104739,6 @@ self: { ]; description = "API library for working with Git repositories"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gitlib-cmdline" = callPackage @@ -106216,7 +104786,6 @@ self: { description = "Run tests between repositories"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gitlib-libgit2" = callPackage @@ -106243,8 +104812,6 @@ self: { ]; description = "Libgit2 backend for gitlib"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gitlib-s3" = callPackage @@ -106275,7 +104842,6 @@ self: { description = "Gitlib repository backend for storing Git objects in Amazon S3"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gitlib-sample" = callPackage @@ -106289,8 +104855,6 @@ self: { ]; description = "Sample backend for gitlib showing the basic structure for any backend"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gitlib-test" = callPackage @@ -106309,8 +104873,6 @@ self: { ]; description = "Test library for confirming gitlib backend compliance"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gitlib-utils" = callPackage @@ -106418,7 +104980,6 @@ self: { description = "CLI Giphy search tool with previews in iTerm 2"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gjk" = callPackage @@ -106531,7 +105092,6 @@ self: { description = "Automagically declares getters for widget handles in specified interface file"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "glambda" = callPackage @@ -106620,7 +105180,6 @@ self: { description = "Extensible effects using ContT, State and variants"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "glazier-pipes" = callPackage @@ -106637,7 +105196,6 @@ self: { description = "A threaded rendering framework using glaizer and pipes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "glazier-react" = callPackage @@ -106658,7 +105216,6 @@ self: { description = "ReactJS binding using Glazier.Command."; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "glazier-react-examples" = callPackage @@ -106684,7 +105241,6 @@ self: { description = "Examples of using glazier-react"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "glazier-react-widget" = callPackage @@ -106705,7 +105261,6 @@ self: { description = "Generic widget library using glazier-react"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gli" = callPackage @@ -106878,7 +105433,6 @@ self: { description = "Library enabling unique top-level declarations"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "global-config" = callPackage @@ -106900,7 +105454,6 @@ self: { description = "Global mutable configuration"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "global-lock" = callPackage @@ -106949,7 +105502,6 @@ self: { description = "ray tracer"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gloss" = callPackage @@ -107005,7 +105557,6 @@ self: { description = "An Interface for gloss in terms of a reactive-banana Behavior"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gloss-devil" = callPackage @@ -107018,7 +105569,6 @@ self: { description = "Display images in Gloss using libdevil for decoding"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gloss-examples" = callPackage @@ -107039,7 +105589,6 @@ self: { description = "Examples using the gloss library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gloss-export" = callPackage @@ -107153,7 +105702,6 @@ self: { description = "A Sodium interface to the Gloss drawing package"; license = lib.licenses.agpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "glpk-headers" = callPackage @@ -107192,8 +105740,6 @@ self: { ]; description = "Comprehensive GLPK linear programming bindings"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) glpk;}; "glsl" = callPackage @@ -107392,7 +105938,6 @@ self: { description = "Composable maps and generic tries"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gmndl" = callPackage @@ -107412,7 +105957,6 @@ self: { description = "Mandelbrot Set explorer using GTK"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gmpint" = callPackage @@ -107441,7 +105985,6 @@ self: { description = "Randomly set a picture as the GNOME desktop background"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gnome-keyring" = callPackage @@ -107480,7 +106023,6 @@ self: { description = "Binding to the GNOME Virtual File System library"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {gnome-vfs = null; gnome-vfs_module = null;}; "gnss-converters" = callPackage @@ -107509,7 +106051,6 @@ self: { description = "GNSS Converters"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gnuidn" = callPackage @@ -107533,7 +106074,6 @@ self: { description = "Bindings for GNU IDN"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) libidn;}; "gnuplot" = callPackage @@ -107621,7 +106161,6 @@ self: { description = "Scientific computing on geometric objects"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "goal-probability" = callPackage @@ -107642,7 +106181,6 @@ self: { description = "Manifolds of probability distributions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "goal-simulation" = callPackage @@ -107667,7 +106205,6 @@ self: { description = "Mealy based simulation tools"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "goat" = callPackage @@ -107702,8 +106239,6 @@ self: { testHaskellDepends = [ base containers HUnit mtl parsec ]; description = "A monadic take on a 2,500-year-old board game - library"; license = lib.licenses.agpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "goatee-gtk" = callPackage @@ -107724,8 +106259,6 @@ self: { testHaskellDepends = [ base HUnit ]; description = "A monadic take on a 2,500-year-old board game - GTK+ UI"; license = lib.licenses.agpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gochan" = callPackage @@ -110065,8 +108598,6 @@ self: { ]; description = "A lightweight golden test runner"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gooey" = callPackage @@ -110136,7 +108667,6 @@ self: { description = "Google Drive API access"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "google-html5-slide" = callPackage @@ -110188,7 +108718,6 @@ self: { description = "Write GMail filters and output to importable XML"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "google-maps-geocoding" = callPackage @@ -110206,7 +108735,6 @@ self: { description = "Bindings to the Google Geocoding API (formerly Maps Geocoding API)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "google-oauth2" = callPackage @@ -110282,8 +108810,6 @@ self: { ]; description = "Get a signed JWT for Google Service Accounts"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "google-search" = callPackage @@ -110320,8 +108846,6 @@ self: { ]; description = "Google APIs for server to server applications"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "google-static-maps" = callPackage @@ -110342,7 +108866,6 @@ self: { description = "Bindings to the Google Maps Static API (formerly Static Maps API)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "google-translate" = callPackage @@ -110379,7 +108902,6 @@ self: { description = "Haskell implementation of the Google+ API v1"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "googlepolyline" = callPackage @@ -110508,7 +109030,6 @@ self: { description = "Gore&Ash engine extension that implements actor style of programming"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gore-and-ash-async" = callPackage @@ -110532,7 +109053,6 @@ self: { description = "Core module for Gore&Ash engine that embeds async IO actions into game loop"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gore-and-ash-demo" = callPackage @@ -110559,7 +109079,6 @@ self: { description = "Demonstration game for Gore&Ash game engine"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gore-and-ash-glfw" = callPackage @@ -110577,7 +109096,6 @@ self: { description = "Core module for Gore&Ash engine for GLFW input events"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gore-and-ash-lambdacube" = callPackage @@ -110598,7 +109116,6 @@ self: { description = "Core module for Gore&Ash engine that do something"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gore-and-ash-logging" = callPackage @@ -110618,7 +109135,6 @@ self: { description = "Core module for gore-and-ash with logging utilities"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gore-and-ash-network" = callPackage @@ -110641,7 +109157,6 @@ self: { description = "Core module for Gore&Ash engine with low level network API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gore-and-ash-sdl" = callPackage @@ -110661,7 +109176,6 @@ self: { description = "Gore&Ash core module for integration with SDL library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gore-and-ash-sync" = callPackage @@ -110682,7 +109196,6 @@ self: { description = "Gore&Ash module for high level network synchronization"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gothic" = callPackage @@ -110807,7 +109320,6 @@ self: { description = "For manipulating GPS coordinates and trails"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gps2htmlReport" = callPackage @@ -110829,7 +109341,6 @@ self: { description = "GPS to HTML Summary Report"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gpx-conduit" = callPackage @@ -110876,7 +109387,6 @@ self: { description = "Applicative parsers for form parameter lists"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "graceful" = callPackage @@ -110934,7 +109444,6 @@ self: { description = "Monadic correlated log events"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "grakn" = callPackage @@ -110978,7 +109487,6 @@ self: { description = "A parsing library of context-free grammar combinators"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "grammatical-parsers" = callPackage @@ -111014,8 +109522,6 @@ self: { ]; description = "parsers that combine into grammars"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "grapefruit-examples" = callPackage @@ -111033,7 +109539,6 @@ self: { description = "Examples using the Grapefruit library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "grapefruit-frp" = callPackage @@ -111065,7 +109570,6 @@ self: { description = "A record system for Functional Reactive Programming"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "grapefruit-ui" = callPackage @@ -111085,7 +109589,6 @@ self: { description = "Declarative user interface programming"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "grapefruit-ui-gtk" = callPackage @@ -111106,7 +109609,6 @@ self: { description = "GTK+-based backend for declarative user interface programming"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "graph" = callPackage @@ -111141,8 +109643,6 @@ self: { ]; description = "Fast, memory efficient and persistent graph implementation"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "graph-generators" = callPackage @@ -111215,7 +109715,6 @@ self: { description = "Interactive graph rewriting system implementing various well-known combinators"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "graph-rewriting-gl" = callPackage @@ -111233,7 +109732,6 @@ self: { description = "OpenGL interface for interactive port graph rewriting"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "graph-rewriting-lambdascope" = callPackage @@ -111256,7 +109754,6 @@ self: { description = "Lambdascope, an optimal evaluator of the lambda calculus, as an interactive graph-rewriting system"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "graph-rewriting-layout" = callPackage @@ -111273,7 +109770,6 @@ self: { description = "Force-directed node placement intended for incremental graph drawing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "graph-rewriting-ski" = callPackage @@ -111294,7 +109790,6 @@ self: { description = "Two evalutors of the SKI combinator calculus as interactive graph rewrite systems"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "graph-rewriting-strategies" = callPackage @@ -111311,7 +109806,6 @@ self: { description = "Evaluation strategies for port-graph rewriting systems"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "graph-rewriting-trs" = callPackage @@ -111334,7 +109828,6 @@ self: { description = "Evaluate first-order applicative term rewrite systems interactively using graph reduction"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "graph-rewriting-ww" = callPackage @@ -111356,7 +109849,6 @@ self: { description = "Evaluator of the lambda-calculus in an interactive graph rewriting system with explicit sharing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "graph-serialize" = callPackage @@ -111403,7 +109895,6 @@ self: { description = "Graph walk abstraction"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "graph-wrapper" = callPackage @@ -111505,7 +109996,6 @@ self: { description = "Classes for renderable objects"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "graphicstools" = callPackage @@ -111525,7 +110015,6 @@ self: { description = "Tools for creating graphical UIs, based on wxHaskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "graphite" = callPackage @@ -111608,8 +110097,6 @@ self: { ]; description = "Haskell GraphQL implementation"; license = "MPL-2.0 AND BSD-3-Clause"; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "graphql-api" = callPackage @@ -111672,7 +110159,6 @@ self: { description = "A client for Haskell programs to query a GraphQL API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "graphql-utils" = callPackage @@ -111751,7 +110237,6 @@ self: { description = "A simple tool to illustrate dependencies between Haskell types"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "graphula" = callPackage @@ -111779,8 +110264,6 @@ self: { testToolDepends = [ markdown-unlit ]; description = "A declarative library for describing dependencies between data"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "graphula-core" = callPackage @@ -111980,7 +110463,6 @@ self: { description = "A foreign function interface pre-processor library for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "greenclip" = callPackage @@ -112190,7 +110672,6 @@ self: { description = "Grid-based prototyping framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gridbounds" = callPackage @@ -112204,7 +110685,6 @@ self: { description = "Collision detection for GridBox"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gridbox" = callPackage @@ -112254,7 +110734,6 @@ self: { description = "Grid-based multimedia engine"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "grids" = callPackage @@ -112641,8 +111120,6 @@ self: { libraryHaskellDepends = [ base generic-data groups ]; description = "Generically derive Group instances"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "grow-vector" = callPackage @@ -112715,7 +111192,6 @@ self: { description = "gRPC client for etcd"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "grpc-haskell" = callPackage @@ -112747,7 +111223,6 @@ self: { description = "Haskell implementation of gRPC layered on shared C library"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "grpc-haskell-core" = callPackage @@ -112774,7 +111249,6 @@ self: { description = "Haskell implementation of gRPC layered on shared C library"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {gpr = null; inherit (pkgs) grpc;}; "gruff" = callPackage @@ -112797,7 +111271,6 @@ self: { description = "fractal explorer GUI using the ruff library"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gruff-examples" = callPackage @@ -112817,7 +111290,6 @@ self: { description = "Mandelbrot Set examples using ruff and gruff"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gsasl" = callPackage @@ -112864,7 +111336,6 @@ self: { description = "scrapes google scholar, provides RSS feed"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gsl-random" = callPackage @@ -112891,7 +111362,6 @@ self: { description = "Instances for using gsl-random with random-fu"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gsmenu" = callPackage @@ -112957,7 +111427,6 @@ self: { description = "Generic implementation of Storable"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gstreamer" = callPackage @@ -113013,7 +111482,6 @@ self: { description = "The General Transit Feed Specification format"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gtfs-realtime" = callPackage @@ -113126,7 +111594,6 @@ self: { description = "GTK+ Serialized event"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) gtk2;}; "gtk-simple-list-view" = callPackage @@ -113171,6 +111638,8 @@ self: { platforms = [ "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" ]; + hydraPlatforms = lib.platforms.none; + broken = true; }) {inherit (pkgs) gtk3;}; "gtk-strut" = callPackage @@ -113467,7 +111936,6 @@ self: { description = "Binding to the GtkImageView library"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) gtkimageview;}; "gtkrsync" = callPackage @@ -113487,7 +111955,6 @@ self: { description = "Gnome rsync progress display"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "gtksourceview2" = callPackage @@ -113553,7 +112020,6 @@ self: { description = "Datatype-generic rewriting with preconditions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "guess-combinator" = callPackage @@ -113566,7 +112032,6 @@ self: { description = "Generate simple combinators given their type"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "guid" = callPackage @@ -113791,7 +112256,6 @@ self: { description = "Control your Arduino board from Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hBDD" = callPackage @@ -113853,8 +112317,6 @@ self: { testHaskellDepends = [ base hashable ]; description = "Conceptual modelling support for Haskell"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hCsound" = callPackage @@ -113976,7 +112438,6 @@ self: { description = "The tool to transform the OFF to other image format"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hOff-parser" = callPackage @@ -114055,7 +112516,6 @@ self: { description = "Protein Databank file format library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hPDB-examples" = callPackage @@ -114083,7 +112543,6 @@ self: { description = "Examples for hPDB library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hPushover" = callPackage @@ -114285,7 +112744,6 @@ self: { description = "Haskell message bot framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hable" = callPackage @@ -114322,7 +112780,6 @@ self: { description = "A minimalist static blog generator"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hablog" = callPackage @@ -114346,7 +112803,6 @@ self: { description = "A blog system"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hacanon-light" = callPackage @@ -114390,7 +112846,6 @@ self: { description = "Hack contrib"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hack-contrib-press" = callPackage @@ -114408,7 +112863,6 @@ self: { description = "Hack helper that renders Press templates"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hack-frontend-happstack" = callPackage @@ -114471,7 +112925,6 @@ self: { description = "hack handler implementation using epoll"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hack-handler-evhttp" = callPackage @@ -114491,7 +112944,6 @@ self: { description = "Hack EvHTTP (libevent) Handler"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {event = null;}; "hack-handler-fastcgi" = callPackage @@ -114505,7 +112957,6 @@ self: { description = "Hack handler direct to fastcgi (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) fcgi;}; "hack-handler-happstack" = callPackage @@ -114542,7 +112993,6 @@ self: { description = "Hyena hack handler"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hack-handler-kibro" = callPackage @@ -114575,7 +113025,6 @@ self: { description = "A simplistic HTTP server handler for Hack. (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hack-middleware-cleanpath" = callPackage @@ -114590,7 +113039,6 @@ self: { description = "Applies some basic redirect rules to get cleaner paths. (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hack-middleware-clientsession" = callPackage @@ -114607,7 +113055,6 @@ self: { description = "Middleware for easily keeping session data in client cookies. (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hack-middleware-gzip" = callPackage @@ -114635,7 +113082,6 @@ self: { description = "Automatic wrapping of JSON responses to convert into JSONP. (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hack2" = callPackage @@ -114699,7 +113145,6 @@ self: { description = "Hack2 Happstack server handler"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hack2-handler-mongrel2-http" = callPackage @@ -114721,7 +113166,6 @@ self: { description = "Hack2 Mongrel2 HTTP handler"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hack2-handler-snap-server" = callPackage @@ -114741,7 +113185,6 @@ self: { description = "Hack2 Snap server handler"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hack2-handler-warp" = callPackage @@ -115036,7 +113479,6 @@ self: { description = "The Hackage web server"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hackage-sparks" = callPackage @@ -115104,7 +113546,6 @@ self: { description = "Send new Hackage releases to Twitter"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hackager" = callPackage @@ -115187,7 +113628,6 @@ self: { description = "Generate useful files for Haskell projects"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hackport" = callPackage @@ -115273,7 +113713,6 @@ self: { description = "A documentation-generation tool for Haskell libraries"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haddock" = callPackage @@ -115291,7 +113730,6 @@ self: { description = "A documentation-generation tool for Haskell libraries"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haddock-api_2_23_1" = callPackage @@ -115484,7 +113922,6 @@ self: { description = "Generate docset of Dash by Haddock haskell documentation tool"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hadolint" = callPackage @@ -115600,7 +114037,6 @@ self: { description = "Fast command line tools for working with Hadoop"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haeredes" = callPackage @@ -115660,7 +114096,6 @@ self: { description = "A static site generator with blogging/comments support"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haggle" = callPackage @@ -115871,7 +114306,6 @@ self: { description = "Dynamic launcher of Hails applications"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hairy" = callPackage @@ -116050,7 +114484,6 @@ self: { description = "A package allowing to write Hakyll blog posts in Rmd"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-agda" = callPackage @@ -116068,7 +114501,6 @@ self: { description = "Wrapper to integrate literate Agda files with Hakyll"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-alectryon" = callPackage @@ -116086,7 +114518,6 @@ self: { description = "Hakyll extension for rendering Coq code using Alectryon"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-blaze-templates" = callPackage @@ -116099,7 +114530,6 @@ self: { description = "Blaze templates for Hakyll"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-contrib" = callPackage @@ -116116,7 +114546,6 @@ self: { description = "Extra modules for the hakyll website compiler"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-contrib-csv" = callPackage @@ -116134,7 +114563,6 @@ self: { description = "Generate Html tables from Csv files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-contrib-elm" = callPackage @@ -116154,7 +114582,6 @@ self: { description = "Compile Elm code for inclusion in Hakyll static site"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-contrib-hyphenation" = callPackage @@ -116167,7 +114594,6 @@ self: { description = "automatic hyphenation for Hakyll"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-contrib-i18n" = callPackage @@ -116213,7 +114639,6 @@ self: { description = "A hakyll library that helps maintain a separate links database"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-convert" = callPackage @@ -116263,7 +114688,6 @@ self: { description = "Dhall compiler for Hakyll"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-dir-list" = callPackage @@ -116279,7 +114703,6 @@ self: { description = "Allow Hakyll to create hierarchical menues from directories"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-elm" = callPackage @@ -116295,7 +114718,6 @@ self: { description = "Hakyll wrapper for the Elm compiler"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-favicon" = callPackage @@ -116311,7 +114733,6 @@ self: { testHaskellDepends = [ base ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-filestore" = callPackage @@ -116327,7 +114748,6 @@ self: { description = "FileStore utilities for Hakyll"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-images" = callPackage @@ -116350,7 +114770,6 @@ self: { description = "Hakyll utilities to work with images"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-ogmarkup" = callPackage @@ -116363,7 +114782,6 @@ self: { description = "Integrate ogmarkup document with Hakyll"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-process" = callPackage @@ -116376,7 +114794,6 @@ self: { description = "Hakyll compiler for arbitrary external processes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-sass" = callPackage @@ -116393,7 +114810,6 @@ self: { description = "Hakyll SASS compiler over hsass"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-series" = callPackage @@ -116406,7 +114822,6 @@ self: { description = "Adds series functionality to hakyll"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-shakespeare" = callPackage @@ -116425,7 +114840,6 @@ self: { description = "Hakyll Hamlet compiler"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-shortcode" = callPackage @@ -116466,7 +114880,6 @@ self: { description = "Use shortcut-links in markdown file for Hakyll"; license = lib.licenses.mpl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hakyll-typescript" = callPackage @@ -116484,7 +114897,6 @@ self: { description = "Typescript and javascript hakyll compilers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hal" = callPackage @@ -116509,8 +114921,6 @@ self: { ]; description = "A runtime environment for Haskell applications running on AWS Lambda"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "halberd" = callPackage @@ -116540,7 +114950,6 @@ self: { description = "A tool to generate missing import statements for Haskell modules"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "half" = callPackage @@ -116646,7 +115055,6 @@ self: { description = "Symmetry operations generater of Hall Symbols"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "halma" = callPackage @@ -116688,7 +115096,6 @@ self: { description = "GTK application for playing Halma"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "halma-telegram-bot" = callPackage @@ -116714,7 +115121,6 @@ self: { description = "Telegram bot for playing Halma"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haltavista" = callPackage @@ -116789,7 +115195,6 @@ self: { testHaskellDepends = [ base bytestring ]; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hamid" = callPackage @@ -116939,7 +115344,6 @@ self: { description = "Library to handle abstract music"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "han2zen" = callPackage @@ -117176,7 +115580,6 @@ self: { description = "Driver for real ethernet devices for HaNS"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hans-pfq" = callPackage @@ -117350,7 +115753,6 @@ self: { description = "The \"Haskell Applets\" Gtk+ ver. 2 back-end for \"happlets\"."; license = "AGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "happraise" = callPackage @@ -117380,7 +115782,6 @@ self: { ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "happs-hsp-template" = callPackage @@ -117398,7 +115799,6 @@ self: { description = "Utilities for using HSP templates in HAppS applications"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "happs-tutorial" = callPackage @@ -117424,7 +115824,6 @@ self: { description = "A Happstack Tutorial that is its own web 2.0-type demo."; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "happstack" = callPackage @@ -117460,7 +115859,6 @@ self: { description = "A Happstack Authentication Suite"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "happstack-authenticate" = callPackage @@ -117491,7 +115889,6 @@ self: { description = "Happstack Authentication Library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "happstack-clientsession" = callPackage @@ -117529,7 +115926,6 @@ self: { description = "Web related tools and services"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "happstack-data" = callPackage @@ -117552,7 +115948,6 @@ self: { description = "Happstack data manipulation libraries"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "happstack-dlg" = callPackage @@ -117571,7 +115966,6 @@ self: { description = "Cross-request user interactions for Happstack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "happstack-facebook" = callPackage @@ -117598,7 +115992,6 @@ self: { description = "A package for building Facebook applications using Happstack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "happstack-fastcgi" = callPackage @@ -117631,7 +116024,6 @@ self: { description = "Support for using Fay with Happstack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "happstack-fay-ajax" = callPackage @@ -117723,7 +116115,6 @@ self: { description = "Convenience functions for Happstack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "happstack-hsp" = callPackage @@ -117776,7 +116167,6 @@ self: { description = "Efficient relational queries on Haskell sets"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "happstack-jmacro" = callPackage @@ -117795,7 +116185,6 @@ self: { description = "Support for using JMacro with Happstack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "happstack-lite" = callPackage @@ -117844,7 +116233,6 @@ self: { description = "The haskell application server stack + reload"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "happstack-server" = callPackage @@ -117931,7 +116319,6 @@ self: { description = "Event-based distributed state"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "happstack-static-routing" = callPackage @@ -117994,7 +116381,6 @@ self: { description = "Utilities for using YUI3 with Happstack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "happy_1_19_9" = callPackage @@ -118117,7 +116503,6 @@ self: { description = "WebKit Happybara driver"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "happybara-webkit-server" = callPackage @@ -118190,7 +116575,6 @@ self: { description = "A Haskell implementation of the Quil instruction set for quantum computing"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "har" = callPackage @@ -118243,7 +116627,6 @@ self: { description = "Deep embedding of hardware descriptions with code generation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "harg" = callPackage @@ -118262,7 +116645,6 @@ self: { description = "Haskell program configuration using higher kinded data"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hark" = callPackage @@ -118282,7 +116664,6 @@ self: { description = "A Gentoo package query tool"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "harmony" = callPackage @@ -118309,7 +116690,6 @@ self: { description = "A web service specification compiler that generates implementation and tests"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haroonga" = callPackage @@ -118347,7 +116727,6 @@ self: { description = "Yet another Groonga http server"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "harp" = callPackage @@ -118426,7 +116805,6 @@ self: { description = "Template Haskell function for Has records"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hasbolt" = callPackage @@ -118447,8 +116825,6 @@ self: { ]; description = "Haskell driver for Neo4j 3+ (BOLT protocol)"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hasbolt-extras" = callPackage @@ -118888,7 +117264,6 @@ self: { description = "A library for working with HashFlare.io contracts and hashrates"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hashids" = callPackage @@ -119104,7 +117479,6 @@ self: { description = "Generate homepages for cabal packages"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskades" = callPackage @@ -119185,7 +117559,6 @@ self: { description = "A dialect of haskell with order of execution based on dependency resolution"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskbot-core" = callPackage @@ -119233,7 +117606,6 @@ self: { description = "Computes and audits file hashes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskdogs" = callPackage @@ -119271,7 +117643,6 @@ self: { description = "A small scheme interpreter"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskeline_0_8_1_2" = callPackage @@ -119361,7 +117732,6 @@ self: { description = "Haskell Application BlockChain Interface (ABCI) Server Library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-aliyun" = callPackage @@ -119385,7 +117755,6 @@ self: { description = "haskell client of aliyun service"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-awk" = callPackage @@ -119462,7 +117831,6 @@ self: { description = "Complete BitMEX Client"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-bitmex-rest" = callPackage @@ -119681,8 +118049,6 @@ self: { ]; description = "Haskell Debug Adapter"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-disque" = callPackage @@ -119724,7 +118090,6 @@ self: { description = "A program to find and display the docs and type of a name"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-eigen-util" = callPackage @@ -119738,7 +118103,6 @@ self: { description = "Some utility functions for haskell-eigen library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-exp-parser" = callPackage @@ -119820,7 +118184,6 @@ self: { description = "A Haskell ftp server with configurable backend"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-generate" = callPackage @@ -120459,7 +118822,6 @@ self: { description = "Tool for presenting PDF-based presentations"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-platform-test" = callPackage @@ -120489,7 +118851,6 @@ self: { description = "A test system for the Haskell Platform environment"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-player" = callPackage @@ -120632,7 +118993,6 @@ self: { description = "Reflect Haskell types"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-rules" = callPackage @@ -120749,7 +119109,6 @@ self: { description = "Observable orphan instances for haskell-src-exts"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-src-exts-prisms" = callPackage @@ -120962,7 +119321,6 @@ self: { description = "Utilities to tie up tokens to an AST"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-tools-ast" = callPackage @@ -120980,7 +119338,6 @@ self: { description = "Haskell AST for efficient tooling"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-tools-ast-fromghc" = callPackage @@ -120999,7 +119356,6 @@ self: { description = "Creating the Haskell-Tools AST from GHC's representations"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-tools-ast-gen" = callPackage @@ -121017,7 +119373,6 @@ self: { description = "Facilities for generating new parts of the Haskell-Tools AST"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-tools-ast-trf" = callPackage @@ -121034,7 +119389,6 @@ self: { description = "Conversions on Haskell-Tools AST to prepare for refactorings"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-tools-backend-ghc" = callPackage @@ -121053,7 +119407,6 @@ self: { description = "Creating the Haskell-Tools AST from GHC's representations"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-tools-builtin-refactorings" = callPackage @@ -121086,7 +119439,6 @@ self: { description = "Refactoring Tool for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-tools-cli" = callPackage @@ -121123,7 +119475,6 @@ self: { description = "Command-line frontend for Haskell-tools Refact"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-tools-daemon" = callPackage @@ -121158,7 +119509,6 @@ self: { description = "Background process for Haskell-tools that editors can connect to"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-tools-debug" = callPackage @@ -121184,7 +119534,6 @@ self: { description = "Debugging Tools for Haskell-tools"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-tools-demo" = callPackage @@ -121216,7 +119565,6 @@ self: { description = "A web-based demo for Haskell-tools Refactor"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-tools-experimental-refactorings" = callPackage @@ -121248,7 +119596,6 @@ self: { description = "Refactoring Tool for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-tools-prettyprint" = callPackage @@ -121266,7 +119613,6 @@ self: { description = "Pretty printing of Haskell-Tools AST"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-tools-refactor" = callPackage @@ -121297,7 +119643,6 @@ self: { description = "Refactoring Tool for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-tools-rewrite" = callPackage @@ -121320,7 +119665,6 @@ self: { description = "Facilities for generating new parts of the Haskell-Tools AST"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-tor" = callPackage @@ -121355,7 +119699,6 @@ self: { description = "A Haskell Tor Node"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskell-type-exts" = callPackage @@ -121528,7 +119871,6 @@ self: { description = "Bracketed HDBC session for HaskellDB"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskelldb-connect-hdbc-catchio-mtl" = callPackage @@ -121545,7 +119887,6 @@ self: { description = "Bracketed HaskellDB HDBC session using MonadCatchIO-mtl"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskelldb-connect-hdbc-catchio-tf" = callPackage @@ -121563,7 +119904,6 @@ self: { description = "Bracketed HaskellDB HDBC session using MonadCatchIO-transformers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskelldb-connect-hdbc-catchio-transformers" = callPackage @@ -121581,7 +119921,6 @@ self: { description = "Bracketed HaskellDB HDBC session using MonadCatchIO-transformers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskelldb-connect-hdbc-lifted" = callPackage @@ -121599,7 +119938,6 @@ self: { description = "Bracketed HaskellDB HDBC session using lifted-base"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskelldb-dynamic" = callPackage @@ -121615,7 +119953,6 @@ self: { description = "HaskellDB support for the dynamically loaded drivers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskelldb-flat" = callPackage @@ -121634,7 +119971,6 @@ self: { description = "An experimental HaskellDB back-end in pure Haskell (no SQL)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskelldb-hdbc" = callPackage @@ -121651,7 +119987,6 @@ self: { description = "HaskellDB support for HDBC"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskelldb-hdbc-mysql" = callPackage @@ -121670,7 +120005,6 @@ self: { description = "HaskellDB support for the HDBC MySQL driver"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskelldb-hdbc-odbc" = callPackage @@ -121689,7 +120023,6 @@ self: { description = "HaskellDB support for the HDBC ODBC driver"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskelldb-hdbc-postgresql" = callPackage @@ -121709,7 +120042,6 @@ self: { description = "HaskellDB support for the HDBC PostgreSQL driver"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) postgresql;}; "haskelldb-hdbc-sqlite3" = callPackage @@ -121728,7 +120060,6 @@ self: { description = "HaskellDB support for the HDBC SQLite driver"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskelldb-hsql" = callPackage @@ -121741,7 +120072,6 @@ self: { description = "HaskellDB support for HSQL"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskelldb-hsql-mysql" = callPackage @@ -121760,7 +120090,6 @@ self: { description = "HaskellDB support for the HSQL MySQL driver"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskelldb-hsql-odbc" = callPackage @@ -121779,7 +120108,6 @@ self: { description = "HaskellDB support for the HSQL ODBC driver"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskelldb-hsql-oracle" = callPackage @@ -121817,7 +120145,6 @@ self: { description = "HaskellDB support for the HSQL PostgreSQL driver"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskelldb-hsql-sqlite" = callPackage @@ -121855,7 +120182,6 @@ self: { description = "HaskellDB support for the HSQL SQLite3 driver"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskelldb-th" = callPackage @@ -121868,7 +120194,6 @@ self: { description = "Template Haskell utilities for HaskellDB"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskelldb-wx" = callPackage @@ -121896,8 +120221,6 @@ self: { ]; description = "For parsing Haskell-ish languages"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskellscrabble" = callPackage @@ -121975,7 +120298,6 @@ self: { description = "Elm to Haskell translation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskelzinc" = callPackage @@ -122083,7 +120405,6 @@ self: { description = "A monad transformer supporting Haskey transactions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskgame" = callPackage @@ -122096,7 +120417,6 @@ self: { description = "Haskell game library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskheap" = callPackage @@ -122219,7 +120539,6 @@ self: { description = "An adapter for haskoin to network-bitcoin"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskoin-core" = callPackage @@ -122252,7 +120571,6 @@ self: { description = "Bitcoin & Bitcoin Cash library for Haskell"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskoin-crypto" = callPackage @@ -122276,7 +120594,6 @@ self: { description = "Implementation of Bitcoin cryptographic primitives"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskoin-node" = callPackage @@ -122309,7 +120626,6 @@ self: { description = "P2P library for Bitcoin and Bitcoin Cash"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskoin-protocol" = callPackage @@ -122333,7 +120649,6 @@ self: { description = "Implementation of the Bitcoin network protocol messages"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskoin-script" = callPackage @@ -122359,7 +120674,6 @@ self: { description = "Implementation of Bitcoin script parsing and evaluation"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskoin-store" = callPackage @@ -122410,7 +120724,6 @@ self: { description = "Storage and index for Bitcoin and Bitcoin Cash"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskoin-store-data" = callPackage @@ -122440,7 +120753,6 @@ self: { description = "Data for Haskoin Store"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskoin-util" = callPackage @@ -122508,7 +120820,6 @@ self: { description = "Implementation of a Bitcoin SPV Wallet with BIP32 and multisig support"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskoon" = callPackage @@ -122527,7 +120838,6 @@ self: { description = "Web Application Abstraction"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskoon-httpspec" = callPackage @@ -122544,7 +120854,6 @@ self: { description = "Integrating HttpSpec with Haskoon"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskoon-salvia" = callPackage @@ -122563,7 +120872,6 @@ self: { description = "Integrating HttpSpec with Haskoon"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskore" = callPackage @@ -122608,7 +120916,6 @@ self: { description = "Routines for realtime playback of Haskore songs"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskore-supercollider" = callPackage @@ -122631,7 +120938,6 @@ self: { description = "Haskore back-end for SuperCollider"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskore-synthesizer" = callPackage @@ -122652,7 +120958,6 @@ self: { description = "Music rendering coded in Haskell"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskore-vintage" = callPackage @@ -122747,7 +121052,6 @@ self: { description = "Torch for tensors and neural networks in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hasktorch-codegen" = callPackage @@ -122838,7 +121142,6 @@ self: { description = "Bindings to Cutorch"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {ATen = null;}; "hasktorch-indef" = callPackage @@ -122868,7 +121171,6 @@ self: { description = "Core Hasktorch abstractions wrapping FFI bindings"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hasktorch-signatures" = callPackage @@ -122895,7 +121197,6 @@ self: { description = "Backpack signatures for Tensor operations"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hasktorch-signatures-partial" = callPackage @@ -122992,7 +121293,6 @@ self: { description = "Neural architectures in hasktorch"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskus-binary" = callPackage @@ -123038,8 +121338,6 @@ self: { ]; description = "Haskus system build tool"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskus-utils" = callPackage @@ -123062,8 +121360,6 @@ self: { ]; description = "Haskus utility modules"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskus-utils-compat" = callPackage @@ -123081,7 +121377,6 @@ self: { description = "Compatibility modules with other external packages (ByteString, etc.)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskus-utils-data" = callPackage @@ -123099,8 +121394,6 @@ self: { testHaskellDepends = [ base doctest ]; description = "Haskus data utility modules"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskus-utils-types" = callPackage @@ -123113,8 +121406,6 @@ self: { testHaskellDepends = [ base doctest ]; description = "Haskus types utility modules"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskus-utils-variant" = callPackage @@ -123137,8 +121428,6 @@ self: { benchmarkHaskellDepends = [ base criterion deepseq QuickCheck ]; description = "Variant and EADT"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskus-web" = callPackage @@ -123156,7 +121445,6 @@ self: { description = "Haskus web"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haskyapi" = callPackage @@ -123205,7 +121493,6 @@ self: { description = "Loan calculator engine"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hasloGUI" = callPackage @@ -123225,7 +121512,6 @@ self: { description = "Loan calculator Gtk GUI. Based on haslo (Haskell Loan) library."; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hasmin" = callPackage @@ -123270,7 +121556,6 @@ self: { description = "This package enables to write SPARQL queries to remote endpoints"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haspell" = callPackage @@ -123374,7 +121659,6 @@ self: { description = "A declarative abstraction over PostgreSQL Cursor"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hasql-cursor-transaction" = callPackage @@ -123570,7 +121854,6 @@ self: { description = "A \"PostgreSQL\" backend for the \"hasql\" library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hasql-postgres-options" = callPackage @@ -123586,7 +121869,6 @@ self: { description = "An \"optparse-applicative\" parser for \"hasql-postgres\""; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hasql-queue" = callPackage @@ -123622,7 +121904,6 @@ self: { description = "A PostgreSQL backed queue"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hasql-simple" = callPackage @@ -123659,8 +121940,6 @@ self: { ]; description = "Template Haskell utilities for Hasql"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hasql-transaction" = callPackage @@ -123695,8 +121974,6 @@ self: { testHaskellDepends = [ base hasql tasty tasty-quickcheck ]; description = "Parse PostgreSQL connection URI into Hasql.Connection Settings"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hasqly-mysql" = callPackage @@ -123759,7 +122036,6 @@ self: { description = "render hastache templates using aeson values"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haste" = callPackage @@ -123795,7 +122071,6 @@ self: { description = "Framework for type-safe, distributed web applications"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haste-compiler" = callPackage @@ -123859,7 +122134,6 @@ self: { description = "Base libraries for haste-compiler"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haste-markup" = callPackage @@ -123875,7 +122149,6 @@ self: { description = "A port of blaze-markup and blaze-html to Haste"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "haste-perch" = callPackage @@ -124175,7 +122448,6 @@ self: { description = "A twitter client for GTK+. Beta version."; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hax" = callPackage @@ -124347,7 +122619,6 @@ self: { description = "A simple HTTP proxy server library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hayland" = callPackage @@ -124409,7 +122680,6 @@ self: { description = "N-back memory game"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hbayes" = callPackage @@ -124440,7 +122710,6 @@ self: { description = "Bayesian Networks"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hbb" = callPackage @@ -124458,7 +122727,6 @@ self: { description = "Haskell Busy Bee, a backend for text editors"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hbcd" = callPackage @@ -124471,7 +122739,6 @@ self: { description = "Packed binary-coded decimal (BCD) serialization"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hbeanstalk" = callPackage @@ -124546,7 +122813,6 @@ self: { description = "An optimizing Brainfuck compiler and evaluator"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hblas" = callPackage @@ -124734,7 +123000,6 @@ self: { description = "haskell cg (minus) (cairo rendering)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hcheat" = callPackage @@ -124748,7 +123013,6 @@ self: { description = "A collection of code cheatsheet"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hcheckers" = callPackage @@ -124783,7 +123047,6 @@ self: { description = "Implementation of checkers (\"draughts\") board game - server application"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hchesslib" = callPackage @@ -125080,7 +123343,6 @@ self: { description = "Haskell Database Independent interface"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hdbi-conduit" = callPackage @@ -125102,7 +123364,6 @@ self: { description = "Conduit glue for HDBI"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hdbi-postgresql" = callPackage @@ -125131,7 +123392,6 @@ self: { description = "PostgreSQL driver for hdbi"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hdbi-sqlite" = callPackage @@ -125152,7 +123412,6 @@ self: { description = "SQlite driver for HDBI"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hdbi-tests" = callPackage @@ -125173,7 +123432,6 @@ self: { description = "test suite for testing HDBI"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hdevtools" = callPackage @@ -125213,7 +123471,6 @@ self: { description = "HDF: Uniform Rate Audio Signal Processing in Haskell"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hdf5-lite" = callPackage @@ -125267,7 +123524,6 @@ self: { description = "Pattern-Expression-based differencing of arbitrary types"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hdigest" = callPackage @@ -125303,7 +123559,6 @@ self: { description = "An IDL compiler for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hdis86" = callPackage @@ -125400,7 +123655,6 @@ self: { description = "Haskell docs tool"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hdph" = callPackage @@ -125428,7 +123682,6 @@ self: { description = "Haskell distributed parallel Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hdph-closure" = callPackage @@ -125622,7 +123875,6 @@ self: { description = "An opinionated app prelude and framework in the UnliftIO style"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "heart-core" = callPackage @@ -125655,8 +123907,6 @@ self: { libraryHaskellDepends = [ async base io-streams time ]; description = "Heartbeats for io-streams"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "heatitup" = callPackage @@ -125687,7 +123937,6 @@ self: { description = "Find and annotate ITDs"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "heatitup-complete" = callPackage @@ -125711,8 +123960,6 @@ self: { ]; description = "Find and annotate ITDs with assembly or read pair joining"; license = lib.licenses.gpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "heatshrink" = callPackage @@ -125747,7 +123994,6 @@ self: { description = "Simle api for heavy logger"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "heavy-logger" = callPackage @@ -125770,7 +124016,6 @@ self: { description = "Full-weight logging based on fast-logger"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "heavy-logger-amazon" = callPackage @@ -125787,7 +124032,6 @@ self: { description = "heavy-logger compatibility with amazonka-core logging"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "heavy-logger-instances" = callPackage @@ -125809,7 +124053,6 @@ self: { description = "Orphan instances for data types in heavy-logger package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hebrew-time" = callPackage @@ -125837,7 +124080,6 @@ self: { description = "Elliptic Curve Cryptography for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "heckin" = callPackage @@ -125924,7 +124166,6 @@ self: { testHaskellDepends = [ base hedgehog hedgehog-checkers lens ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hedgehog-classes" = callPackage @@ -125968,8 +124209,6 @@ self: { testHaskellDepends = [ base containers fakedata hedgehog ]; description = "Use 'fakedata' with 'hedgehog'"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hedgehog-fn" = callPackage @@ -126023,7 +124262,6 @@ self: { description = "JSON generators for Hedgehog"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hedgehog-generic" = callPackage @@ -126201,7 +124439,6 @@ self: { description = "Caching mandatory data with Redis"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hedis-simple" = callPackage @@ -126272,8 +124509,6 @@ self: { ]; description = "Base functor for EDN AST"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hedra" = callPackage @@ -126319,7 +124554,6 @@ self: { description = "Tidy data in Haskell"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hein" = callPackage @@ -126399,7 +124633,6 @@ self: { description = "Use JSON directly from Heist templates"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "heist-async" = callPackage @@ -126461,7 +124694,6 @@ self: { description = "New Relic® agent SDK wrapper for Haskell"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {newrelic-collector-client = null; newrelic-common = null; newrelic-transaction = null;}; @@ -126481,7 +124713,6 @@ self: { description = "New Relic® agent SDK wrapper for wai"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "helisp" = callPackage @@ -126521,7 +124752,6 @@ self: { description = "The Helium Compiler"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "helium-overture" = callPackage @@ -126609,7 +124839,6 @@ self: { description = "Distributed hackage mirror"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hellnet" = callPackage @@ -126635,7 +124864,6 @@ self: { description = "Simple, distributed, anonymous data sharing network"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hello" = callPackage @@ -126749,7 +124977,6 @@ self: { description = "Haskell port of the Emokit EEG project"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hen" = callPackage @@ -126771,7 +124998,6 @@ self: { description = "Haskell bindings to Xen hypervisor interface"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {xenctrl = null;}; "henet" = callPackage @@ -126787,7 +125013,6 @@ self: { description = "Bindings and high level interface for to ENet v1.3.9"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hepevt" = callPackage @@ -126800,7 +125025,6 @@ self: { description = "HEPEVT parser"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "her-lexer" = callPackage @@ -126826,7 +125050,6 @@ self: { description = "Parsec frontend to \"her-lexer\" for Haskell source code"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "herbalizer" = callPackage @@ -127154,7 +125377,6 @@ self: { description = "Haskell Equational Reasoning Model-to-Implementation Tunnel"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hermit-syb" = callPackage @@ -127171,7 +125393,6 @@ self: { description = "HERMIT plugin for optimizing Scrap-Your-Boilerplate traversals"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "herms" = callPackage @@ -127256,7 +125477,6 @@ self: { description = "A library for compiling and serving static web assets"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "herringbone-embed" = callPackage @@ -127274,7 +125494,6 @@ self: { description = "Embed preprocessed web assets in your executable with Template Haskell"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "herringbone-wai" = callPackage @@ -127292,7 +125511,6 @@ self: { description = "Wai adapter for the Herringbone web asset preprocessor"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hesh" = callPackage @@ -127320,7 +125538,6 @@ self: { description = "the Haskell Extensible Shell: Haskell for Bash-style scripts"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hesql" = callPackage @@ -127339,7 +125556,6 @@ self: { description = "Haskell's embedded SQL"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hetero-dict" = callPackage @@ -127423,7 +125639,6 @@ self: { description = "A heterogeneous list type"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hetris" = callPackage @@ -127524,7 +125739,6 @@ self: { description = "Genetic Mona Lisa problem in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hevolisa-dph" = callPackage @@ -127544,7 +125758,6 @@ self: { description = "Genetic Mona Lisa problem in Haskell - using Data Parallel Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hex" = callPackage @@ -127568,8 +125781,6 @@ self: { testHaskellDepends = [ base bytestring text ]; description = "ByteString-Text hexidecimal conversions"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hexchat" = callPackage @@ -127712,7 +125923,6 @@ self: { description = "Chunked XML parsing using iteratees"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hexpat-lens" = callPackage @@ -127913,8 +126123,6 @@ self: { ]; description = "Streaming-friendly XML parsers"; license = lib.licenses.cc0; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "heyefi" = callPackage @@ -127969,8 +126177,6 @@ self: { ]; description = "Heyting and Boolean algebras"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hfann" = callPackage @@ -128007,7 +126213,6 @@ self: { description = "Flash debugger"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hfiar" = callPackage @@ -128024,7 +126229,6 @@ self: { description = "Four in a Row in Haskell!!"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hflags" = callPackage @@ -128212,7 +126416,6 @@ self: { description = "Haskell Genetic Algorithm Library"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hgdbmi" = callPackage @@ -128268,7 +126471,6 @@ self: { description = "Random generation of modal and hybrid logic formulas"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hgeometric" = callPackage @@ -128405,7 +126607,6 @@ self: { description = "Writing geometric primitives from HGeometry as SVG Files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hgeos" = callPackage @@ -128420,8 +126621,6 @@ self: { testHaskellDepends = [ base MissingH ]; description = "Simple Haskell bindings to GEOS C API"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) geos;}; "hgettext" = callPackage @@ -128492,7 +126691,6 @@ self: { description = "Haskell bindings to the GitHub API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hgl-example" = callPackage @@ -128522,8 +126720,6 @@ self: { testHaskellDepends = [ base QuickCheck ]; description = "Haskell interface to GMP"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hgom" = callPackage @@ -128656,8 +126852,6 @@ self: { ]; description = "Happy Haskell Programming"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hhwloc" = callPackage @@ -128762,7 +126956,6 @@ self: { description = "Relatively efficient Tcl interpreter with support for basic operations"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hichi" = callPackage @@ -129040,6 +127233,8 @@ self: { testToolDepends = [ hspec-discover ]; description = "hierarchical environments for dependency injection"; license = lib.licenses.bsd3; + hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "hierarchical-exceptions" = callPackage @@ -129084,7 +127279,6 @@ self: { description = "Hierarchical spectral clustering of a graph"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hierarchy" = callPackage @@ -129262,7 +127456,6 @@ self: { description = "Derive swagger instances from highjson specs"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "highjson-th" = callPackage @@ -129284,7 +127477,6 @@ self: { description = "Template Haskell helpers for highjson specs"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "highlight" = callPackage @@ -129475,7 +127667,6 @@ self: { description = "multithreaded snmp poller for riemann"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hindent" = callPackage @@ -129510,8 +127701,6 @@ self: { ]; description = "Extensible Haskell pretty printer"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hindley-milner" = callPackage @@ -129557,7 +127746,6 @@ self: { description = "Interface and utilities for classifiers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hinduce-classifier-decisiontree" = callPackage @@ -129576,7 +127764,6 @@ self: { description = "Decision Tree Classifiers for hInduce"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hinduce-examples" = callPackage @@ -129597,7 +127784,6 @@ self: { description = "Example data for hInduce"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hinduce-missingh" = callPackage @@ -129781,7 +127967,6 @@ self: { description = "A server process that runs hint"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hinter" = callPackage @@ -129848,7 +128033,6 @@ self: { description = "Space Invaders"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hinze-streams" = callPackage @@ -129861,7 +128045,6 @@ self: { description = "Streams and Unique Fixed Points"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hip" = callPackage @@ -129886,8 +128069,6 @@ self: { ]; description = "Haskell Image Processing (HIP) Library"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hipbot" = callPackage @@ -129913,7 +128094,6 @@ self: { description = "A library for building HipChat Bots"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hipchat-hs" = callPackage @@ -130001,7 +128181,6 @@ self: { ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hipsql-monad" = callPackage @@ -130034,7 +128213,6 @@ self: { ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hircules" = callPackage @@ -130076,7 +128254,6 @@ self: { description = "Calculates IRT 2PL and 3PL models"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hissmetrics" = callPackage @@ -130118,7 +128295,6 @@ self: { description = "Umbrella package for the historical dictionary of Polish"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hist-pl-dawg" = callPackage @@ -130134,7 +128310,6 @@ self: { description = "A generic, DAWG-based dictionary"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hist-pl-fusion" = callPackage @@ -130152,7 +128327,6 @@ self: { description = "Merging historical dictionary with PoliMorf"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hist-pl-lexicon" = callPackage @@ -130170,7 +128344,6 @@ self: { description = "A binary representation of the historical dictionary of Polish"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hist-pl-lmf" = callPackage @@ -130183,7 +128356,6 @@ self: { description = "LMF parsing for the historical dictionary of Polish"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hist-pl-transliter" = callPackage @@ -130293,7 +128465,6 @@ self: { description = "Git like program in haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hit-graph" = callPackage @@ -130310,7 +128481,6 @@ self: { description = "Use graph algorithms to access and manipulate Git repos"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hit-on" = callPackage @@ -130484,7 +128654,6 @@ self: { description = "JSON Schema library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hjugement" = callPackage @@ -130535,7 +128704,6 @@ self: { description = "Majority Judgment and Helios-C command line tool"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hjugement-protocol" = callPackage @@ -130744,7 +128912,6 @@ self: { description = "Fast algorithm for mining closed frequent itemsets"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hleap" = callPackage @@ -130836,7 +129003,6 @@ self: { description = "Web API server for the hledger accounting tool"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hledger-chart" = callPackage @@ -131361,8 +129527,6 @@ self: { ]; description = "High-level Redis Database"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hlrdb-core" = callPackage @@ -131381,8 +129545,6 @@ self: { ]; description = "High-level Redis Database Core API"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hls" = callPackage @@ -131396,7 +129558,6 @@ self: { description = "Haskell Lindenmayer Systems"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hls-brittany-plugin" = callPackage @@ -131700,7 +129861,6 @@ self: { description = "Haskell LilyPond"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hmark" = callPackage @@ -131720,7 +129880,6 @@ self: { description = "A tool and library for Markov chains based text generation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hmarkup" = callPackage @@ -132001,7 +130160,6 @@ self: { description = "hmatrix interface to sundials"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {sundials_arkode = null; sundials_cvode = null;}; "hmatrix-svdlibc" = callPackage @@ -132087,7 +130245,6 @@ self: { description = "Haskell Meapsoft Parser"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hmeap-utils" = callPackage @@ -132108,7 +130265,6 @@ self: { description = "Haskell Meapsoft Parser Utilities"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hmemdb" = callPackage @@ -132159,7 +130315,6 @@ self: { description = "HMEP Multi Expression Programming – a genetic programming variant"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hmidi" = callPackage @@ -132252,7 +130407,6 @@ self: { description = "Hidden Markov Models using LAPACK primitives"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hmp3" = callPackage @@ -132329,7 +130483,6 @@ self: { description = "Haskell Music Theory"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hmt-diagrams" = callPackage @@ -132348,7 +130501,6 @@ self: { description = "Haskell Music Theory Diagrams"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hmumps" = callPackage @@ -132594,7 +130746,6 @@ self: { description = "Log message normalisation tool producing structured JSON messages"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ho-rewriting" = callPackage @@ -132679,7 +130830,6 @@ self: { description = "A source code editor aiming for the convenience of use"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hobbes" = callPackage @@ -132716,8 +130866,6 @@ self: { ]; description = "A library for canonically representing terms with binding"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hocilib" = callPackage @@ -132915,8 +131063,6 @@ self: { ]; description = "Bindings to the Toggl.com REST API"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hogre" = callPackage @@ -132933,7 +131079,6 @@ self: { description = "Haskell binding to a subset of OGRE"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {OGRE = null; OgreMain = null; cgen-hs = null; grgen = null;}; "hogre-examples" = callPackage @@ -132950,7 +131095,6 @@ self: { description = "Examples for using Hogre"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {OgreMain = null;}; "hois" = callPackage @@ -133111,7 +131255,6 @@ self: { description = "Start your Haskell project with cabal, git and tests"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "homeomorphic" = callPackage @@ -133139,7 +131282,6 @@ self: { description = "Haskell Offline Music Manipulation And Generation EDSL"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hommage-ds" = callPackage @@ -133288,7 +131430,6 @@ self: { description = "Debugging by observing in place"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hood-off" = callPackage @@ -133333,7 +131474,6 @@ self: { description = "A small, toy roguelike"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hoodle" = callPackage @@ -133355,7 +131495,6 @@ self: { description = "Executable for hoodle"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hoodle-builder" = callPackage @@ -133373,7 +131512,6 @@ self: { description = "text builder for hoodle file format"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hoodle-core" = callPackage @@ -133407,7 +131545,6 @@ self: { description = "Core library for hoodle"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs.xorg) libX11; inherit (pkgs.xorg) libXi;}; "hoodle-extra" = callPackage @@ -133434,7 +131571,6 @@ self: { description = "extra hoodle tools"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hoodle-parser" = callPackage @@ -133453,7 +131589,6 @@ self: { description = "Hoodle file parser"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hoodle-publish" = callPackage @@ -133481,7 +131616,6 @@ self: { description = "publish hoodle files as a static web site"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hoodle-render" = callPackage @@ -133503,7 +131637,6 @@ self: { description = "Hoodle file renderer"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hoodle-types" = callPackage @@ -133672,7 +131805,6 @@ self: { description = "Haskell Media Server"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hopencc" = callPackage @@ -133941,7 +132073,6 @@ self: { description = "A language based on homotopy type theory with an interval type"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hora" = callPackage @@ -134274,7 +132405,6 @@ self: { description = "Real-time heap graphing utility and profile stream server with a reusable graphing module"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) freeglut; inherit (pkgs) libGL; inherit (pkgs) libGLU;}; @@ -134297,7 +132427,6 @@ self: { description = "A utility to visualise and compare heap profiles"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hp2html" = callPackage @@ -134431,8 +132560,6 @@ self: { ]; description = "hpack's dhalling"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hpaco" = callPackage @@ -134451,7 +132578,6 @@ self: { description = "Modular template compiler"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hpaco-lib" = callPackage @@ -134470,7 +132596,6 @@ self: { description = "Modular template compiler library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hpage" = callPackage @@ -134493,7 +132618,6 @@ self: { description = "A scrapbook for Haskell developers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hpapi" = callPackage @@ -134506,6 +132630,9 @@ self: { librarySystemDepends = [ papi ]; description = "Binding for the PAPI library"; license = lib.licenses.bsd3; + platforms = [ + "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" + ]; hydraPlatforms = lib.platforms.none; broken = true; }) {inherit (pkgs) papi;}; @@ -134536,7 +132663,6 @@ self: { description = "Haskell paste web site"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hpasteit" = callPackage @@ -134773,7 +132899,6 @@ self: { description = "Tracer with AJAX interface"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hpdft" = callPackage @@ -134974,7 +133099,6 @@ self: { description = "Extra utilities for hpqtypes library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hprotoc" = callPackage @@ -135035,7 +133159,6 @@ self: { description = "Parse Google Protocol Buffer specifications"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hprox" = callPackage @@ -135071,7 +133194,6 @@ self: { description = "Haskell Postscript"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hps-cairo" = callPackage @@ -135088,7 +133210,6 @@ self: { description = "Cairo rendering for the haskell postscript library"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hps-kmeans" = callPackage @@ -135196,7 +133317,6 @@ self: { description = "Python language tools"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hquantlib" = callPackage @@ -135227,7 +133347,6 @@ self: { description = "HQuantLib is a port of essencial parts of QuantLib to Haskell"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hquantlib-time" = callPackage @@ -135272,7 +133391,6 @@ self: { description = "Basic utility for ranking a list of items"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hreader" = callPackage @@ -135293,7 +133411,6 @@ self: { description = "Generalization of MonadReader and ReaderT using hset"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hreader-lens" = callPackage @@ -135310,7 +133427,6 @@ self: { description = "Optics for hreader package"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hreq-client" = callPackage @@ -135340,7 +133456,6 @@ self: { description = "A Type dependent Highlevel HTTP client library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hreq-conduit" = callPackage @@ -135366,7 +133481,6 @@ self: { description = "Conduit streaming support for Hreq"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hreq-core" = callPackage @@ -135441,8 +133555,6 @@ self: { ]; description = "A Riemann Client for Haskell"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hruby" = callPackage @@ -135528,7 +133640,6 @@ self: { description = "A cryptohash-inspired library for blake2"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) libb2;}; "hs-brotli" = callPackage @@ -135548,7 +133659,6 @@ self: { description = "Compression and decompression in the brotli format"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {brotlidec = null; brotlienc = null;}; "hs-captcha" = callPackage @@ -135628,8 +133738,6 @@ self: { ]; description = "Conllu validating parser and utils"; license = lib.licenses.lgpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hs-di" = callPackage @@ -135726,7 +133834,6 @@ self: { description = "Bindings to FFMPEG library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hs-fltk" = callPackage @@ -135784,7 +133891,6 @@ self: { description = "Utility to generate haskell-names interface files"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hs-gizapp" = callPackage @@ -135814,8 +133920,6 @@ self: { testHaskellDepends = [ base haskell-src hspec ]; description = "Haskell source code analyzer"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hs-ix" = callPackage @@ -136060,7 +134164,6 @@ self: { description = "A library for Passbook pass creation & signing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hs-popen" = callPackage @@ -136226,6 +134329,7 @@ self: { testHaskellDepends = [ base hashtables swisstable ]; description = "Data.HashTable.Class instance definition for Data.HashTable.ST.Swiss"; license = lib.licenses.bsd3; + hydraPlatforms = lib.platforms.none; }) {}; "hs-tags" = callPackage @@ -136606,7 +134710,6 @@ self: { description = "Haskell bindings for PyAutoGUI, a library for automating user interaction"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsay" = callPackage @@ -136659,7 +134762,6 @@ self: { description = "simple utility for rolling filesystem backups"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsbc" = callPackage @@ -136718,7 +134820,6 @@ self: { description = "Backend for uploading benchmark data to CodeSpeed"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsbencher-fusion" = callPackage @@ -136743,7 +134844,6 @@ self: { description = "Backend for uploading benchmark data to Google Fusion Tables"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsc2hs" = callPackage @@ -136802,7 +134902,6 @@ self: { description = "Haskell SuperCollider Auditor"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsc3-cairo" = callPackage @@ -136816,7 +134915,6 @@ self: { description = "haskell supercollider cairo drawing"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsc3-data" = callPackage @@ -136835,7 +134933,6 @@ self: { description = "haskell supercollider data"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsc3-db" = callPackage @@ -136849,7 +134946,6 @@ self: { description = "Haskell SuperCollider Unit Generator Database"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsc3-dot" = callPackage @@ -136863,7 +134959,6 @@ self: { description = "haskell supercollider graph drawing"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsc3-forth" = callPackage @@ -136884,7 +134979,6 @@ self: { description = "FORTH SUPERCOLLIDER"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsc3-graphs" = callPackage @@ -136910,7 +135004,6 @@ self: { description = "Haskell SuperCollider Graphs"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsc3-lang" = callPackage @@ -136932,7 +135025,6 @@ self: { description = "Haskell SuperCollider Language"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsc3-lisp" = callPackage @@ -136953,7 +135045,6 @@ self: { description = "LISP SUPERCOLLIDER"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsc3-plot" = callPackage @@ -136972,7 +135063,6 @@ self: { description = "Haskell SuperCollider Plotting"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsc3-process" = callPackage @@ -136993,7 +135083,6 @@ self: { description = "Create and control scsynth processes"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsc3-rec" = callPackage @@ -137007,7 +135096,6 @@ self: { description = "Haskell SuperCollider Record Variants"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsc3-rw" = callPackage @@ -137054,7 +135142,6 @@ self: { description = "SuperCollider server resource management and synchronization"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsc3-sf" = callPackage @@ -137086,7 +135173,6 @@ self: { description = "Haskell SuperCollider SoundFile"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsc3-unsafe" = callPackage @@ -137100,7 +135186,6 @@ self: { description = "Unsafe Haskell SuperCollider"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsc3-utils" = callPackage @@ -137123,7 +135208,6 @@ self: { description = "Haskell SuperCollider Utilities"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hscaffold" = callPackage @@ -137185,7 +135269,6 @@ self: { description = "cassandra database interface"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hscd" = callPackage @@ -137350,7 +135433,6 @@ self: { description = "cscope like browser for Haskell code"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hscrtmpl" = callPackage @@ -137461,7 +135543,6 @@ self: { description = "Haskell development library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsdif" = callPackage @@ -137597,8 +135678,6 @@ self: { ]; description = "sendxmpp clone, sending XMPP messages via CLI"; license = lib.licenses.agpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsenv" = callPackage @@ -137647,7 +135726,6 @@ self: { description = "Primitive list with elements of unique types"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsexif" = callPackage @@ -137678,7 +135756,6 @@ self: { description = "A small and ugly library that emulates the output of the puppet facter program"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsfcsh" = callPackage @@ -137911,8 +135988,6 @@ self: { ]; description = "Inspect Haskell source files"; license = lib.licenses.gpl3Plus; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsinspect-lsp" = callPackage @@ -138119,7 +136194,6 @@ self: { description = "A library to work with, or as, a logstash server"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hslua" = callPackage @@ -138399,7 +136473,6 @@ self: { description = "Nock 5K interpreter"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsnoise" = callPackage @@ -138768,8 +136841,6 @@ self: { testHaskellDepends = [ aeson-qq base hspec ]; description = "Hspec expectations for JSON Values"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hspec-expectations-lens" = callPackage @@ -138831,7 +136902,6 @@ self: { description = "hspec-expectations with pretty printing on failure"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hspec-expectations-pretty-diff" = callPackage @@ -138938,8 +137008,6 @@ self: { ]; description = "Initial project template from stack"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hspec-hedgehog" = callPackage @@ -139133,7 +137201,6 @@ self: { description = "Helpers for creating database tests with hspec and pg-transact"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hspec-server" = callPackage @@ -139182,7 +137249,6 @@ self: { description = "Add an hspec test-suite in one command"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hspec-shouldbe" = callPackage @@ -139195,7 +137261,6 @@ self: { description = "Convenience wrapper and utilities for hspec"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hspec-slow" = callPackage @@ -139337,7 +137402,6 @@ self: { description = "Hspec convenience functions for use with test-sandbox"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hspec-wai" = callPackage @@ -139448,7 +137512,6 @@ self: { description = "Spec for testing properties for variant types"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hspkcs11" = callPackage @@ -139539,7 +137602,6 @@ self: { description = "The Haskell Stream Processor command line utility"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsql" = callPackage @@ -139568,7 +137630,6 @@ self: { description = "MySQL driver for HSQL"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {mysqlclient = null;}; "hsql-odbc" = callPackage @@ -139582,7 +137643,6 @@ self: { description = "A Haskell Interface to ODBC"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) unixODBC;}; "hsql-postgresql" = callPackage @@ -139596,7 +137656,6 @@ self: { description = "A Haskell Interface to PostgreSQL via the PQ library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) postgresql;}; "hsql-sqlite3" = callPackage @@ -139610,7 +137669,6 @@ self: { description = "SQLite3 driver for HSQL"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) sqlite;}; "hsqml" = callPackage @@ -139775,7 +137833,6 @@ self: { description = "Access to the Readability API"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsrelp" = callPackage @@ -139899,7 +137956,6 @@ self: { description = "hssqlppp extras which need template-haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hstar" = callPackage @@ -139923,7 +137979,6 @@ self: { description = "Haskell version of tar CLI utility"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hstatistics" = callPackage @@ -140056,7 +138111,6 @@ self: { description = "A Tox protocol implementation in Haskell"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hstradeking" = callPackage @@ -140082,7 +138136,6 @@ self: { description = "Tradeking API bindings for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hstyle" = callPackage @@ -140123,7 +138176,6 @@ self: { description = "A two player abstract strategy game"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsubconvert" = callPackage @@ -140146,7 +138198,6 @@ self: { description = "One-time, faithful conversion of Subversion repositories to Git"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsudoku" = callPackage @@ -140209,7 +138260,6 @@ self: { description = "embedding prolog in haskell"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) ncurses; inherit (pkgs) readline; swipl = null;}; @@ -140242,7 +138292,6 @@ self: { description = "hsp+jmacro support"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsx-xhtml" = callPackage @@ -140255,7 +138304,6 @@ self: { description = "XHTML utilities to use together with HSX"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hsx2hs" = callPackage @@ -140388,8 +138436,6 @@ self: { ]; description = "A Haskell98 parsing tags program similar to ctags"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "htar" = callPackage @@ -140895,7 +138941,6 @@ self: { description = "Haskell Music Typesetting"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "htsn" = callPackage @@ -141131,7 +139176,6 @@ self: { description = "HTTP authorization (both basic and digest) done right"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "http-client-conduit" = callPackage @@ -141583,7 +139627,6 @@ self: { description = "HTTP client package with enumerator interface and HTTPS support. (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "http-grammar" = callPackage @@ -141619,7 +139662,6 @@ self: { description = "HTTP and WebSocket client based on io-streams"; license = "BSD-3-Clause AND GPL-2.0-or-later"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "http-kinder" = callPackage @@ -141973,8 +140015,6 @@ self: { ]; description = "RFC7807 style response messages"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "http-server" = callPackage @@ -142181,7 +140221,6 @@ self: { description = "A command-line http2 client"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "http2-client-grpc" = callPackage @@ -142202,7 +140241,6 @@ self: { description = "Implement gRPC-over-HTTP2 clients"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "http2-grpc-proto-lens" = callPackage @@ -142239,8 +140277,6 @@ self: { ]; description = "Encoders based on `proto3-wire` for gRPC over HTTP2"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "http2-grpc-types" = callPackage @@ -142292,7 +140328,6 @@ self: { description = "High-level access to HTTPS Everywhere rulesets"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "https-everywhere-rules-raw" = callPackage @@ -142308,7 +140343,6 @@ self: { description = "Low-level (i.e. XML) access to HTTPS Everywhere rulesets."; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "httpspec" = callPackage @@ -142327,7 +140361,6 @@ self: { description = "Specification of HTTP request/response generators and parsers"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "htune" = callPackage @@ -142527,7 +140560,6 @@ self: { description = "Hugs Front-end to Yhc Core"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hulk" = callPackage @@ -142555,7 +140587,6 @@ self: { description = "IRC server written in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hum" = callPackage @@ -142718,7 +140749,6 @@ self: { description = "A GUI testrunner for HUnit"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hunit-parsec" = callPackage @@ -142763,7 +140793,6 @@ self: { description = "Unpacker tool with DWIM"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hunspell-hs" = callPackage @@ -142814,7 +140843,6 @@ self: { description = "A search and indexing engine"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hunt-server" = callPackage @@ -142839,7 +140867,6 @@ self: { description = "A search and indexing engine server"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hunt-server-cli" = callPackage @@ -142911,7 +140938,6 @@ self: { description = "Extract function names from Windows DLLs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hurl" = callPackage @@ -142936,8 +140962,6 @@ self: { executableHaskellDepends = [ base directory network-uri ]; description = "Haskell URL resolver"; license = lib.licenses.gpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hurriyet" = callPackage @@ -142982,8 +141006,6 @@ self: { ]; description = "R5RS Scheme interpreter, compiler, and library"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "husk-scheme-libs" = callPackage @@ -142999,8 +141021,6 @@ self: { ]; description = "Extra libraries for the husk Scheme platform"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "husky" = callPackage @@ -143019,7 +141039,6 @@ self: { description = "A simple command line calculator"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hutton" = callPackage @@ -143069,7 +141088,6 @@ self: { description = "Fuzzy logic library with support for T1, IT2, GT2"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hvect" = callPackage @@ -143159,7 +141177,6 @@ self: { description = "Demo library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hw-aws-sqs-conduit" = callPackage @@ -143176,8 +141193,6 @@ self: { testHaskellDepends = [ base ]; description = "AWS SQS conduit"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hw-balancedparens" = callPackage @@ -143365,7 +141380,6 @@ self: { description = "Unbelievably fast streaming DSV file parser"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hw-dump" = callPackage @@ -143642,7 +141656,6 @@ self: { description = "Memory efficient JSON parser"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hw-json-lens" = callPackage @@ -143673,7 +141686,6 @@ self: { description = "Lens for hw-json"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hw-json-simd" = callPackage @@ -143740,7 +141752,6 @@ self: { description = "Memory efficient JSON parser"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hw-json-standard-cursor" = callPackage @@ -143781,7 +141792,6 @@ self: { description = "Memory efficient JSON parser"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hw-kafka-avro" = callPackage @@ -143809,7 +141819,6 @@ self: { description = "Avro support for Kafka infrastructure"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hw-kafka-client" = callPackage @@ -144002,8 +142011,6 @@ self: { benchmarkHaskellDepends = [ base criterion vector ]; description = "Primitive support for bit manipulation"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hw-rankselect" = callPackage @@ -144136,7 +142143,6 @@ self: { description = "SIMD library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hw-streams" = callPackage @@ -144253,7 +142259,6 @@ self: { description = "Supports IO on URIs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hw-vector" = callPackage @@ -144435,7 +142440,6 @@ self: { description = "Library for sending email with Amazon's SES and hworker"; license = lib.licenses.isc; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hwormhole" = callPackage @@ -144469,7 +142473,6 @@ self: { description = "magic-wormhole client"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hws" = callPackage @@ -144489,7 +142492,6 @@ self: { description = "Simple Haskell Web Server"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hwsl2" = callPackage @@ -144523,7 +142525,6 @@ self: { description = "A hashed byte-vector based on algebraic hashes and finger trees"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hwsl2-reducers" = callPackage @@ -144538,7 +142539,6 @@ self: { description = "Semigroup and Reducer instances for Data.Hash.SL2"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hx" = callPackage @@ -144571,7 +142571,6 @@ self: { description = "Haskell XMPP (Jabber Client) Command Line Interface (CLI)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hxournal" = callPackage @@ -144599,7 +142598,6 @@ self: { description = "A pen notetaking program written in haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hxt" = callPackage @@ -144651,6 +142649,7 @@ self: { description = "Cache for HXT XML Documents and other binary data"; license = "unknown"; hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "hxt-charproperties" = callPackage @@ -144862,7 +142861,6 @@ self: { description = "Helper functions for HXT"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hxweb" = callPackage @@ -144875,7 +142873,6 @@ self: { description = "Minimal webframework using fastcgi, libxml2 and libxslt"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hyahtzee" = callPackage @@ -144929,7 +142926,6 @@ self: { description = "A implementation of a type-checker for Lambda-H"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hybrid-vectors" = callPackage @@ -145032,7 +143028,6 @@ self: { description = "Hydrogen Data"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hydrogen-cli-args" = callPackage @@ -145049,7 +143044,6 @@ self: { description = "Hydrogen Command Line Arguments Parser"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hydrogen-data" = callPackage @@ -145062,7 +143056,6 @@ self: { description = "Hydrogen Data"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hydrogen-multimap" = callPackage @@ -145090,7 +143083,6 @@ self: { description = "Hydrogen Parsing Utilities"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hydrogen-prelude" = callPackage @@ -145111,7 +143103,6 @@ self: { description = "Hydrogen Prelude"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hydrogen-prelude-parsec" = callPackage @@ -145124,7 +143115,6 @@ self: { description = "Hydrogen Prelude /w Parsec"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hydrogen-syntax" = callPackage @@ -145142,7 +143132,6 @@ self: { description = "Hydrogen Syntax"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hydrogen-util" = callPackage @@ -145158,7 +143147,6 @@ self: { description = "Hydrogen Tools"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hydrogen-version" = callPackage @@ -145188,7 +143176,6 @@ self: { description = "Simple web application server"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hylide" = callPackage @@ -145255,7 +143242,6 @@ self: { description = "Tableau based theorem prover for hybrid logics"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hyloutils" = callPackage @@ -145272,7 +143258,6 @@ self: { description = "Very small programs for hybrid logics"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hyper" = callPackage @@ -145436,7 +143421,6 @@ self: { description = "A thin wrapper for the Hyperpublic API"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "hyphenate" = callPackage @@ -145601,8 +143585,6 @@ self: { testSystemDepends = [ zookeeper_mt ]; description = "Haskell client library for Apache Zookeeper"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) zookeeper_mt;}; "hzulip" = callPackage @@ -145827,7 +143809,6 @@ self: { description = "Lattice iCE40 Primitive IP"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "icepeak" = callPackage @@ -145973,7 +143954,6 @@ self: { description = "An IDE backend library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ide-backend-common" = callPackage @@ -145999,7 +143979,6 @@ self: { description = "Shared library used be ide-backend and ide-backend-server"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ide-backend-rts" = callPackage @@ -146035,7 +144014,6 @@ self: { description = "An IDE backend server"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ideas" = callPackage @@ -146075,7 +144053,6 @@ self: { description = "Interactive domain reasoner for logic and mathematics"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ideas-math-types" = callPackage @@ -146090,7 +144067,6 @@ self: { description = "Common types for mathematical domain reasoners"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ideas-statistics" = callPackage @@ -146107,7 +144083,6 @@ self: { description = "Interactive domain reasoner for statistics"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "idempotent" = callPackage @@ -146500,7 +144475,6 @@ self: { description = "Bindings for the Gtk/OS X integration library"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {ige-mac-integration = null;}; "ignore" = callPackage @@ -146806,7 +144780,6 @@ self: { description = "a rDisp quasiquote to show plots from Rlang-QQ in IHaskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ihaskell-widgets" = callPackage @@ -146858,7 +144831,6 @@ self: { description = "Incremental HTTP iteratee"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ilist" = callPackage @@ -147015,7 +144987,6 @@ self: { description = "An efficient IMAP client library, with SSL and streaming"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "imapget" = callPackage @@ -147057,7 +145028,6 @@ self: { description = "Minimalistic reference manager"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "imgur" = callPackage @@ -147096,7 +145066,6 @@ self: { description = "Uploader for Imgur"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "imj-animation" = callPackage @@ -147110,7 +145079,6 @@ self: { description = "Animation Framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "imj-base" = callPackage @@ -147136,7 +145104,6 @@ self: { description = "Game engine with geometry, easing, animated text, delta rendering"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "imj-game-hamazed" = callPackage @@ -147158,7 +145125,6 @@ self: { description = "A game with flying numbers and 8-bit color animations"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "imj-measure-stdout" = callPackage @@ -147175,7 +145141,6 @@ self: { description = "An application to determine the maximum capacity of stdout buffer"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "imj-prelude" = callPackage @@ -147228,7 +145193,6 @@ self: { description = "Execute arbitrary actions for each item from RSS/Atom feeds"; license = lib.licenses.cc0; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "immortal_0_2_2_1" = callPackage @@ -147316,7 +145280,6 @@ self: { description = "Multi-platform parser analyzer and generator"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "imperative-edsl" = callPackage @@ -147361,7 +145324,6 @@ self: { description = "Deep embedding of VHDL programs with code generation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "impl" = callPackage @@ -147513,7 +145475,6 @@ self: { description = "Tool for haskell imports refactoring"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "imports" = callPackage @@ -147612,7 +145573,6 @@ self: { description = "An imperative, verifiable programming language for high assurance applications"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "impure-containers" = callPackage @@ -147722,7 +145682,6 @@ self: { description = "A type-checker for Haskell with integer constraints"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "inchworm" = callPackage @@ -147791,7 +145750,6 @@ self: { description = "Incremental computing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "incremental-maps" = callPackage @@ -147816,7 +145774,6 @@ self: { description = "Package for doing incremental computations on maps"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "incremental-parser" = callPackage @@ -147871,7 +145828,6 @@ self: { description = "type classes for incremental updates to data"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "indent" = callPackage @@ -147903,7 +145859,6 @@ self: { description = "Indentation sensitive parsing combinators for Parsec and Trifecta"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "indentation-core" = callPackage @@ -147932,7 +145887,6 @@ self: { description = "Indentation sensitive parsing combinators for Parsec"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "indentation-trifecta" = callPackage @@ -147950,7 +145904,6 @@ self: { description = "Indentation sensitive parsing combinators for Trifecta"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "indentparser" = callPackage @@ -147978,8 +145931,6 @@ self: { testHaskellDepends = [ base mtl parsec tasty tasty-hunit ]; description = "indentation sensitive parser-combinators for parsec"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "index-core" = callPackage @@ -148015,7 +145966,6 @@ self: { description = "Tools for entity indexation"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "indexed" = callPackage @@ -148204,7 +146154,6 @@ self: { description = "A collection of implementations of IndieWeb algorithms"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "indigo" = callPackage @@ -148313,8 +146262,6 @@ self: { ]; description = "The Infernal Machine - An AWS Lambda Custom Runtime for Haskell"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "infernu" = callPackage @@ -148336,7 +146283,6 @@ self: { description = "Type inference and checker for JavaScript (experimental)"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "infinite-search" = callPackage @@ -148615,8 +146561,6 @@ self: { ]; description = "Inline some Assembly in ur Haskell!"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "inline-c" = callPackage @@ -148703,7 +146647,6 @@ self: { description = "Java interop via inline Java code in Haskell modules"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "inline-r" = callPackage @@ -148882,7 +146825,6 @@ self: { description = "Create benchmarks from the HAR files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "instana-haskell-trace-sdk" = callPackage @@ -148967,7 +146909,6 @@ self: { description = "Generic Aeson instances through instant-generics"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "instant-bytes" = callPackage @@ -148985,7 +146926,6 @@ self: { description = "Generic Serial instances through instant-generics"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "instant-deepseq" = callPackage @@ -148998,7 +146938,6 @@ self: { description = "Generic NFData instances through instant-generics"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "instant-generics" = callPackage @@ -149026,7 +146965,6 @@ self: { description = "Generic Hashable instances through instant-generics"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "instant-zipper" = callPackage @@ -149041,7 +146979,6 @@ self: { description = "Heterogenous Zipper in Instant Generics"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "instapaper-sender" = callPackage @@ -149062,7 +146999,6 @@ self: { description = "Basic HTTP gateway to save articles to Instapaper"; license = lib.licenses.agpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "instinct" = callPackage @@ -149609,7 +147545,6 @@ self: { description = "QuasiQuoter for Ruby-style multi-line interpolated strings"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "interpolatedstring-qq-mwotton" = callPackage @@ -149626,7 +147561,6 @@ self: { description = "DO NOT USE THIS. interpolatedstring-qq works now."; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "interpolatedstring-qq2" = callPackage @@ -149917,7 +147851,6 @@ self: { description = "A prelude for the tests of safe new projects"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "intset" = callPackage @@ -149930,7 +147863,6 @@ self: { description = "Pure, mergeable, succinct Int sets"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "intset-imperative" = callPackage @@ -150071,7 +148003,6 @@ self: { description = "invertible functions and instances for HList"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "invertible-hxt" = callPackage @@ -150354,7 +148285,6 @@ self: { description = "EDSL for concurrent, realtime, embedded programming on top of Ivory"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ioref-stable" = callPackage @@ -150436,7 +148366,6 @@ self: { description = "Library for IP and MAC addresses"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ip-quoter" = callPackage @@ -150527,7 +148456,6 @@ self: { description = "interactive patch editor"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ipc" = callPackage @@ -150544,7 +148472,6 @@ self: { description = "High level inter-process communication library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ipcvar" = callPackage @@ -150604,8 +148531,6 @@ self: { ]; description = "Auto-generated IPFS HTTP API"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ipld-cid" = callPackage @@ -150628,7 +148553,6 @@ self: { description = "IPLD Content-IDentifiers "; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ipopt-hs" = callPackage @@ -150664,7 +148588,6 @@ self: { description = "Tiny helper for pretty-printing values in ghci console"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "iproute" = callPackage @@ -150729,7 +148652,6 @@ self: { description = "web-interface for iptables"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ipynb" = callPackage @@ -150928,7 +148850,6 @@ self: { description = "Library for writing fun IRC bots"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "irc-fun-client" = callPackage @@ -150948,7 +148869,6 @@ self: { description = "Another library for writing IRC clients"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "irc-fun-color" = callPackage @@ -150966,7 +148886,6 @@ self: { description = "Add color and style decorations to IRC messages"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "irc-fun-messages" = callPackage @@ -150981,7 +148900,6 @@ self: { description = "Types and functions for working with the IRC protocol"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "irc-fun-types" = callPackage @@ -151064,7 +148982,6 @@ self: { description = "RFC-based resource identifier library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "iridium" = callPackage @@ -151130,7 +149047,6 @@ self: { description = "A technical demo for Antisplice"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "irt" = callPackage @@ -151201,7 +149117,6 @@ self: { description = "Check whether a value has been evaluated"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "isiz" = callPackage @@ -151243,7 +149158,6 @@ self: { description = "Advanced ESMTP library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "iso-deriving" = callPackage @@ -151381,7 +149295,6 @@ self: { description = "A (bytestring-) builder for the ISO-14496-12 base media file format"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "isohunt" = callPackage @@ -151399,7 +149312,6 @@ self: { description = "Bindings to the isoHunt torrent search API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "isotope" = callPackage @@ -151532,7 +149444,6 @@ self: { description = "iteratees for statistical processing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "iterIO" = callPackage @@ -151611,7 +149522,6 @@ self: { description = "Enumeratees for compressing and decompressing streams"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) bzip2; inherit (pkgs) zlib;}; "iteratee-mtl" = callPackage @@ -151630,7 +149540,6 @@ self: { description = "Iteratee-based I/O"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "iteratee-parsec" = callPackage @@ -151647,7 +149556,6 @@ self: { description = "Package allowing parsec parser initeratee"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "iteratee-stm" = callPackage @@ -151662,7 +149570,6 @@ self: { description = "Concurrent iteratees using STM"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "iterio-server" = callPackage @@ -151680,7 +149587,6 @@ self: { description = "Library for building servers with IterIO"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "iterm-show" = callPackage @@ -151697,8 +149603,6 @@ self: { executableHaskellDepends = [ base bytestring ]; description = "Enable graphical display of images inline on some terminals"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "iterm-show-JuicyPixels" = callPackage @@ -151712,8 +149616,6 @@ self: { libraryHaskellDepends = [ base iterm-show JuicyPixels ]; description = "Orphan Show instances for JuciyPixels image types"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "iterm-show-diagrams" = callPackage @@ -151732,7 +149634,6 @@ self: { description = "Orphan Show instances for diagrams package that render inline in some terminals"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ival" = callPackage @@ -151779,7 +149680,6 @@ self: { description = "Theorem proving library based on dependent type theory"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ivory" = callPackage @@ -151829,7 +149729,6 @@ self: { description = "Ivory register bindings for the Atmega328p"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ivory-backend-c" = callPackage @@ -151851,7 +149750,6 @@ self: { description = "Ivory C backend"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ivory-bitdata" = callPackage @@ -151871,7 +149769,6 @@ self: { description = "Ivory bit-data support"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ivory-eval" = callPackage @@ -151891,7 +149788,6 @@ self: { description = "Simple concrete evaluator for Ivory programs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ivory-examples" = callPackage @@ -151915,7 +149811,6 @@ self: { description = "Ivory examples"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ivory-hw" = callPackage @@ -151929,7 +149824,6 @@ self: { description = "Ivory hardware model (STM32F4)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ivory-opts" = callPackage @@ -151947,7 +149841,6 @@ self: { description = "Ivory compiler optimizations"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ivory-quickcheck" = callPackage @@ -151970,7 +149863,6 @@ self: { description = "QuickCheck driver for Ivory"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ivory-serialize" = callPackage @@ -151988,7 +149880,6 @@ self: { description = "Serialization library for Ivory"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ivory-stdlib" = callPackage @@ -152002,7 +149893,6 @@ self: { description = "Ivory standard library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ivy-web" = callPackage @@ -152019,7 +149909,6 @@ self: { description = "A lightweight web framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "iwlib" = callPackage @@ -152208,7 +150097,6 @@ self: { description = "CLI (command line interface) to YQL"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "j" = callPackage @@ -152246,7 +150134,6 @@ self: { description = "j2hs"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ja-base-extra" = callPackage @@ -152363,7 +150250,6 @@ self: { description = "Jailed IO monad"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "jailbreak-cabal" = callPackage @@ -152579,7 +150465,6 @@ self: { description = "Utilities for working with the java-bridge package"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "java-character" = callPackage @@ -152592,7 +150477,6 @@ self: { description = "Functions to simulate Java's Character class"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "java-poker" = callPackage @@ -152619,7 +150503,6 @@ self: { description = "Tools for reflecting on Java classes"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "javaclass" = callPackage @@ -152705,7 +150588,6 @@ self: { description = "A utility to print the SourceFile attribute of one or more Java class files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "javav" = callPackage @@ -152929,7 +150811,6 @@ self: { description = "QuasiQuotation library for programmatic generation of Javascript code"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "jmacro-rpc" = callPackage @@ -152949,7 +150830,6 @@ self: { description = "JSON-RPC clients and servers using JMacro, and evented client-server Reactive Programming"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "jmacro-rpc-happstack" = callPackage @@ -152967,7 +150847,6 @@ self: { description = "Happstack backend for jmacro-rpc"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "jmacro-rpc-snap" = callPackage @@ -152984,7 +150863,6 @@ self: { description = "Snap backend for jmacro-rpc"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "jml-web-service" = callPackage @@ -153020,7 +150898,6 @@ self: { description = "Jmonkey is very restricted but handy EDSL for JavaScript"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "jni" = callPackage @@ -153093,7 +150970,6 @@ self: { description = "A library for creating a jobs management website running custom jobs"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "join" = callPackage @@ -153107,7 +150983,6 @@ self: { description = "Parallel Join Patterns with Guards and Propagation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "join-api" = callPackage @@ -153273,7 +151148,6 @@ self: { description = "Tiny markdown notebook"; license = lib.licenses.isc; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "jpeg" = callPackage @@ -153476,7 +151350,9 @@ self: { ]; description = "Interface for JavaScript that works with GHCJS and GHC"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; + platforms = [ + "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" + ]; }) {}; "jsaddle-webkitgtk" = callPackage @@ -153543,7 +151419,6 @@ self: { description = "Javascript Monadic Writer base package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "json" = callPackage @@ -153669,7 +151544,6 @@ self: { description = "Encoders of JSON AST"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "json-ast-quickcheck" = callPackage @@ -153721,7 +151595,6 @@ self: { description = "Automatic type declaration for JSON input data"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "json-b" = callPackage @@ -153745,7 +151618,6 @@ self: { description = "JSON parser that uses byte strings"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "json-builder" = callPackage @@ -153840,7 +151712,6 @@ self: { description = "Pure-Haskell utilities for dealing with JSON with the enumerator package. (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "json-extra" = callPackage @@ -153923,7 +151794,6 @@ self: { description = "Incremental JSON parser with early termination and a declarative DSL"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "json-litobj" = callPackage @@ -154068,7 +151938,6 @@ self: { description = "Kitchen sink for querying JSON"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "json-rpc" = callPackage @@ -154216,8 +152085,6 @@ self: { ]; description = "Generics JSON (de)serialization using generics-sop"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "json-state" = callPackage @@ -154282,7 +152149,6 @@ self: { description = "High-performance JSON parser and encoder"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "json-to-haskell" = callPackage @@ -154314,8 +152180,6 @@ self: { recursion-schemes text unordered-containers vector ]; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "json-togo" = callPackage @@ -154334,7 +152198,6 @@ self: { description = "Effectful parsing of JSON documents"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "json-tokens" = callPackage @@ -154363,7 +152226,6 @@ self: { description = "Tokenize JSON"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "json-tools" = callPackage @@ -154455,7 +152317,6 @@ self: { description = "Support JSON for SQL Database"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "json2-types" = callPackage @@ -154538,7 +152399,6 @@ self: { description = "Fast and simple JSON encoding toolkit"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "jsonnet" = callPackage @@ -154633,8 +152493,6 @@ self: { testToolDepends = [ hspec-discover ]; description = "JSON-RPC 2.0 server over a Conduit."; license = lib.licenses.gpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "jsons-to-schema" = callPackage @@ -154667,7 +152525,6 @@ self: { description = "JSON to JSON Schema"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "jsonschema-gen" = callPackage @@ -154797,7 +152654,6 @@ self: { description = "Extract substructures from JSON by following a path"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "juandelacosa" = callPackage @@ -154821,8 +152677,6 @@ self: { ]; description = "Manage users in MariaDB >= 10.1.1"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "judge" = callPackage @@ -155033,7 +152887,6 @@ self: { description = "Call JVM methods from Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "jvm-batching" = callPackage @@ -155061,7 +152914,6 @@ self: { description = "Provides batched marshalling of values between Java and Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "jvm-binary" = callPackage @@ -155141,7 +152993,6 @@ self: { description = "Expose Java iterators as streams from the streaming package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "jwt" = callPackage @@ -155262,7 +153113,6 @@ self: { description = "UI device events via a Kafka message broker"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kafka-device-glut" = callPackage @@ -155278,7 +153128,6 @@ self: { description = "GLUT events via a Kafka message broker"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kafka-device-joystick" = callPackage @@ -155300,7 +153149,6 @@ self: { description = "Linux joystick events via a Kafka message broker"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kafka-device-leap" = callPackage @@ -155320,7 +153168,6 @@ self: { description = "Leap Motion events via a Kafka message broker"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kafka-device-spacenav" = callPackage @@ -155342,7 +153189,6 @@ self: { description = "Linux SpaceNavigator events via a Kafka message broker"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kafka-device-vrpn" = callPackage @@ -155358,7 +153204,6 @@ self: { description = "VRPN events via a Kafka message broker"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kaleidoscope" = callPackage @@ -155382,7 +153227,6 @@ self: { description = "Haskell Kaleidoscope tutorial"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kalman" = callPackage @@ -155503,7 +153347,6 @@ self: { description = "Kansas Lava is a hardware simulator and VHDL generator"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kansas-lava-cores" = callPackage @@ -155524,7 +153367,6 @@ self: { description = "FPGA Cores Written in Kansas Lava"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kansas-lava-papilio" = callPackage @@ -155544,7 +153386,6 @@ self: { description = "Kansas Lava support files for the Papilio FPGA board"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kansas-lava-shake" = callPackage @@ -155562,7 +153403,6 @@ self: { description = "Shake rules for building Kansas Lava projects"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "karakuri" = callPackage @@ -155579,7 +153419,6 @@ self: { description = "Good stateful automata"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "karps" = callPackage @@ -155716,7 +153555,6 @@ self: { description = "ElasticSearch scribe for the Katip logging framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "katip-kafka" = callPackage @@ -155809,7 +153647,6 @@ self: { description = "Katip scribe that logs to Rollbar"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "katip-scalyr-scribe" = callPackage @@ -155953,7 +153790,6 @@ self: { description = "Utilities for serving static sites and blogs with Wai/Warp"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kawhi" = callPackage @@ -156200,7 +154036,6 @@ self: { description = "Rapid Gtk Application Development - I18N"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "keera-hails-mvc-controller" = callPackage @@ -156229,7 +154064,6 @@ self: { description = "Haskell on Gtk rails - Gtk-based global environment for MVC applications"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "keera-hails-mvc-model-lightmodel" = callPackage @@ -156247,7 +154081,6 @@ self: { description = "Rapid Gtk Application Development - Reactive Protected Light Models"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "keera-hails-mvc-model-protectedmodel" = callPackage @@ -156265,7 +154098,6 @@ self: { description = "Rapid Gtk Application Development - Protected Reactive Models"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "keera-hails-mvc-solutions-config" = callPackage @@ -156299,7 +154131,6 @@ self: { description = "Haskell on Gtk rails - Common solutions to recurrent problems in Gtk applications"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "keera-hails-mvc-view" = callPackage @@ -156343,7 +154174,6 @@ self: { description = "Reactive Haskell on Rails - CBMVars as reactive values"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "keera-hails-reactive-fs" = callPackage @@ -156360,7 +154190,6 @@ self: { description = "Haskell on Rails - Files as Reactive Values"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "keera-hails-reactive-gtk" = callPackage @@ -156378,7 +154207,6 @@ self: { description = "Haskell on Gtk rails - Reactive Fields for Gtk widgets"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "keera-hails-reactive-htmldom" = callPackage @@ -156397,7 +154225,6 @@ self: { description = "Keera Hails Reactive bindings for HTML DOM via GHCJS"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "keera-hails-reactive-network" = callPackage @@ -156414,7 +154241,6 @@ self: { description = "Haskell on Rails - Sockets as Reactive Values"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "keera-hails-reactive-polling" = callPackage @@ -156430,7 +154256,6 @@ self: { description = "Haskell on Rails - Polling based Readable RVs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "keera-hails-reactive-wx" = callPackage @@ -156445,7 +154270,6 @@ self: { description = "Haskell on Rails - Reactive Fields for WX widgets"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "keera-hails-reactive-yampa" = callPackage @@ -156462,7 +154286,6 @@ self: { description = "Haskell on Rails - FRP Yampa Signal Functions as RVs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "keera-hails-reactivelenses" = callPackage @@ -156475,7 +154298,6 @@ self: { description = "Reactive Haskell on Rails - Lenses applied to Reactive Values"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "keera-hails-reactivevalues" = callPackage @@ -156691,7 +154513,6 @@ self: { description = "a dAmn ↔ IRC proxy"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "key" = callPackage @@ -156854,7 +154675,6 @@ self: { description = "back up a secret key securely to the cloud"; license = lib.licenses.agpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "keystore" = callPackage @@ -156886,8 +154706,6 @@ self: { ]; description = "Managing stores of secret things"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "keyvaluehash" = callPackage @@ -156905,7 +154723,6 @@ self: { description = "Pure Haskell key/value store implementation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "keyword-args" = callPackage @@ -156928,7 +154745,6 @@ self: { description = "Extract data from a keyword-args config file format"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "khph" = callPackage @@ -156995,7 +154811,6 @@ self: { description = "Parser and writer for KiCad files"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kickass-torrents-dump-parser" = callPackage @@ -157054,7 +154869,6 @@ self: { description = "Process KIF iOS test logs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kind-apply" = callPackage @@ -157125,7 +154939,6 @@ self: { description = "A dependency manager for Xcode (Objective-C) projects"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kleene" = callPackage @@ -157148,7 +154961,6 @@ self: { description = "Kleene algebra"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kleene-list" = callPackage @@ -157199,7 +155011,6 @@ self: { description = "Sequential and parallel implementations of Lloyd's algorithm"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kmeans-vector" = callPackage @@ -157217,7 +155028,6 @@ self: { description = "An implementation of the kmeans clustering algorithm based on the vector package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kmonad" = callPackage @@ -157275,7 +155085,6 @@ self: { description = "Repa-like array processing using LLVM JIT"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "knead-arithmetic" = callPackage @@ -157290,7 +155099,6 @@ self: { description = "Linear algebra and interpolation using LLVM JIT"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "knit" = callPackage @@ -157343,7 +155151,6 @@ self: { description = "a minimal Rmarkdown sort-of-thing for haskell, by way of Pandoc"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "knob" = callPackage @@ -157374,7 +155181,6 @@ self: { description = "Khovanov homology computations"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "koellner-phonetic" = callPackage @@ -157501,7 +155307,6 @@ self: { description = "The Korfu ORF Utility"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kparams" = callPackage @@ -157650,7 +155455,6 @@ self: { description = "Kolmogorov distribution and Kolmogorov-Smirnov test"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ksystools" = callPackage @@ -157733,7 +155537,6 @@ self: { description = "Client library for Kubernetes"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kubernetes-client-core" = callPackage @@ -157761,8 +155564,6 @@ self: { ]; description = "Auto-generated kubernetes-client-core API Client"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kubernetes-webhook-haskell" = callPackage @@ -157803,8 +155604,6 @@ self: { libraryHaskellDepends = [ base dlist transformers ]; description = "Combinators for Strategic Programming"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kure-your-boilerplate" = callPackage @@ -157851,7 +155650,6 @@ self: { description = "Find the alpha emoji"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "kvitable" = callPackage @@ -157968,7 +155766,6 @@ self: { description = "an experiment management framework"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "labsat" = callPackage @@ -157993,7 +155790,6 @@ self: { description = "LabSat TCP Interface Wrapper"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "labyrinth" = callPackage @@ -158016,7 +155812,6 @@ self: { description = "A complicated turn-based game"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "labyrinth-server" = callPackage @@ -158051,7 +155846,6 @@ self: { description = "A complicated turn-based game - Web server"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lackey" = callPackage @@ -158064,8 +155858,6 @@ self: { testHaskellDepends = [ base hspec servant servant-foreign text ]; description = "Generate Ruby clients from Servant APIs"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lacroix" = callPackage @@ -158119,7 +155911,6 @@ self: { description = "Minimalistic type-checked compile-time template engine"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lambda-ast" = callPackage @@ -158167,7 +155958,6 @@ self: { description = "A lambda calculus interpreter"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lambda-calculus-interpreter" = callPackage @@ -158223,7 +156013,6 @@ self: { description = "a Paralell-DEVS implementaion based on distributed-process"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lambda-options" = callPackage @@ -158239,7 +156028,6 @@ self: { description = "Declarative command-line parser with type-driven pattern matching"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lambda-placeholders" = callPackage @@ -158324,7 +156112,6 @@ self: { description = "RSS 2.0 feed generator"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lambdaLit" = callPackage @@ -158343,7 +156130,6 @@ self: { description = "..."; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lambdabot" = callPackage @@ -158583,7 +156369,6 @@ self: { description = "Lambdabot for Zulip Chat"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lambdacat" = callPackage @@ -158646,7 +156431,6 @@ self: { description = "LambdaCms \"media\" extension"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lambdacube" = callPackage @@ -158661,7 +156445,6 @@ self: { description = "A simple lambda cube type checker"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lambdacube-bullet" = callPackage @@ -158676,7 +156459,6 @@ self: { description = "Example for combining LambdaCube and Bullet"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lambdacube-compiler" = callPackage @@ -158702,7 +156484,6 @@ self: { description = "LambdaCube 3D is a DSL to program GPUs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lambdacube-core" = callPackage @@ -158719,7 +156500,6 @@ self: { description = "LambdaCube 3D IR"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lambdacube-edsl" = callPackage @@ -158737,7 +156517,6 @@ self: { description = "LambdaCube 3D EDSL definition"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lambdacube-engine" = callPackage @@ -158758,7 +156537,6 @@ self: { description = "3D rendering engine written entirely in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lambdacube-examples" = callPackage @@ -158776,7 +156554,6 @@ self: { description = "Examples for LambdaCube"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lambdacube-gl" = callPackage @@ -158796,7 +156573,6 @@ self: { description = "OpenGL 3.3 Core Profile backend for LambdaCube 3D"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lambdacube-ir" = callPackage @@ -158832,7 +156608,6 @@ self: { description = "Samples for LambdaCube 3D"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lambdatex" = callPackage @@ -158896,7 +156671,6 @@ self: { description = "Fpga bus core and serialization for RedPitaya"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lambdiff" = callPackage @@ -158915,7 +156689,6 @@ self: { description = "Diff Viewer"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lame" = callPackage @@ -158973,7 +156746,6 @@ self: { description = "A Lisp"; license = lib.licenses.agpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "language-Modula2" = callPackage @@ -159007,7 +156779,6 @@ self: { description = "Parser, pretty-printer, and more for the Modula-2 programming language"; license = lib.licenses.gpl3Plus; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "language-asn" = callPackage @@ -159130,7 +156901,6 @@ self: { description = "Interpreter and language infrastructure for Boogie"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "language-c" = callPackage @@ -159376,8 +157146,6 @@ self: { doHaddock = false; description = "A language for generative literature"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "language-docker" = callPackage @@ -159503,7 +157271,6 @@ self: { description = "Parser and pretty printer for the Eiffel language"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "language-elm" = callPackage @@ -159536,8 +157303,6 @@ self: { libraryToolDepends = [ alex happy ]; description = "Fortran lexer and parser, language support, and extensions"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "language-gcl" = callPackage @@ -159746,7 +157511,6 @@ self: { description = "Parser and serializer for the Kort information language"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "language-lua" = callPackage @@ -159871,7 +157635,6 @@ self: { description = "A library for dealing with the Ninja build language"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "language-nix" = callPackage @@ -159920,7 +157683,6 @@ self: { description = "Parser, pretty-printer, and more for the Oberon programming language"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "language-objc" = callPackage @@ -160094,7 +157856,6 @@ self: { description = "Generate coloured XHTML for Python code"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "language-python-test" = callPackage @@ -160125,7 +157886,6 @@ self: { description = "Utilities for working with the Qux language"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "language-rust" = callPackage @@ -160226,7 +157986,6 @@ self: { description = "Various tools to detect/correct mistakes in words"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "language-sqlite" = callPackage @@ -160282,8 +158041,6 @@ self: { testToolDepends = [ hspec-discover ]; description = "Parser and pretty printer for the Thrift IDL format"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "language-tl" = callPackage @@ -160393,7 +158150,6 @@ self: { description = "Numerical Linear Algebra using LAPACK"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lapack-carray" = callPackage @@ -160411,7 +158167,6 @@ self: { description = "Auto-generated interface to Fortran LAPACK via CArrays"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lapack-comfort-array" = callPackage @@ -160429,7 +158184,6 @@ self: { description = "Auto-generated interface to Fortran LAPACK via comfort-array"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lapack-ffi" = callPackage @@ -160496,8 +158250,10 @@ self: { ]; description = "Efficiently hash (large) Haskell values"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; + platforms = [ + "armv7l-linux" "i686-linux" "x86_64-darwin" "x86_64-linux" + ]; + maintainers = with lib.maintainers; [ sternenseemann ]; }) {}; "largeword" = callPackage @@ -160535,7 +158291,6 @@ self: { description = "Tool to track security alerts on LWN"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "latest-npm-version" = callPackage @@ -160598,7 +158353,6 @@ self: { description = "Use actual LaTeX to render formulae inside Hakyll pages"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "latex-formulae-image" = callPackage @@ -160641,7 +158395,6 @@ self: { description = "Render LaTeX formulae in pandoc documents to images with an actual LaTeX installation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "latex-function-tables" = callPackage @@ -160695,7 +158448,6 @@ self: { description = "Use actual LaTeX to render formulae inside Hakyll pages"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "latex-svg-image" = callPackage @@ -160735,7 +158487,6 @@ self: { description = "Render LaTeX formulae in pandoc documents to images with an actual LaTeX"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lattices" = callPackage @@ -160794,8 +158545,6 @@ self: { ]; description = "Server-side SDK for integrating with LaunchDarkly"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "launchpad-control" = callPackage @@ -160894,7 +158643,6 @@ self: { description = "Control structure similar to Control.Monad.State, allowing multiple nested states, distinguishable by provided phantom types."; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "layers" = callPackage @@ -160928,7 +158676,6 @@ self: { description = "A prototypical 2d platform game"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "layout" = callPackage @@ -160966,8 +158713,6 @@ self: { libraryHaskellDepends = [ alex-tools base text ]; description = "A collection of different layout implementations"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "layouting" = callPackage @@ -160984,7 +158729,6 @@ self: { description = "General layouting library. Currently supports layouting 2D areas and can be used as a backend for text pretty printing or automatic windows layouting managers."; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lazy" = callPackage @@ -161029,7 +158773,6 @@ self: { description = "Identifiers for not-yet-computed values"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lazy-hash-cache" = callPackage @@ -161051,7 +158794,6 @@ self: { description = "Storing computed values for re-use when the same program runs again"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lazy-io" = callPackage @@ -161076,8 +158818,6 @@ self: { libraryHaskellDepends = [ base bytestring io-streams ]; description = "Get lazy with your io-streams"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lazy-priority-queue" = callPackage @@ -161107,8 +158847,6 @@ self: { libraryHaskellDepends = [ base size-based ]; description = "Finds values satisfying a lazy predicate"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lazyarray" = callPackage @@ -161299,7 +159037,6 @@ self: { description = "LDIF idempotent apply tool"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ldif" = callPackage @@ -161363,7 +159100,6 @@ self: { description = "Robust space leak, and its strictification"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lean" = callPackage @@ -161380,7 +159116,6 @@ self: { description = "Bonds to Lean theorem prover"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lean-peano" = callPackage @@ -161483,8 +159218,6 @@ self: { ]; description = "Use the Leanpub API via Wreq"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "leapseconds" = callPackage @@ -161667,7 +159400,6 @@ self: { description = "Distributed, stateful, homogeneous microservice framework"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "legion-discovery" = callPackage @@ -161694,7 +159426,6 @@ self: { description = "A discovery service based on Legion"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "legion-discovery-client" = callPackage @@ -161715,7 +159446,6 @@ self: { description = "Client library for communicating with legion-discovery"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "legion-extra" = callPackage @@ -161738,7 +159468,6 @@ self: { description = "Extra non-essential utilities for building legion applications"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "leksah" = callPackage @@ -161815,7 +159544,6 @@ self: { description = "Metadata collection for leksah"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lendingclub" = callPackage @@ -162356,7 +160084,6 @@ self: { description = "Collection of missing lens utilities"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lens-xml" = callPackage @@ -162422,8 +160149,6 @@ self: { ]; description = "frugal issue tracker"; license = lib.licenses.gpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lenz" = callPackage @@ -162577,7 +160302,6 @@ self: { description = "An implementation of the Levenberg-Marquardt algorithm"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "levmar-chart" = callPackage @@ -162592,7 +160316,6 @@ self: { description = "Plots the results of the Levenberg-Marquardt algorithm in a chart"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lex-applicative" = callPackage @@ -162613,7 +160336,6 @@ self: { description = "See README for more info"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lexer-applicative" = callPackage @@ -162672,7 +160394,6 @@ self: { description = "Lens GUI Toolkit"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lha" = callPackage @@ -162685,7 +160406,6 @@ self: { description = "Data structures for the Les Houches Accord"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lhae" = callPackage @@ -162706,7 +160426,6 @@ self: { description = "Simple spreadsheet program"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lhc" = callPackage @@ -162734,7 +160453,6 @@ self: { description = "Parser and writer for Les-Houches event files"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lhs2TeX-hl" = callPackage @@ -162869,8 +160587,6 @@ self: { ]; description = "Haskell interface to libarchive"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) libarchive;}; "libarchive-conduit" = callPackage @@ -162908,7 +160624,6 @@ self: { description = "Haskell bindings to libconfig"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) libconfig;}; "libcspm" = callPackage @@ -162930,7 +160645,6 @@ self: { description = "A library providing a parser, type checker and evaluator for CSPM"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "libexpect" = callPackage @@ -163174,7 +160888,6 @@ self: { description = "Lastfm API interface"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "liblawless" = callPackage @@ -163211,7 +160924,6 @@ self: { description = "Prelude based on protolude for GHC 8 and beyond"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "liblinear-enumerator" = callPackage @@ -163226,7 +160938,6 @@ self: { description = "liblinear iteratee"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "libltdl" = callPackage @@ -163290,7 +161001,6 @@ self: { description = "Prelude based on protolude for GHC 8 and beyond"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "libmpd" = callPackage @@ -163486,7 +161196,6 @@ self: { description = "Raft consensus algorithm"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "librandomorg" = callPackage @@ -163521,7 +161230,6 @@ self: { description = "Bindings to the Librato API"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "libravatar" = callPackage @@ -163638,7 +161346,6 @@ self: { description = "Conduit wrappers for libssh2 FFI bindings (see libssh2 package)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "libstackexchange" = callPackage @@ -163815,7 +161522,6 @@ self: { description = "Enumerator-based API for libXML's SAX interface"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "libxml-sax" = callPackage @@ -163969,7 +161675,6 @@ self: { description = "Flexible manual resource management"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lift-generics" = callPackage @@ -164081,7 +161786,6 @@ self: { description = "lifted IO operations from the base library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lifted-protolude" = callPackage @@ -164212,7 +161916,6 @@ self: { description = "Haskell client for lightning-viz REST API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lightstep-haskell" = callPackage @@ -164245,7 +161948,6 @@ self: { description = "LightStep OpenTracing client library"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lighttpd-conf" = callPackage @@ -164263,7 +161965,6 @@ self: { description = "Lighttpd configuration file tools"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lighttpd-conf-qq" = callPackage @@ -164281,7 +161982,6 @@ self: { description = "A QuasiQuoter for lighttpd configuration files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lilypond" = callPackage @@ -164458,8 +162158,6 @@ self: { ]; description = "Haskell SDK for LINE Messaging API"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "line-break" = callPackage @@ -164630,7 +162328,6 @@ self: { description = "Compute resistance of linear electrical circuits"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "linear-code" = callPackage @@ -164777,7 +162474,6 @@ self: { description = "Native, complete, matrix-free linear algebra"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "linearscan" = callPackage @@ -164814,7 +162510,6 @@ self: { description = "Makes it easy to use the linearscan register allocator with Hoopl"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "linebreak" = callPackage @@ -164925,7 +162620,6 @@ self: { description = "linkchk is a network interface link ping monitor"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "linkcore" = callPackage @@ -164943,7 +162637,6 @@ self: { description = "Combines multiple GHC Core modules into a single module"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "linked-list-with-iterator" = callPackage @@ -165032,8 +162725,6 @@ self: { ]; description = "Lightweight library for building HTTP API"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "linnet-aeson" = callPackage @@ -165051,8 +162742,6 @@ self: { ]; description = "Aeson JSON support for Linnet"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "linnet-conduit" = callPackage @@ -165073,8 +162762,6 @@ self: { ]; description = "Conduit-backed support for streaming in Linnet"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "linode" = callPackage @@ -165285,7 +162972,6 @@ self: { description = "Wrapping of Linux' ptrace(2)"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "linux-xattr" = callPackage @@ -165347,7 +163033,6 @@ self: { description = "Labeled IO library"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lio-fs" = callPackage @@ -165410,7 +163095,6 @@ self: { description = "RISC-V Core"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lipsum-gen" = callPackage @@ -165464,7 +163148,6 @@ self: { description = "Drop-in base replacement for LiquidHaskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "liquid-bytestring" = callPackage @@ -165481,7 +163164,6 @@ self: { description = "LiquidHaskell specs for the bytestring package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "liquid-containers" = callPackage @@ -165498,7 +163180,6 @@ self: { description = "LiquidHaskell specs for the containers package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "liquid-fixpoint" = callPackage @@ -165547,7 +163228,6 @@ self: { description = "Drop-in ghc-prim replacement for LiquidHaskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "liquid-parallel" = callPackage @@ -165563,7 +163243,6 @@ self: { description = "LiquidHaskell specs for the parallel package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "liquid-platform" = callPackage @@ -165584,7 +163263,6 @@ self: { description = "A battery-included platform for LiquidHaskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "liquid-prelude" = callPackage @@ -165602,7 +163280,6 @@ self: { description = "General utility modules for LiquidHaskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "liquid-vector" = callPackage @@ -165617,7 +163294,6 @@ self: { description = "LiquidHaskell specs for the vector package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "liquidhaskell" = callPackage @@ -165883,7 +163559,6 @@ self: { description = "An \"attoparsec\" adapter for \"list-t\""; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "list-t-html-parser" = callPackage @@ -165908,7 +163583,6 @@ self: { description = "Streaming HTML parser"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "list-t-http-client" = callPackage @@ -166031,7 +163705,6 @@ self: { description = "Witnesses for working with type-level lists"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "list-zip-def" = callPackage @@ -166087,7 +163760,6 @@ self: { description = "A client library to the ListenBrainz project"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "listlike-instances" = callPackage @@ -166224,8 +163896,6 @@ self: { ]; description = "Basic logging based on co-log"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "little-rio" = callPackage @@ -166270,7 +163940,6 @@ self: { description = "Live coding of MIDI music"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "liveplot" = callPackage @@ -166358,7 +164027,6 @@ self: { description = "Bindings to the LLVM compiler toolkit"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "llvm-analysis" = callPackage @@ -166387,7 +164055,6 @@ self: { description = "A Haskell library for analyzing LLVM bitcode"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "llvm-base" = callPackage @@ -166422,7 +164089,6 @@ self: { description = "The base types for a mostly pure Haskell LLVM analysis library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "llvm-base-util" = callPackage @@ -166435,7 +164101,6 @@ self: { description = "Utilities for bindings to the LLVM compiler toolkit"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "llvm-data-interop" = callPackage @@ -166457,7 +164122,6 @@ self: { description = "A low-level data interoperability binding for LLVM"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "llvm-dsl" = callPackage @@ -166476,7 +164140,6 @@ self: { description = "Support for writing an EDSL with LLVM-JIT as target"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "llvm-extension" = callPackage @@ -166496,7 +164159,6 @@ self: { description = "Processor specific intrinsics for the llvm interface"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "llvm-extra" = callPackage @@ -166523,7 +164185,6 @@ self: { description = "Utility functions for the llvm interface"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "llvm-ffi" = callPackage @@ -166586,7 +164247,6 @@ self: { description = "General purpose LLVM bindings"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {llvm-config = null;}; "llvm-general-pure" = callPackage @@ -166633,7 +164293,6 @@ self: { description = "QuasiQuoting llvm code for llvm-general"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "llvm-hs" = callPackage @@ -166782,7 +164441,6 @@ self: { description = "LLVM bitcode parsing library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "llvm-tf" = callPackage @@ -166805,7 +164463,6 @@ self: { description = "Bindings to the LLVM compiler toolkit using type families"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "llvm-tools" = callPackage @@ -166834,7 +164491,6 @@ self: { description = "Useful tools built on llvm-analysis"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lmdb" = callPackage @@ -166927,7 +164583,6 @@ self: { description = "LMonad for Yesod integrates LMonad's IFC with Yesod web applications"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "load-balancing" = callPackage @@ -167039,7 +164694,6 @@ self: { description = "Generalised local search within Haskell, for applications in combinatorial optimisation"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "localization" = callPackage @@ -167070,7 +164724,6 @@ self: { description = "GNU Gettext-based messages localization library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "located" = callPackage @@ -167197,7 +164850,6 @@ self: { description = "Very simple poll lock"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lockfree-queue" = callPackage @@ -167256,7 +164908,6 @@ self: { description = "Structured logging solution with multiple backends"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "log-base" = callPackage @@ -167372,7 +165023,6 @@ self: { description = "Structured logging solution (PostgreSQL back end)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "log-utils" = callPackage @@ -167396,7 +165046,6 @@ self: { description = "Utils for working with logs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "log-warper" = callPackage @@ -167611,7 +165260,6 @@ self: { description = "Supplemental packages for `logging-effect`"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "logging-effect-extra-file" = callPackage @@ -167746,7 +165394,6 @@ self: { description = "Framework for propositional and first order logic, theorem proving"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "logicst" = callPackage @@ -167866,7 +165513,6 @@ self: { description = "Useful utilities for the Lojban language"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lojbanParser" = callPackage @@ -167913,7 +165559,6 @@ self: { description = "Prolog with lojban"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lol" = callPackage @@ -167965,7 +165610,6 @@ self: { description = "Lattice-based cryptographic applications using ."; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lol-benches" = callPackage @@ -167983,7 +165627,6 @@ self: { description = "A library for benchmarking ."; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lol-calculus" = callPackage @@ -168027,7 +165670,6 @@ self: { description = "A fast C++ backend for ."; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lol-repa" = callPackage @@ -168048,7 +165690,6 @@ self: { description = "A repa backend for ."; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lol-tests" = callPackage @@ -168069,7 +165710,6 @@ self: { description = "A library for testing ."; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lol-typing" = callPackage @@ -168095,7 +165735,6 @@ self: { description = "Type inferencer for LOL (λω language)"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "loli" = callPackage @@ -168114,7 +165753,6 @@ self: { description = "A minimum web dev DSL in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "long-double" = callPackage @@ -168171,7 +165809,6 @@ self: { description = "Fast Brute-force search using parallelism"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lookup-tables" = callPackage @@ -168216,7 +165853,6 @@ self: { description = "control-monad-loop port for effin"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "loop-while" = callPackage @@ -168388,7 +166024,6 @@ self: { description = "EDSL for the Michelson Language"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "loris" = callPackage @@ -168442,7 +166077,6 @@ self: { description = "An implementation of an adictive two-player card game"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "louis" = callPackage @@ -168477,7 +166111,6 @@ self: { description = "Amazon Simple Workflow Service Wrapper for Work Pools"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lowgl" = callPackage @@ -168603,7 +166236,6 @@ self: { description = "List USB devices"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lscabal" = callPackage @@ -168787,7 +166419,6 @@ self: { description = "Paint an L-System Grammar"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ltext" = callPackage @@ -168819,6 +166450,8 @@ self: { ]; description = "Parameterized file evaluator"; license = lib.licenses.bsd3; + hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "lti13" = callPackage @@ -168840,7 +166473,6 @@ self: { description = "Core functionality for LTI 1.3."; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ltiv1p1" = callPackage @@ -168958,7 +166590,6 @@ self: { description = "Library functions for reading and writing Lua chunks"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "luautils" = callPackage @@ -169039,7 +166670,6 @@ self: { description = "Helper functions for using lucid with colonnade"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lucid-extras" = callPackage @@ -169107,7 +166737,6 @@ self: { description = "Server side feed aggregator/reader"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "luhn" = callPackage @@ -169120,7 +166749,6 @@ self: { description = "An implementation of Luhn's check digit algorithm"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lui" = callPackage @@ -169137,7 +166765,6 @@ self: { description = "Purely FunctionaL User Interface"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "luis-client" = callPackage @@ -169246,7 +166873,6 @@ self: { description = "Luminance samples"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lushtags" = callPackage @@ -169315,7 +166941,6 @@ self: { description = "Parallel scheduler, LVar data structures, and infrastructure to build more"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lvmlib" = callPackage @@ -169468,8 +167093,6 @@ self: { ]; description = "Bindings to LZ4"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lz4-conduit" = callPackage @@ -169494,7 +167117,6 @@ self: { description = "LZ4 compression for conduits"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "lz4-frame-conduit" = callPackage @@ -169649,7 +167271,6 @@ self: { description = "Enumerator interface for lzma/xz compression"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) xz;}; "lzma-static" = callPackage @@ -169722,7 +167343,6 @@ self: { description = "Library for talking to the mDNSResponder daemon"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "maam" = callPackage @@ -169802,7 +167422,6 @@ self: { description = "Macbeth - A beautiful and minimalistic FICS client"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "maccatcher" = callPackage @@ -169892,7 +167511,6 @@ self: { description = "Machine transducers for Amazonka calls"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "machines-attoparsec" = callPackage @@ -169913,8 +167531,6 @@ self: { ]; description = "Parse machines streams with attoparsec parsers"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "machines-binary" = callPackage @@ -169926,8 +167542,6 @@ self: { libraryHaskellDepends = [ base binary bytestring machines ]; description = "Binary utilities for the machines library"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "machines-bytestring" = callPackage @@ -169986,8 +167600,6 @@ self: { ]; description = "IO utilities for the machines library"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "machines-process" = callPackage @@ -170002,8 +167614,6 @@ self: { ]; description = "Process (system) utilities for the machines library"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "machines-zlib" = callPackage @@ -170120,7 +167730,6 @@ self: { description = "Make a macosx app standalone deployable"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "macrm" = callPackage @@ -170274,7 +167883,6 @@ self: { description = "Interact with Magic Wormhole"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "magicbane" = callPackage @@ -170306,7 +167914,6 @@ self: { description = "A web framework that integrates Servant, RIO, EKG, fast-logger, wai-cli…"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "magico" = callPackage @@ -170325,7 +167932,6 @@ self: { description = "Compute solutions for Magico puzzle"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "magma" = callPackage @@ -170373,7 +167979,6 @@ self: { description = "ImageBoards to XMPP gate"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "maid" = callPackage @@ -170396,7 +168001,6 @@ self: { description = "A simple static web server"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mail-pool" = callPackage @@ -170420,7 +168024,6 @@ self: { description = "Preconfigured email connection pool on top of smtp"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mail-reports" = callPackage @@ -170436,8 +168039,6 @@ self: { ]; description = "A parser library for DMARC and SMTP TLS reports"; license = lib.licenses.agpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mailbox-count" = callPackage @@ -170522,7 +168123,6 @@ self: { description = "API binding for Mailgun"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "main-tester" = callPackage @@ -170573,7 +168173,6 @@ self: { description = "Majordomo protocol for ZeroMQ"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "majority" = callPackage @@ -170586,7 +168185,6 @@ self: { description = "Boyer-Moore Majority Vote Algorithm"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "make-hard-links" = callPackage @@ -170749,7 +168347,6 @@ self: { description = "The Haskell/Gtk+ Integrated Live Environment"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "manatee-all" = callPackage @@ -170797,7 +168394,6 @@ self: { description = "Multithread interactive input/search framework for Manatee"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "manatee-browser" = callPackage @@ -170842,7 +168438,6 @@ self: { description = "The core of Manatee"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "manatee-curl" = callPackage @@ -170866,7 +168461,6 @@ self: { description = "Download Manager extension for Manatee"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "manatee-editor" = callPackage @@ -170888,7 +168482,6 @@ self: { description = "Editor extension for Manatee"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "manatee-filemanager" = callPackage @@ -170910,7 +168503,6 @@ self: { description = "File manager extension for Manatee"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "manatee-imageviewer" = callPackage @@ -170932,7 +168524,6 @@ self: { description = "Image viewer extension for Manatee"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "manatee-ircclient" = callPackage @@ -170958,7 +168549,6 @@ self: { description = "IRC client extension for Manatee"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "manatee-mplayer" = callPackage @@ -170981,7 +168571,6 @@ self: { description = "Mplayer client extension for Manatee"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "manatee-pdfviewer" = callPackage @@ -171003,7 +168592,6 @@ self: { description = "PDF viewer extension for Manatee"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "manatee-processmanager" = callPackage @@ -171024,7 +168612,6 @@ self: { description = "Process manager extension for Manatee"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "manatee-reader" = callPackage @@ -171066,7 +168653,6 @@ self: { description = "Template code to create Manatee application"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "manatee-terminal" = callPackage @@ -171087,7 +168673,6 @@ self: { description = "Terminal Emulator extension for Manatee"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "manatee-welcome" = callPackage @@ -171108,7 +168693,6 @@ self: { description = "Welcome module to help user play Manatee quickly"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mancala" = callPackage @@ -171246,7 +168830,6 @@ self: { description = "Sampling random points on general manifolds"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "manifolds" = callPackage @@ -171277,7 +168860,6 @@ self: { description = "Coordinate-free hypersurfaces"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "manifolds-core" = callPackage @@ -171472,7 +169054,6 @@ self: { description = "A study of marionetta movements"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "markdown" = callPackage @@ -171532,7 +169113,6 @@ self: { description = "markdown parser with papillon"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "markdown-unlit" = callPackage @@ -171573,7 +169153,6 @@ self: { description = "markdown to svg converter"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "marked-pretty" = callPackage @@ -171644,7 +169223,6 @@ self: { description = "Hidden Markov processes"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "markov-realization" = callPackage @@ -171657,8 +169235,6 @@ self: { testHaskellDepends = [ base HTF MonadRandom ]; description = "Realizations of Markov chains"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "markup" = callPackage @@ -171678,7 +169254,6 @@ self: { description = "Abstraction for HTML-embedded content"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "markup-preview" = callPackage @@ -171728,7 +169303,6 @@ self: { description = "Upload packages to Marmalade"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "marquise" = callPackage @@ -171764,7 +169338,6 @@ self: { description = "Client library for Vaultaire"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mars" = callPackage @@ -171832,7 +169405,6 @@ self: { description = "A framework for modular, portable chat bots"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "marvin-interpolate" = callPackage @@ -171897,7 +169469,6 @@ self: { description = "@minamiyama1994_bot on haskell"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mason" = callPackage @@ -172064,7 +169635,6 @@ self: { description = "The project management tool for hackers"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mastermind" = callPackage @@ -172140,7 +169710,6 @@ self: { description = "Text matchers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) pcre;}; "math-extras" = callPackage @@ -172264,7 +169833,6 @@ self: { description = "A GLPK backend to the math-programming library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) glpk;}; "math-programming-tests" = callPackage @@ -172281,7 +169849,6 @@ self: { description = "Utility functions for testing implementations of the math-programming library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mathblog" = callPackage @@ -172309,7 +169876,6 @@ self: { description = "A program for creating and managing a static weblog with LaTeX math and diagrams"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mathexpr" = callPackage @@ -172401,7 +169967,6 @@ self: { description = "Write Mathematica packages in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "matlab" = callPackage @@ -172637,7 +170202,6 @@ self: { description = "ncurses XMPP client"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "matterhorn" = callPackage @@ -172763,7 +170327,6 @@ self: { description = "Compute Maximum Entropy Distributions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "maxent-learner-hw" = callPackage @@ -172811,7 +170374,6 @@ self: { description = "GUI for maxent-learner-hw"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "maximal-cliques" = callPackage @@ -172845,7 +170407,6 @@ self: { description = "Maximal sharing of terms in the lambda calculus with letrec"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "maybe-justify" = callPackage @@ -173080,7 +170641,6 @@ self: { description = "Sample from a posterior using Markov chain Monte Carlo"; license = lib.licenses.gpl3Plus; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mcmc-samplers" = callPackage @@ -173097,7 +170657,6 @@ self: { description = "Combinators for MCMC sampling"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mcmc-synthesis" = callPackage @@ -173257,7 +170816,6 @@ self: { description = "See readme.md"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "means" = callPackage @@ -173426,7 +170984,6 @@ self: { description = "Mediabus plugin for the Frauenhofer ISO-14496-3 AAC FDK"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {fdk-aac = null;}; "mediabus-rtp" = callPackage @@ -173465,7 +171022,6 @@ self: { description = "Receive and Send RTP Packets"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "median-stream" = callPackage @@ -173691,7 +171247,6 @@ self: { description = "GPIO support for mellon"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mellon-web" = callPackage @@ -173734,7 +171289,6 @@ self: { description = "A REST web service for Mellon controllers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "melody" = callPackage @@ -173811,8 +171365,6 @@ self: { benchmarkHaskellDepends = [ base bytestring criterion ]; description = "A memcached client library"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "memcache-conduit" = callPackage @@ -173833,7 +171385,6 @@ self: { description = "Conduit library for memcache procotol"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "memcache-haskell" = callPackage @@ -174226,7 +171777,6 @@ self: { description = "Support for using mergeful from persistent-based databases"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mergeless" = callPackage @@ -174266,7 +171816,6 @@ self: { description = "Support for using mergeless from persistent-based databases"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "merkle-log" = callPackage @@ -174319,7 +171868,6 @@ self: { description = "A modified Merkle Patricia DB"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "merkle-tree" = callPackage @@ -174470,7 +172018,6 @@ self: { description = "Support for integrated Accelerate computations within Meta-par"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "metadata" = callPackage @@ -174521,7 +172068,6 @@ self: { description = "a tiny ghc api wrapper"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "metar" = callPackage @@ -174548,7 +172094,6 @@ self: { description = "Australian METAR"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "metar-http" = callPackage @@ -174574,7 +172119,6 @@ self: { description = "HTTP for METAR"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "method" = callPackage @@ -174752,7 +172296,6 @@ self: { description = "Time Synchronized execution"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mezzo" = callPackage @@ -174882,7 +172425,6 @@ self: { description = "A Micro service gateway"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "micro-recursion-schemes" = callPackage @@ -175002,7 +172544,6 @@ self: { description = "A Microformats 2 parser"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "microformats2-types" = callPackage @@ -175019,7 +172560,6 @@ self: { description = "Microformats 2 types (with Aeson instances)"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "microgroove" = callPackage @@ -175427,7 +172967,6 @@ self: { description = "A Memory-like (Concentration, Pairs, ...) game for tones"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "midisurface" = callPackage @@ -175468,7 +173007,6 @@ self: { description = "Simple Web Server in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mighttpd2" = callPackage @@ -175537,8 +173075,6 @@ self: { ]; description = "Semi-automatic database schema migrations"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "migrant-hdbc" = callPackage @@ -175598,8 +173134,6 @@ self: { ]; description = "Semi-automatic database schema migrations"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mikmod" = callPackage @@ -175836,7 +173370,6 @@ self: { description = "a DSL for generating minecraft commands and levels"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mines" = callPackage @@ -175872,7 +173405,6 @@ self: { description = "Minesweeper game which is always solvable without guessing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mini-egison" = callPackage @@ -175895,7 +173427,6 @@ self: { description = "Template Haskell Implementation of Egison Pattern Matching"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "miniball" = callPackage @@ -175929,7 +173460,6 @@ self: { description = "Miniature FORTH-like interpreter"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "minilens" = callPackage @@ -176001,7 +173531,6 @@ self: { description = "A binding library of minilight for Lua langauge"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "minimal-configuration" = callPackage @@ -176044,7 +173573,6 @@ self: { description = "Shows how to run grabber on Mac OS X"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "minio-hs" = callPackage @@ -176116,7 +173644,6 @@ self: { description = "fast and simple operational monad"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "miniplex" = callPackage @@ -176482,8 +174009,6 @@ self: { ]; description = "A tasty Haskell front-end framework"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "miso-action-logger" = callPackage @@ -176559,7 +174084,6 @@ self: { description = "A Haskell git implimentation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "miss-porcelain" = callPackage @@ -176579,7 +174103,6 @@ self: { description = "Useability extras built on top of miss"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "missing-foreign" = callPackage @@ -176606,7 +174129,6 @@ self: { description = "Haskell interface to Python"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mit-3qvpPyAi6mH" = callPackage @@ -176692,7 +174214,6 @@ self: { description = "Find optimal mixed strategies for two-player games"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mixed-types-num" = callPackage @@ -176770,7 +174291,6 @@ self: { description = "Makes an OS X .app bundle from a binary."; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mkcabal" = callPackage @@ -176790,7 +174310,6 @@ self: { description = "Generate cabal files for a Haskell project"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ml-w" = callPackage @@ -176819,7 +174338,6 @@ self: { description = "Monadic List alternative to lazy I/O"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mltool" = callPackage @@ -176955,7 +174473,6 @@ self: { description = "Command line interface to the MMark markdown processor"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mmark-ext" = callPackage @@ -176977,7 +174494,6 @@ self: { description = "Commonly useful extensions for the MMark markdown processor"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mmorph_1_1_3" = callPackage @@ -177133,8 +174649,6 @@ self: { ]; description = "Produces a sound recording specified by the Ukrainian text"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mmsyn7l" = callPackage @@ -177250,7 +174764,6 @@ self: { description = "MonadBase type-class for mmtl"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mnist-idx" = callPackage @@ -177281,7 +174794,6 @@ self: { description = "Language-agnostic analyzer for positional morphosyntactic tags"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mock-httpd" = callPackage @@ -177481,7 +174993,6 @@ self: { description = "Modify fasta (and CLIP) files in several optional ways"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "modsplit" = callPackage @@ -177503,7 +175014,6 @@ self: { description = "Haskell source splitter driven by special comments"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "modular" = callPackage @@ -177558,7 +175068,6 @@ self: { description = "Reifying ClassyPrelude a la ModularPrelude"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "modularity" = callPackage @@ -177575,7 +175084,6 @@ self: { description = "Find the modularity of a network"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "module-management" = callPackage @@ -177646,7 +175154,6 @@ self: { description = "Modular C code generator"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "moe" = callPackage @@ -177744,7 +175251,6 @@ self: { description = "A glorified string replacement tool"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mollie-api-haskell" = callPackage @@ -178077,7 +175583,6 @@ self: { description = "Exstensible monadic exceptions"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "monad-extras" = callPackage @@ -178527,8 +176032,6 @@ self: { ]; description = "An extensible and type-safe wrapper around EKG metrics"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "monad-mock" = callPackage @@ -178802,7 +176305,6 @@ self: { description = "Utility library for monads, particularly those involving state"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "monad-statevar" = callPackage @@ -178863,7 +176365,6 @@ self: { description = "ST-like monad capturing variables to regions and supporting STM"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "monad-stm" = callPackage @@ -179022,8 +176523,6 @@ self: { libraryHaskellDepends = [ base base-compat stm ]; description = "Generic operations over variables"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "monad-wrap" = callPackage @@ -179196,7 +176695,6 @@ self: { description = "Constraint Programming"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {gecodeint = null; gecodekernel = null; gecodesearch = null; gecodeset = null; gecodesupport = null;}; @@ -179353,7 +176851,6 @@ self: { description = "Monadic interface for TokyoTyrant"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mondo" = callPackage @@ -179391,7 +176888,6 @@ self: { description = "Mid-level bindings for the MonetDB API (mapi)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "money" = callPackage @@ -179438,8 +176934,6 @@ self: { ]; description = "Driver (client) for MongoDB, a free, scalable, fast, document DBMS"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mongodb-queue" = callPackage @@ -179480,7 +176974,6 @@ self: { description = "Mongrel2 Handler Library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "monitor" = callPackage @@ -179521,7 +177014,6 @@ self: { description = "A system state collecting library and application"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mono-foldable" = callPackage @@ -179885,7 +177377,6 @@ self: { description = "A monad and transformer for Monte Carlo calculations"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "months" = callPackage @@ -179971,7 +177462,6 @@ self: { description = "Genetic algorithm library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "moonshine" = callPackage @@ -180097,7 +177587,6 @@ self: { description = "Developer tools for the Michelson Language"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "morley-prelude" = callPackage @@ -180181,7 +177670,6 @@ self: { description = "A multi-lingual, typed, workflow language"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "morph" = callPackage @@ -180228,8 +177716,6 @@ self: { ]; description = "Morpheus GraphQL"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "morpheus-graphql-app" = callPackage @@ -180256,8 +177742,6 @@ self: { ]; description = "Morpheus GraphQL Core"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "morpheus-graphql-cli" = callPackage @@ -180352,8 +177836,6 @@ self: { ]; description = "Morpheus GraphQL Subscriptions"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "morphisms" = callPackage @@ -180389,7 +177871,6 @@ self: { description = "Inventory is state and store"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "morphisms-objects" = callPackage @@ -180457,7 +177938,6 @@ self: { description = "Generación interactiva de mosaicos"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mosquitto-hs" = callPackage @@ -180569,7 +178049,6 @@ self: { description = "Generate state diagrams from Motor FSM typeclasses"; license = lib.licenses.mpl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "motor-reflection" = callPackage @@ -180675,7 +178154,6 @@ self: { description = "Music player for linux"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mp3decoder" = callPackage @@ -180708,7 +178186,6 @@ self: { description = "MPD/PowerMate executable"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mpg123-bindings" = callPackage @@ -180852,7 +178329,6 @@ self: { description = "A minimalish prelude"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mpretty" = callPackage @@ -180870,7 +178346,6 @@ self: { description = "a monadic, extensible pretty printing library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mpris" = callPackage @@ -180902,7 +178377,6 @@ self: { description = "Simple equational reasoning for a Haskell-ish language"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mps" = callPackage @@ -180923,7 +178397,6 @@ self: { description = "simply oo"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mptcp-pm" = callPackage @@ -180949,7 +178422,6 @@ self: { description = "A work in progress Multipath TCP path manager"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mpvguihs" = callPackage @@ -181146,7 +178618,6 @@ self: { description = "Aeson adapter for MessagePack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "msgpack-binary" = callPackage @@ -181197,7 +178668,6 @@ self: { description = "An IDL Compiler for MessagePack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "msgpack-rpc" = callPackage @@ -181219,7 +178689,6 @@ self: { description = "A MessagePack-RPC Implementation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "msgpack-rpc-conduit" = callPackage @@ -181242,7 +178711,6 @@ self: { description = "A MessagePack-RPC Implementation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "msgpack-types" = callPackage @@ -181372,7 +178840,6 @@ self: { description = "Library to communicate with Mt.Gox"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mtl_2_2_2" = callPackage @@ -181580,8 +179047,6 @@ self: { ]; description = "Avro serialization support for Mu microservices"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mu-graphql" = callPackage @@ -181611,8 +179076,6 @@ self: { ]; description = "GraphQL support for Mu"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mu-grpc-client" = callPackage @@ -181637,7 +179100,6 @@ self: { description = "gRPC clients from Mu definitions"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mu-grpc-common" = callPackage @@ -181657,8 +179119,6 @@ self: { ]; description = "gRPC for Mu, common modules for client and server"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mu-grpc-server" = callPackage @@ -181686,7 +179146,6 @@ self: { description = "gRPC servers for Mu definitions"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mu-kafka" = callPackage @@ -181703,8 +179162,6 @@ self: { ]; description = "Utilities for interoperation between Mu and Kafka"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mu-lens" = callPackage @@ -181720,8 +179177,6 @@ self: { ]; description = "Lenses for @mu-schema@ terms"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mu-optics" = callPackage @@ -181736,8 +179191,6 @@ self: { ]; description = "Optics for @mu-schema@ terms"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mu-persistent" = callPackage @@ -181754,8 +179207,6 @@ self: { ]; description = "Utilities for interoperation between Mu and Persistent"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mu-prometheus" = callPackage @@ -181772,8 +179223,6 @@ self: { ]; description = "Metrics support for Mu using Prometheus"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mu-protobuf" = callPackage @@ -181801,8 +179250,6 @@ self: { ]; description = "Protocol Buffers serialization and gRPC schema import for Mu microservices"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mu-rpc" = callPackage @@ -181819,8 +179266,6 @@ self: { ]; description = "Protocol-independent declaration of services and servers"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mu-schema" = callPackage @@ -181839,8 +179284,6 @@ self: { ]; description = "Format-independent schemas for serialization"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mu-servant-server" = callPackage @@ -181864,8 +179307,6 @@ self: { ]; description = "Servant servers for Mu definitions"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mu-tracing" = callPackage @@ -181880,7 +179321,6 @@ self: { description = "Tracing support for Mu"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mucipher" = callPackage @@ -182047,7 +179487,6 @@ self: { description = "A tool supporting multi cabal project builds"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "multi-containers" = callPackage @@ -182087,8 +179526,6 @@ self: { testHaskellDepends = [ base containers HTF ]; description = "Trie of sets, as a model for compound names having multiple values"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "multiaddr" = callPackage @@ -182154,7 +179591,6 @@ self: { description = "Self-identifying base encodings, implementation of "; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "multifile" = callPackage @@ -182199,7 +179635,6 @@ self: { description = "Bidirectional Two-level Transformation of XML Schemas"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "multihash" = callPackage @@ -182262,7 +179697,6 @@ self: { description = "CBOR encoding of multihashes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "multihashmap" = callPackage @@ -182321,7 +179755,6 @@ self: { description = "Conduit-based input/output capability for multilinear package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "multimap" = callPackage @@ -182436,7 +179869,6 @@ self: { description = "Wrapper program for duplicity, adding config files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "multipool" = callPackage @@ -182564,7 +179996,6 @@ self: { description = "Alternative multirec instances deriver"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "multirec-binary" = callPackage @@ -182577,7 +180008,6 @@ self: { description = "Generic Data.Binary instances using MultiRec."; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "multiset" = callPackage @@ -182620,7 +180050,6 @@ self: { description = "Multi-set rewrite rules with guards and a parallel execution scheme"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "multistate" = callPackage @@ -182730,7 +180159,6 @@ self: { description = "MUtually Recursive Definitions Explicitly Represented"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "murmur" = callPackage @@ -182803,7 +180231,6 @@ self: { description = "32-bit non-cryptographic hashing"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mushu" = callPackage @@ -182897,7 +180324,6 @@ self: { description = "Diagrams-based visualization of musical data structures"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "music-parts" = callPackage @@ -182921,7 +180347,6 @@ self: { description = "Musical instruments, parts and playing techniques"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "music-pitch" = callPackage @@ -182940,7 +180365,6 @@ self: { description = "Musical pitch representation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "music-pitch-literal" = callPackage @@ -182982,7 +180406,6 @@ self: { description = "Some useful preludes for the Music Suite"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "music-score" = callPackage @@ -183007,7 +180430,6 @@ self: { description = "Musical score and part representation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "music-sibelius" = callPackage @@ -183028,7 +180450,6 @@ self: { description = "Interaction with Sibelius"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "music-suite" = callPackage @@ -183049,7 +180470,6 @@ self: { description = "A set of libraries for composition, analysis and manipulation of music"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "music-util" = callPackage @@ -183129,7 +180549,6 @@ self: { description = "Send an email to all MusicBrainz editors"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "musicw" = callPackage @@ -183185,7 +180604,6 @@ self: { description = "A representation of the MusicXML format"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mustache" = callPackage @@ -183316,7 +180734,6 @@ self: { description = "iteratees based upon mutable buffers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mutable-lens" = callPackage @@ -183354,7 +180771,6 @@ self: { description = "Watches your screensaver and (un)mutes music when you (un)lock the screen"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mvar-lock" = callPackage @@ -183398,7 +180814,6 @@ self: { description = "Concurrent and combinable updates"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mvclient" = callPackage @@ -183418,7 +180833,6 @@ self: { description = "Client library for metaverse systems like Second Life"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mwc-probability" = callPackage @@ -183572,7 +180986,6 @@ self: { description = "mxnet dataiters"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mxnet-examples" = callPackage @@ -183587,7 +181000,6 @@ self: { description = "Examples for MXNet in Haskell"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mxnet-nn" = callPackage @@ -183614,7 +181026,6 @@ self: { description = "Train a neural network with MXNet in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mxnet-nnvm" = callPackage @@ -183707,7 +181118,6 @@ self: { description = "None"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "myanimelist-export" = callPackage @@ -183809,7 +181219,6 @@ self: { description = "Example projects using mysnapsession"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mysql" = callPackage @@ -183899,7 +181308,6 @@ self: { description = "TLS support for mysql-haskell package using openssl"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mysql-simple" = callPackage @@ -183951,7 +181359,6 @@ self: { description = "Typed extension to mysql simple"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "mystem" = callPackage @@ -183997,7 +181404,6 @@ self: { description = "Web application to view and kill MySQL queries"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "myxine-client" = callPackage @@ -184145,7 +181551,6 @@ self: { description = "N2O adapter for WebSockets"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "nagios-check" = callPackage @@ -184256,7 +181661,6 @@ self: { description = "Client library for the Nakadi Event Broker"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "namecoin-update" = callPackage @@ -184335,8 +181739,6 @@ self: { libraryHaskellDepends = [ base named servant ]; description = "support records and named (from the named package) parameters in servant"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "named-servant-client" = callPackage @@ -184352,8 +181754,6 @@ self: { ]; description = "client support for named-servant"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "named-servant-server" = callPackage @@ -184439,8 +181839,6 @@ self: { testHaskellDepends = [ base ]; description = "A Generic Haskell library for managing namespaces"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "nano-cryptr" = callPackage @@ -184638,7 +182036,6 @@ self: { description = "Simple interface to rendering with NanoVG"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "nanq" = callPackage @@ -184837,7 +182234,6 @@ self: { description = "Haskell API for NATS messaging system"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "natural" = callPackage @@ -184899,7 +182295,6 @@ self: { description = "Natural numbers tagged with a type-level representation of the number"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "natural-numbers" = callPackage @@ -185246,7 +182641,6 @@ self: { description = "A collection of Nemesis tasks to bootstrap a Haskell project with a focus on continuous integration"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "neptune-backend" = callPackage @@ -185309,7 +182703,6 @@ self: { description = "Nerf, a named entity recognition tool based on linear-chain CRFs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "nero" = callPackage @@ -185346,7 +182739,6 @@ self: { description = "WAI adapter for Nero server applications"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "nero-warp" = callPackage @@ -185359,7 +182751,6 @@ self: { description = "Run Nero server applications with Warp"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "nest" = callPackage @@ -185407,7 +182798,6 @@ self: { description = "Declarative, compositional Wai responses"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "nested-sequence" = callPackage @@ -185590,7 +182980,6 @@ self: { description = "CLI option parsers for NetSpider objects"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "net-spider-pangraph" = callPackage @@ -185610,7 +182999,6 @@ self: { description = "Conversion between net-spider and pangraph"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "net-spider-rpl" = callPackage @@ -185633,7 +183021,6 @@ self: { description = "NetSpider data model and utility for RPL networks"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "net-spider-rpl-cli" = callPackage @@ -185661,7 +183048,6 @@ self: { description = "CLI executable of NetSpider.RPL."; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "netclock" = callPackage @@ -185723,7 +183109,6 @@ self: { description = "The NetCore compiler and runtime system for OpenFlow networks"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "netease-fm" = callPackage @@ -185814,7 +183199,6 @@ self: { description = "Enumerator tools for text-based network protocols"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "netlink" = callPackage @@ -185945,7 +183329,6 @@ self: { description = "Enumerator-based netstring parsing"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "nettle" = callPackage @@ -185988,7 +183371,6 @@ self: { description = "FRP for controlling networks of OpenFlow switches"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "nettle-netkit" = callPackage @@ -186005,7 +183387,6 @@ self: { description = "DSL for describing OpenFlow networks, and a compiler generating NetKit labs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "nettle-openflow" = callPackage @@ -186023,7 +183404,6 @@ self: { description = "OpenFlow protocol messages, binary formats, and servers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "netwire" = callPackage @@ -186204,7 +183584,6 @@ self: { description = "Haskell API for I2P anonymous networking"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "network-anonymous-tor" = callPackage @@ -186235,7 +183614,6 @@ self: { description = "Haskell API for Tor anonymous networking"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "network-api-support" = callPackage @@ -186276,8 +183654,6 @@ self: { testToolDepends = [ hspec-discover ]; description = "Arbitrary Instances for Network Types"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "network-attoparsec" = callPackage @@ -186405,8 +183781,6 @@ self: { ]; description = "A Haskell implementation of the Carbon protocol (part of the Graphite monitoring tools)"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "network-conduit" = callPackage @@ -186455,7 +183829,6 @@ self: { description = "A wrapper around a generic stream-like connection"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "network-data" = callPackage @@ -186524,7 +183897,6 @@ self: { description = "Enumerators for network sockets"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "network-fancy" = callPackage @@ -186548,7 +183920,6 @@ self: { description = "HaNS to Network shims for easier HaNS integration"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "network-house" = callPackage @@ -186587,7 +183958,6 @@ self: { description = "Haskell bindings for the ifreq structure"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "network-ip" = callPackage @@ -186670,7 +184040,6 @@ self: { description = "WebSocket backend for MessagePack RPC"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "network-metrics" = callPackage @@ -186687,6 +184056,7 @@ self: { description = "Send metrics to Ganglia, Graphite, and statsd"; license = "unknown"; hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "network-minihttp" = callPackage @@ -186707,7 +184077,6 @@ self: { description = "A ByteString based library for writing HTTP(S) servers and clients"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "network-msg" = callPackage @@ -186720,6 +184089,7 @@ self: { description = "Recvmsg and sendmsg bindings"; license = "unknown"; hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "network-msgpack-rpc" = callPackage @@ -186772,7 +184142,6 @@ self: { description = "Haskell bindings for low-level packet sockets (AF_PACKET)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "network-packet-linux" = callPackage @@ -186825,7 +184194,6 @@ self: { description = "Client library for the XMPP protocol"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "network-rpca" = callPackage @@ -186844,7 +184212,6 @@ self: { description = "A cross-platform RPC library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "network-run" = callPackage @@ -187004,7 +184371,6 @@ self: { description = "ByteString and Text streams for networking"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "network-topic-models" = callPackage @@ -187027,7 +184393,6 @@ self: { description = "A few network topic model implementations for bayes-stack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "network-transport" = callPackage @@ -187299,7 +184664,6 @@ self: { description = "WebSocket library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "networked-game" = callPackage @@ -187568,7 +184932,6 @@ self: { description = "A mailgun backend for the newsletter package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "newsynth" = callPackage @@ -187689,8 +185052,6 @@ self: { ]; description = "Newtype Wrapper Zoo"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "newtyper" = callPackage @@ -187797,7 +185158,6 @@ self: { description = "Ngrams loader based on http://www.ngrams.info format"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ngx-export" = callPackage @@ -187852,7 +185212,6 @@ self: { description = "More extra tools for Nginx haskell module"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "niagra" = callPackage @@ -187987,7 +185346,6 @@ self: { description = "Command line utility publishes Nike+ runs on blogs and Twitter"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "nimber" = callPackage @@ -188038,7 +185396,6 @@ self: { description = "IDL compiler and RPC/distributed object framework for microservices"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "nist-beacon" = callPackage @@ -188293,8 +185650,6 @@ self: { ]; description = "Lightweight dependency management with Nix"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "nix-tools" = callPackage @@ -188522,7 +185877,6 @@ self: { description = "NLP scoring command-line programs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "nm" = callPackage @@ -188730,8 +186084,6 @@ self: { ]; description = "A static site generator"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "nom" = callPackage @@ -189206,8 +186558,6 @@ self: { benchmarkHaskellDepends = [ base bytestring criterion deepseq ]; description = "Normalization insensitive string comparison"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "normalize" = callPackage @@ -189389,7 +186739,6 @@ self: { description = "Binding for notmuch MUA library"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) notmuch;}; "notmuch-web" = callPackage @@ -189428,7 +186777,6 @@ self: { description = "A web interface to the notmuch email indexer"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "notzero" = callPackage @@ -189767,8 +187115,6 @@ self: { testHaskellDepends = [ base vector ]; description = "Multidimensional arrays, Linear algebra, Numerical analysis"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "null-canvas" = callPackage @@ -190019,7 +187365,6 @@ self: { description = "Ode solvers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "numeric-prelude" = callPackage @@ -190124,7 +187469,6 @@ self: { description = "core package for Numerical Haskell project"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "numericpeano" = callPackage @@ -190221,7 +187565,6 @@ self: { description = "Laws and tests for numhask"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "numhask-histogram" = callPackage @@ -190239,7 +187582,6 @@ self: { description = "See readme.md"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "numhask-prelude" = callPackage @@ -190275,7 +187617,6 @@ self: { description = "Numbers that are range representations"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "numhask-space" = callPackage @@ -190313,7 +187654,6 @@ self: { description = "Laws and tests for numhask"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "nums" = callPackage @@ -190552,7 +187892,6 @@ self: { description = "An interactive GUI for manipulating L-systems"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "nyx-game" = callPackage @@ -190752,7 +188091,6 @@ self: { description = "Communicate to OBD interfaces over ELM327"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "obdd" = callPackage @@ -190770,7 +188108,6 @@ self: { description = "Ordered Reduced Binary Decision Diagrams"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "oberon0" = callPackage @@ -190791,7 +188128,6 @@ self: { description = "Oberon0 Compiler"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "obj" = callPackage @@ -190812,7 +188148,6 @@ self: { description = "Reads and writes obj models"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "objectid" = callPackage @@ -190834,7 +188169,6 @@ self: { description = "Rather unique identifier for things that need to be stored"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "objective" = callPackage @@ -190962,7 +188296,6 @@ self: { description = "Owned channels in the Ownership Monad"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ochintin-daicho" = callPackage @@ -191004,7 +188337,6 @@ self: { description = "Parse Rocket League replays"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "octohat" = callPackage @@ -191036,7 +188368,6 @@ self: { description = "A tested, minimal wrapper around GitHub's API"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "octopus" = callPackage @@ -191058,7 +188389,6 @@ self: { description = "Lisp with more dynamism, more power, more simplicity"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "oculus" = callPackage @@ -191079,7 +188409,6 @@ self: { "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" ]; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) libGL; inherit (pkgs.xorg) libX11; inherit (pkgs.xorg) libXinerama; ovr = null; inherit (pkgs) systemd;}; @@ -191164,7 +188493,6 @@ self: { description = "A full-featured PostgreSQL-backed job queue (with an admin UI)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "oden-go-packages" = callPackage @@ -191252,7 +188580,6 @@ self: { description = "A parser for simplified-syntax OFF files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ofx" = callPackage @@ -191309,7 +188636,6 @@ self: { description = "Interface to the Ohloh API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "oi" = callPackage @@ -191368,7 +188694,6 @@ self: { description = "wrapper for OIS input manager for use with hogre"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {OIS = null;}; "old-locale" = callPackage @@ -191433,7 +188758,6 @@ self: { description = "An OpenLayers JavaScript Wrapper and Webframework with snaplet-fay"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "om-actor" = callPackage @@ -191822,7 +189146,6 @@ self: { description = "See readme.md"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "online-csv" = callPackage @@ -191842,7 +189165,6 @@ self: { description = "See readme.md"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "only" = callPackage @@ -192004,8 +189326,6 @@ self: { ]; description = "A monad transformer for Opaleye"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "open-adt" = callPackage @@ -192043,7 +189363,6 @@ self: { description = "Open algebraic data type examples"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "open-browser" = callPackage @@ -192138,8 +189457,6 @@ self: { benchmarkHaskellDepends = [ base criterion ]; description = "Open type representations and dynamic types"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "open-union" = callPackage @@ -192155,7 +189472,6 @@ self: { description = "Extensible, type-safe unions"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "open-witness" = callPackage @@ -192214,8 +189530,6 @@ self: { ]; description = "Unofficial OpenAI servant types"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "openapi-petstore" = callPackage @@ -192751,7 +190065,6 @@ self: { description = "Fetch OpenSSH keys from a GitHub team"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "openssh-protocol" = callPackage @@ -193193,7 +190506,6 @@ self: { description = "Jaeger backend for OpenTracing"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "opentracing-wai" = callPackage @@ -193236,7 +190548,6 @@ self: { description = "Zipkin V1 backend for OpenTracing"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "opentracing-zipkin-v2" = callPackage @@ -193295,8 +190606,6 @@ self: { ]; description = "Access data at OpenWeatherMap"; license = lib.licenses.publicDomain; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "operate-do" = callPackage @@ -193664,7 +190973,6 @@ self: { description = "Command-line arguments parsing for Hasql"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "optimal-blocks" = callPackage @@ -193690,7 +190998,6 @@ self: { description = "Optimal Block boundary determination for rsync-like behaviours"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "optimization" = callPackage @@ -193727,7 +191034,6 @@ self: { description = "A supercompiler for f-lite"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "option" = callPackage @@ -193876,8 +191182,6 @@ self: { ]; description = "An enum-text based toolkit for optparse-applicative"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "optparse-generic" = callPackage @@ -194037,7 +191341,6 @@ self: { description = "Haskell Wiki Library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "orchid-demo" = callPackage @@ -194058,7 +191361,6 @@ self: { description = "Haskell Wiki Demo"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ord-adhoc" = callPackage @@ -194087,7 +191389,6 @@ self: { description = "Algorithms for the order maintenance problem with a safe interface"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "order-statistic-tree" = callPackage @@ -194134,6 +191435,7 @@ self: { description = "A definition of Posets"; license = "unknown"; hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "ordered-containers" = callPackage @@ -194256,7 +191558,6 @@ self: { description = "Lucid integration for org-mode"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "org2anki" = callPackage @@ -194657,7 +191958,6 @@ self: { description = "Download Open Street Map tiles"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "oso2pdf" = callPackage @@ -194740,7 +192040,6 @@ self: { description = "OTP Authenticator (a la google) command line client"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ottparse-pretty" = callPackage @@ -195196,7 +192495,6 @@ self: { description = "Controlling padKONTROL native mode"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "paddle" = callPackage @@ -195398,7 +192696,6 @@ self: { description = "Bilinear pairings"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "palette" = callPackage @@ -195465,7 +192762,6 @@ self: { description = "Parse syslog traffic from PAN-OS"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "panda" = callPackage @@ -195487,7 +192783,6 @@ self: { description = "A simple static blog engine"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pandoc" = callPackage @@ -195653,8 +192948,6 @@ self: { executableHaskellDepends = [ base csv pandoc pandoc-types ]; description = "Convert CSV to Pandoc Table Markdown"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pandoc-dhall-decoder" = callPackage @@ -195826,7 +193119,6 @@ self: { description = "Japanese-specific markup filters for pandoc"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pandoc-lens" = callPackage @@ -195926,8 +193218,6 @@ self: { testToolDepends = [ hspec-discover ]; description = "Render and insert PlantUML diagrams with Pandoc"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pandoc-plot" = callPackage @@ -196388,7 +193678,6 @@ self: { description = "Reasonable default import"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "papa-base" = callPackage @@ -196403,7 +193692,6 @@ self: { description = "Prelude with only useful functions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "papa-base-export" = callPackage @@ -196429,7 +193717,6 @@ self: { description = "Useful base functions reimplemented"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "papa-bifunctors" = callPackage @@ -196490,7 +193777,6 @@ self: { description = "Reasonable default import"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "papa-implement" = callPackage @@ -196513,7 +193799,6 @@ self: { description = "Reasonable default import"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "papa-include" = callPackage @@ -196673,7 +193958,6 @@ self: { description = "Prelude with only useful functions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "papa-semigroupoids-export" = callPackage @@ -196806,7 +194090,6 @@ self: { description = "The Haskell library and examples for the kids programming robot paprika"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "par-dual" = callPackage @@ -196979,8 +194262,6 @@ self: { ]; description = "Classes and data structures for working with data-kind indexed types"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "paramtree" = callPackage @@ -197051,7 +194332,6 @@ self: { description = "Generalised parser combinators - Attoparsec interface"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "parco-parsec" = callPackage @@ -197064,7 +194344,6 @@ self: { description = "Generalised parser combinators - Parsec interface"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "parcom-lib" = callPackage @@ -197111,7 +194390,6 @@ self: { description = "Examples to accompany the book \"Parallel and Concurrent Programming in Haskell\""; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pareto" = callPackage @@ -197171,8 +194449,6 @@ self: { ]; description = "Help Manage project specific documentation"; license = lib.licenses.agpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "parport" = callPackage @@ -197210,7 +194486,6 @@ self: { description = "Streaming Parquet reader"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "parse-dimacs" = callPackage @@ -197259,7 +194534,6 @@ self: { description = "generate command line arguments from a --help output"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "parseargs" = callPackage @@ -197728,7 +195002,6 @@ self: { description = "NMR-STAR file format parser"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "parsimony" = callPackage @@ -197849,7 +195122,6 @@ self: { description = "Haskell 98 Partial Lenses"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "partial-order" = callPackage @@ -198047,6 +195319,7 @@ self: { description = "Deterministic password generator core"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "password" = callPackage @@ -198648,7 +195921,6 @@ self: { description = "Common patterns in message-oriented applications"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pava" = callPackage @@ -198844,7 +196116,6 @@ self: { description = "Convert a pcap into an enumerator"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pcapng" = callPackage @@ -198875,7 +196146,6 @@ self: { ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pcd-loader" = callPackage @@ -198920,7 +196190,6 @@ self: { description = "A one file compiler for PCF"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pcf-font" = callPackage @@ -198953,7 +196222,6 @@ self: { description = "Template Haskell for embedding text rendered using PCF fonts"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pcg-random" = callPackage @@ -199107,7 +196375,6 @@ self: { description = "Tool to generate PDF from haskintex templates and YAML input"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pdf-slave-server" = callPackage @@ -199181,8 +196448,6 @@ self: { ]; description = "A collection of tools for processing PDF files"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pdf-toolbox-core" = callPackage @@ -199208,8 +196473,6 @@ self: { ]; description = "A collection of tools for processing PDF files"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pdf-toolbox-document" = callPackage @@ -199231,8 +196494,6 @@ self: { ]; description = "A collection of tools for processing PDF files"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pdf-toolbox-viewer" = callPackage @@ -199380,7 +196641,6 @@ self: { description = "Experiemental library for composable interactive programs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "peano" = callPackage @@ -199431,7 +196691,6 @@ self: { description = "pec embedded compiler"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pecoff" = callPackage @@ -199540,7 +196799,6 @@ self: { description = "Package to solve the Generalized Pell Equation"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pem" = callPackage @@ -199646,7 +196904,6 @@ self: { description = "Extensible double-entry accounting system"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "penny-bin" = callPackage @@ -199666,7 +196923,6 @@ self: { description = "Deprecated - use penny package instead"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "penny-lib" = callPackage @@ -199689,7 +196945,6 @@ self: { description = "Deprecated - use penny package instead"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "penrose" = callPackage @@ -199726,7 +196981,6 @@ self: { description = "Create beautiful diagrams just by typing mathematical notation in plain text"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "peparser" = callPackage @@ -199739,7 +196993,6 @@ self: { description = "A parser for PE object files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "percent-encoder" = callPackage @@ -199813,8 +197066,6 @@ self: { benchmarkToolDepends = [ cpphs ]; description = "Find duplicate images"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "perdure" = callPackage @@ -199904,7 +197155,6 @@ self: { description = "analysis example using perf"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "perfect-hash-generator" = callPackage @@ -199984,7 +197234,6 @@ self: { description = "A perfect hashing library for mapping bytestrings to values"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "perhaps" = callPackage @@ -200060,7 +197309,6 @@ self: { description = "Periodic task system haskell client"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "periodic-client-exe" = callPackage @@ -200086,7 +197334,6 @@ self: { description = "Periodic task system haskell client executables"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "periodic-common" = callPackage @@ -200146,7 +197393,6 @@ self: { description = "Periodic task system haskell server"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "perm" = callPackage @@ -200164,7 +197410,6 @@ self: { description = "permutation Applicative and Monad with many mtl instances"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "permutation" = callPackage @@ -200411,7 +197656,6 @@ self: { description = "Parses a Persist Model file and produces Audit Models"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "persistent-cereal" = callPackage @@ -200473,6 +197717,8 @@ self: { testToolDepends = [ hspec-discover ]; description = "Persistent module discover utilities"; license = lib.licenses.bsd3; + hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "persistent-documentation" = callPackage @@ -200534,7 +197780,6 @@ self: { description = "Declare Persistent entities using SQL SELECT query syntax"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "persistent-instances-iproute" = callPackage @@ -200579,7 +197824,6 @@ self: { description = "A thread-safe (STM) persistency interface for finite map types"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "persistent-migration" = callPackage @@ -201181,8 +198425,6 @@ self: { ]; description = "Tests for Persistent"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "persistent-test_2_13_0_0" = callPackage @@ -201209,7 +198451,6 @@ self: { description = "Tests for Persistent"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "persistent-typed-db" = callPackage @@ -201276,8 +198517,6 @@ self: { benchmarkHaskellDepends = [ base containers criterion deepseq ]; description = "A persistent sequence based on array mapped tries"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "persistent-zookeeper" = callPackage @@ -201349,7 +198588,6 @@ self: { description = "Persona (BrowserID) Identity Provider"; license = lib.licenses.agpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pesca" = callPackage @@ -201393,7 +198631,6 @@ self: { description = "Pretty Easy YOshikuni-made TLS library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "peyotls-codec" = callPackage @@ -201412,7 +198649,6 @@ self: { description = "Codec parts of Pretty Easy YOshikuni-made TLS library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pez" = callPackage @@ -201576,7 +198812,6 @@ self: { description = "A postgresql-simple transaction monad"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pgdl" = callPackage @@ -201666,7 +198901,6 @@ self: { description = "A mid-level PostgreSQL client library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pgstream" = callPackage @@ -201956,7 +199190,6 @@ self: { description = "A generalization of the uniqueness-periods-vector-examples functionality"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "phonetic-languages-filters-array" = callPackage @@ -202234,7 +199467,6 @@ self: { description = "Simplified and somewhat optimized version of the phonetic-languages-examples"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "phonetic-languages-simplified-properties-array" = callPackage @@ -202341,7 +199573,6 @@ self: { description = "Functional user interfaces"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "photoname" = callPackage @@ -202364,7 +199595,6 @@ self: { description = "Rename photo image files based on EXIF shoot date"; license = lib.licenses.isc; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "phraskell" = callPackage @@ -202565,7 +199795,6 @@ self: { description = "Remotely controlling Java Swing applications"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "picedit" = callPackage @@ -202728,7 +199957,6 @@ self: { description = "Yet another Haskell build system"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pier-core" = callPackage @@ -202821,8 +200049,6 @@ self: { ]; description = "Access to the Pinboard API"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pinboard-notes-backup" = callPackage @@ -202889,8 +200115,6 @@ self: { ]; description = "A code generator for the pinch Thrift library"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pinchot" = callPackage @@ -202953,7 +200177,6 @@ self: { description = "icmp echo requests"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ping-parser-attoparsec" = callPackage @@ -203046,7 +200269,6 @@ self: { description = "A gateway for various cloud notification services"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pipe-enumerator" = callPackage @@ -203059,7 +200281,6 @@ self: { description = "A bidirectional bridge between pipes and iteratees"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pipeclip" = callPackage @@ -203233,7 +200454,6 @@ self: { description = "Streaming parsing in the pipes-core framework with Attoparsec"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pipes-bgzf" = callPackage @@ -203305,7 +200525,6 @@ self: { description = "Brotli (RFC7932) compressors and decompressors for the Pipes package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pipes-bytestring" = callPackage @@ -203362,7 +200581,6 @@ self: { description = "Pipes for Noise-secured network connections"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pipes-category" = callPackage @@ -203456,7 +200674,6 @@ self: { description = "A streaming serialization library on top of \"pipes\" and \"cereal-plus\""; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pipes-cliff" = callPackage @@ -203504,7 +200721,6 @@ self: { description = "Conduit adapters"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pipes-core" = callPackage @@ -203534,7 +200750,6 @@ self: { description = "Pipes utilities for interfacing with the courier message-passing framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pipes-csv" = callPackage @@ -203597,7 +200812,6 @@ self: { description = "Various basic utilities for Pipes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pipes-extras" = callPackage @@ -203659,7 +200873,6 @@ self: { description = "Fast traversal of directory trees using pipes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pipes-fluid" = callPackage @@ -203733,7 +200946,6 @@ self: { description = "Illumina NGS data processing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pipes-interleave" = callPackage @@ -203806,7 +201018,6 @@ self: { description = "Streaming processing of CSV files preceded by key-value pairs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pipes-lines" = callPackage @@ -203874,8 +201085,6 @@ self: { testHaskellDepends = [ base monad-control mongoDB pipes text ]; description = "Stream results from MongoDB"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pipes-network" = callPackage @@ -203952,7 +201161,6 @@ self: { description = "P2P network nodes with pipes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pipes-p2p-examples" = callPackage @@ -203972,7 +201180,6 @@ self: { description = "Examples using pipes-p2p"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pipes-parse" = callPackage @@ -204294,7 +201501,6 @@ self: { description = "A dependently typed core language"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pit" = callPackage @@ -204340,7 +201546,6 @@ self: { description = "Pitch tracking library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pivotal-tracker" = callPackage @@ -204458,8 +201663,6 @@ self: { ]; description = "Pixiv API binding based on servant-client"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "piyo" = callPackage @@ -204571,7 +201774,6 @@ self: { description = "Package tree diff tool"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pktree" = callPackage @@ -204793,7 +201995,6 @@ self: { description = "Planet Mitchell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "planet-mitchell-test" = callPackage @@ -204997,7 +202198,6 @@ self: { description = "plot data from stdin through socketed"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "plot" = callPackage @@ -205227,8 +202427,6 @@ self: { ]; description = "Dynamic linking for Haskell and C objects"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "plugins-auto" = callPackage @@ -205364,7 +202562,6 @@ self: { description = "read/write png file"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pngload" = callPackage @@ -205382,7 +202579,6 @@ self: { description = "Pure Haskell loader for PNG images"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pngload-fixed" = callPackage @@ -205460,7 +202656,6 @@ self: { description = "Multi-backend (zookeeper and sqlite) DNS Server using persistent-library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "point-octree" = callPackage @@ -205480,7 +202675,6 @@ self: { description = "Point octree, with bounding boxes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pointed" = callPackage @@ -205632,7 +202826,6 @@ self: { description = "Pointless Lenses library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pointless-rewrite" = callPackage @@ -205649,7 +202842,6 @@ self: { description = "Pointless Rewrite library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "poke" = callPackage @@ -205682,7 +202874,6 @@ self: { description = "Discord verification bot"; license = lib.licenses.mpl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pokemon-go-protobuf-types" = callPackage @@ -205792,7 +202983,6 @@ self: { description = "A library for manipulating the historical dictionary of Polish (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "policeman" = callPackage @@ -205942,7 +203132,6 @@ self: { description = "Wrap together data and it's constraints"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polydata-core" = callPackage @@ -206094,7 +203283,6 @@ self: { description = "Experimental, RandomFu effect and interpreters for polysemy"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysemy-chronos" = callPackage @@ -206116,8 +203304,6 @@ self: { ]; description = "Polysemy effect for chronos"; license = "BSD-2-Clause-Patent"; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysemy-conc" = callPackage @@ -206141,8 +203327,6 @@ self: { ]; description = "Polysemy Effects for Concurrency"; license = "BSD-2-Clause-Patent"; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysemy-extra" = callPackage @@ -206159,7 +203343,6 @@ self: { description = "Extra Input and Output functions for polysemy.."; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysemy-fs" = callPackage @@ -206191,7 +203374,6 @@ self: { description = "Run a KVStore as a filesystem in polysemy"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysemy-http" = callPackage @@ -206221,8 +203403,6 @@ self: { ]; description = "Polysemy effect for http-client"; license = "BSD-2-Clause-Patent"; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysemy-kvstore-jsonfile" = callPackage @@ -206240,7 +203420,6 @@ self: { description = "Run a KVStore as a single json file in polysemy"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysemy-log" = callPackage @@ -206264,8 +203443,6 @@ self: { ]; description = "Polysemy effects for logging"; license = "BSD-2-Clause-Patent"; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysemy-log-co" = callPackage @@ -206289,7 +203466,6 @@ self: { description = "polysemy-log interpreter for co-log"; license = "BSD-2-Clause-Patent"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysemy-log-di" = callPackage @@ -206311,8 +203487,6 @@ self: { ]; description = "polysemy-log interpreter for di"; license = "BSD-2-Clause-Patent"; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysemy-methodology" = callPackage @@ -206329,7 +203503,6 @@ self: { description = "Domain modelling algebra for polysemy"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysemy-methodology-composite" = callPackage @@ -206347,7 +203520,6 @@ self: { description = "Functions for using polysemy-methodology with composite"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysemy-mocks" = callPackage @@ -206375,7 +203547,6 @@ self: { description = "Optics for Polysemy"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysemy-path" = callPackage @@ -206392,7 +203563,6 @@ self: { description = "Polysemy versions of Path functions"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysemy-plugin" = callPackage @@ -206433,8 +203603,6 @@ self: { ]; description = "Polysemy error tracking"; license = "BSD-2-Clause-Patent"; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysemy-test" = callPackage @@ -206459,8 +203627,6 @@ self: { ]; description = "Polysemy effects for testing"; license = "BSD-2-Clause-Patent"; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysemy-time" = callPackage @@ -206484,8 +203650,6 @@ self: { ]; description = "Polysemy effect for time"; license = "BSD-2-Clause-Patent"; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysemy-video" = callPackage @@ -206512,7 +203676,6 @@ self: { description = "Functions for mapping vinyl records in polysemy"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysemy-webserver" = callPackage @@ -206581,7 +203744,6 @@ self: { description = "Taming Selective Strictness"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polysoup" = callPackage @@ -206620,7 +203782,6 @@ self: { description = "Utilities for polytypeable"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "polyvariadic" = callPackage @@ -206658,8 +203819,6 @@ self: { ]; description = "Maps and sets of partial orders"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pomodoro" = callPackage @@ -206679,7 +203838,6 @@ self: { description = "pomodoro timer"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pomohoro" = callPackage @@ -206805,8 +203963,6 @@ self: { ]; description = "An XMPP client library"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pontarius-xmpp-extras" = callPackage @@ -206931,7 +204087,6 @@ self: { description = "popenhs is a popen-like library for Haskell"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "popkey" = callPackage @@ -207032,7 +204187,6 @@ self: { description = "Express portable, composable and reusable data tasks and pipelines"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "porcupine-http" = callPackage @@ -207062,7 +204216,6 @@ self: { description = "A location accessor for porcupine to connect to HTTP sources/sinks"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "porcupine-s3" = callPackage @@ -207094,7 +204247,6 @@ self: { description = "A location accessor for porcupine to connect to AWS S3 sources/sinks"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "porpoise" = callPackage @@ -207223,7 +204375,6 @@ self: { description = "The Haskell Ports Library"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ports-tools" = callPackage @@ -207259,7 +204410,6 @@ self: { description = "Simple extensible library to run SQL file against PostgreSQL database"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "poseidon-postgis" = callPackage @@ -207281,7 +204431,6 @@ self: { description = "Extension of Poseidon library for Postgis (Spatial and Geographic objects for PostgreSQL)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "positive" = callPackage @@ -207939,7 +205088,6 @@ self: { description = "Sql interpolating quasiquote plus some kind of primitive ORM using it"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "postgresql-schema" = callPackage @@ -208053,8 +205201,6 @@ self: { testHaskellDepends = [ base bytestring hspec postgresql-simple ]; description = "PostgreSQL Schema Migrations"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "postgresql-simple-named" = callPackage @@ -208125,7 +205271,6 @@ self: { description = "A PostgreSQL backed queue"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "postgresql-simple-sop" = callPackage @@ -208156,7 +205301,6 @@ self: { description = "Typed extension for PostgreSQL simple"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "postgresql-simple-url" = callPackage @@ -208203,8 +205347,6 @@ self: { ]; description = "PostgreSQL AST parsing and rendering"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "postgresql-transactional" = callPackage @@ -208260,7 +205402,6 @@ self: { description = "postgresql-tx interfacing for use with postgresql-query"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "postgresql-tx-simple" = callPackage @@ -208293,7 +205434,6 @@ self: { description = "postgresql-tx interfacing for use with squeal-postgresql"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "postgresql-tx-squeal-compat-simple" = callPackage @@ -208308,7 +205448,6 @@ self: { description = "Connection interop from postgresql-simple connections to postgresql-libpq connections"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "postgresql-typed" = callPackage @@ -208479,7 +205618,6 @@ self: { description = "Library for postmarkapp.com HTTP Api"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "postmark-streams" = callPackage @@ -208547,7 +205685,6 @@ self: { description = "Simple streaming in IO"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "potoki-cereal" = callPackage @@ -208571,7 +205708,6 @@ self: { description = "Streaming serialization"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "potoki-conduit" = callPackage @@ -208595,7 +205731,6 @@ self: { description = "Integration of \"potoki\" and \"conduit\""; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "potoki-core" = callPackage @@ -208641,7 +205776,6 @@ self: { description = "Integration of \"potoki\" and \"hasql\""; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "potoki-zlib" = callPackage @@ -208656,7 +205790,6 @@ self: { description = "Streaming ZLib decompression"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "potrace" = callPackage @@ -208686,8 +205819,6 @@ self: { libraryHaskellDepends = [ base diagrams-lib JuicyPixels potrace ]; description = "Potrace bindings for the diagrams library"; license = lib.licenses.gpl2Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "powermate" = callPackage @@ -208790,7 +205921,6 @@ self: { description = "A Amazon SQS backend for powerqueue"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ppm" = callPackage @@ -208879,7 +206009,6 @@ self: { description = "Fully encapsulated monad transformers with queuelike functionality"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "practice-room" = callPackage @@ -208899,7 +206028,6 @@ self: { description = "Practice Room"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "praglude" = callPackage @@ -209028,7 +206156,6 @@ self: { description = "Simple cached predicates"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pred-trie" = callPackage @@ -209058,7 +206185,6 @@ self: { description = "Predicative tries"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "predicate-class" = callPackage @@ -209083,8 +206209,6 @@ self: { libraryHaskellDepends = [ adjunctions base deepseq lens mtl ]; description = "A library for writing predicates and transformations over predicates in Haskell"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "predicate-typed" = callPackage @@ -209181,7 +206305,6 @@ self: { description = "Tests and QuickCheck generators to accompany prednote"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "prefetch" = callPackage @@ -209552,7 +206675,6 @@ self: { description = "An HDBC connector for Presto"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "prettify" = callPackage @@ -209845,8 +206967,6 @@ self: { testHaskellDepends = [ base hspec tagged ]; description = "A small pretty printing DSL for complex types"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "prettyFunctionComposing" = callPackage @@ -209992,8 +207112,6 @@ self: { libraryHaskellDepends = [ base lucid prettyprinter text ]; description = "A prettyprinter backend for lucid"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "prettyprinter-vty" = callPackage @@ -210025,7 +207143,6 @@ self: { description = "The method of previewing data (instead of wholly show-ing it)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "prim" = callPackage @@ -210126,8 +207243,6 @@ self: { ]; description = "Primeval world of Haskell"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "primal-memory" = callPackage @@ -210147,8 +207262,6 @@ self: { ]; description = "Unified interface for memory managemenet"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "prime" = callPackage @@ -210286,8 +207399,6 @@ self: { ]; description = "containers backed by arrays"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "primitive-convenience" = callPackage @@ -210417,8 +207528,6 @@ self: { benchmarkHaskellDepends = [ base gauge ghc-prim primitive random ]; description = "Sort primitive arrays"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "primitive-stablename" = callPackage @@ -210499,7 +207608,6 @@ self: { description = "ImageBoard on Happstack and HSP"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "primula-bot" = callPackage @@ -210519,7 +207627,6 @@ self: { description = "Jabber-bot for primula-board ImageBoard"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pringletons" = callPackage @@ -210786,7 +207893,6 @@ self: { description = "Parse process information for Linux"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "proc-net" = callPackage @@ -210877,7 +207983,6 @@ self: { description = "IterIO Process Library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "process-leksah" = callPackage @@ -210926,7 +208031,6 @@ self: { description = "Run a process and do reportsing on its progress"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "process-qq" = callPackage @@ -210944,7 +208048,6 @@ self: { description = "Quasi-Quoters for exec process"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "process-sequential" = callPackage @@ -210988,7 +208091,6 @@ self: { description = "Streaming interface to system processes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "processing" = callPackage @@ -211127,7 +208229,6 @@ self: { description = "Simple streaming datatype"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "product" = callPackage @@ -211202,7 +208303,6 @@ self: { description = "Convert GHC profiles into GraphViz's dot format"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "prof2pretty" = callPackage @@ -211426,7 +208526,6 @@ self: { description = "Progressbar API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "progression" = callPackage @@ -211550,7 +208649,6 @@ self: { description = "Relational Algebra Engine"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "project-template" = callPackage @@ -211634,8 +208732,6 @@ self: { ]; description = "Profunctor-based lightweight implementation of optics"; license = lib.licenses.mpl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "prolog" = callPackage @@ -211708,7 +208804,6 @@ self: { description = "Better, more general Prelude exporting common utilities"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "prolude" = callPackage @@ -211731,7 +208826,6 @@ self: { description = "ITProTV's custom prelude"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "prometheus" = callPackage @@ -211803,7 +208897,6 @@ self: { description = "Instrument applications with metrics and publish/push to Prometheus"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "prometheus-metrics-ghc" = callPackage @@ -211942,7 +209035,6 @@ self: { description = "Functional synthesis of images and animations"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "propeller" = callPackage @@ -212033,7 +209125,6 @@ self: { description = "A library for functional GUI development"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "props" = callPackage @@ -212092,7 +209183,6 @@ self: { description = "A DSL for processing Prosidy documents"; license = lib.licenses.mpl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "prospect" = callPackage @@ -212209,7 +209299,6 @@ self: { description = "neovim project manager"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "proto-lens" = callPackage @@ -212288,7 +209377,6 @@ self: { description = "Protocol buffers for describing the definitions of messages"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "proto-lens-jsonpb" = callPackage @@ -212432,7 +209520,6 @@ self: { description = "A low level library for writing out data in the Protocol Buffers wire format"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "proto3-wire" = callPackage @@ -212456,8 +209543,6 @@ self: { ]; description = "A low-level implementation of the Protocol Buffers (version 3) wire format"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "protobuf" = callPackage @@ -212503,7 +209588,6 @@ self: { description = "Protocol Buffers via C++"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "protobuf-simple" = callPackage @@ -212592,7 +209676,6 @@ self: { description = "Text.DescriptorProto.Options and code generated from the Google Protocol Buffer specification"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "protocol-buffers-fork" = callPackage @@ -212697,7 +209780,6 @@ self: { ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "proton-haskell" = callPackage @@ -212881,7 +209963,6 @@ self: { description = "Language support for the PureScript programming language"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pseudo-boolean" = callPackage @@ -212906,8 +209987,6 @@ self: { ]; description = "Reading/Writing OPB/WBO files used in pseudo boolean competition"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pseudo-trie" = callPackage @@ -213256,7 +210335,6 @@ self: { description = "A CLI assistant"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pugixml" = callPackage @@ -213333,7 +210411,6 @@ self: { description = "Portable Haskell/POSIX layer for Pugs"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pugs-hsregex" = callPackage @@ -213346,7 +210423,6 @@ self: { description = "Haskell PCRE binding"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pulse" = callPackage @@ -213404,7 +210480,6 @@ self: { description = "Multilingual unsupervised sentence tokenization with Punkt"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "punycode" = callPackage @@ -213440,7 +210515,6 @@ self: { description = "A program that displays the puppet resources associated to a node given .pp files."; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pure-cdb" = callPackage @@ -213460,7 +210534,6 @@ self: { description = "Another pure-haskell CDB (Constant Database) implementation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pure-fft" = callPackage @@ -213519,7 +210592,6 @@ self: { description = "Tests for the pure-priority-queue package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pure-shuffle" = callPackage @@ -213631,8 +210703,6 @@ self: { testHaskellDepends = [ base ]; description = "Simple Routing functions for Wai Applications"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "purescript" = callPackage @@ -213708,7 +210778,6 @@ self: { description = "PureScript Programming Language Compiler"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "purescript-ast" = callPackage @@ -213726,8 +210795,6 @@ self: { ]; description = "PureScript Programming Language Abstract Syntax Tree"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "purescript-bridge" = callPackage @@ -213821,7 +210888,6 @@ self: { description = "Isomorphic trivial data type definitions over JSON"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "purescript-tsd-gen" = callPackage @@ -213845,7 +210911,6 @@ self: { description = "TypeScript Declaration File (.d.ts) generator for PureScript"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pursuit-client" = callPackage @@ -213907,7 +210972,6 @@ self: { description = "A server-side library for sending push notifications"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "push-notify-apn" = callPackage @@ -213934,7 +210998,6 @@ self: { description = "Send push notifications to mobile iOS devices"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "push-notify-ccs" = callPackage @@ -213955,7 +211018,6 @@ self: { description = "A server-side library for sending/receiving push notifications through CCS (Google Cloud Messaging)"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "push-notify-general" = callPackage @@ -213975,7 +211037,6 @@ self: { description = "A general library for sending/receiving push notif. through dif. services."; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pushbullet" = callPackage @@ -214165,7 +211226,6 @@ self: { description = "Creating graphics for pencil puzzles"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "puzzle-draw-cmdline" = callPackage @@ -214185,7 +211245,6 @@ self: { description = "Creating graphics for pencil puzzles, command line tools"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "pvar" = callPackage @@ -214224,7 +211283,6 @@ self: { description = "A photo viewer daemon application with remote controlling abilities"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) libdevil;}; "pvss" = callPackage @@ -214451,7 +211509,6 @@ self: { description = "'Vec' instances for 'qd' types"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "qed" = callPackage @@ -214496,7 +211553,6 @@ self: { description = "Command line tool qhs, SQL queries on CSV and TSV files"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "qhull-simple" = callPackage @@ -214676,7 +211732,6 @@ self: { description = "Library to generate QR codes from bytestrings and objects and scale image files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "qrcode" = callPackage @@ -214984,7 +212039,6 @@ self: { description = "Retrieve, store and manage real quantum random data"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quarantimer" = callPackage @@ -215072,7 +212126,6 @@ self: { description = "Analysis and parsing library for SQL queries"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "queryparser-demo" = callPackage @@ -215090,7 +212143,6 @@ self: { description = "Demo package containing queryparser examples"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "queryparser-hive" = callPackage @@ -215111,7 +212163,6 @@ self: { description = "Parsing for Hive SQL queries"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "queryparser-presto" = callPackage @@ -215132,7 +212183,6 @@ self: { description = "Parsing for Presto SQL queries"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "queryparser-vertica" = callPackage @@ -215153,7 +212203,6 @@ self: { description = "Parsing for Vertica SQL queries"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "querystring-pickle" = callPackage @@ -215188,7 +212237,6 @@ self: { description = "A package for prompting values from the command-line"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "queue" = callPackage @@ -215212,7 +212260,6 @@ self: { description = "A library of queuelike data structures, both functional and stateful"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quick-generator" = callPackage @@ -215266,7 +212313,6 @@ self: { description = "quick & easy benchmarking of command-line programs"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quickbooks" = callPackage @@ -215320,8 +212366,6 @@ self: { ]; description = "Generate QuickCheck Gen for Sum Types"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quickcheck-assertions" = callPackage @@ -215461,7 +212505,6 @@ self: { description = "Automating QuickCheck for polymorphic and overlaoded properties"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quickcheck-properties" = callPackage @@ -215515,7 +212558,6 @@ self: { description = "Generate regex-constrained strings for QuickCheck"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quickcheck-relaxng" = callPackage @@ -215532,7 +212574,6 @@ self: { description = "Generate RelaxNG-constrained XML documents for QuickCheck"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quickcheck-rematch" = callPackage @@ -215639,7 +212680,6 @@ self: { description = "Test monadic programs using state machine based models"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quickcheck-state-machine-distributed" = callPackage @@ -215664,7 +212704,6 @@ self: { description = "Test monadic programs using state machine based models"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quickcheck-string-random" = callPackage @@ -215681,8 +212720,6 @@ self: { ]; description = "Helper to build generators with Text.StringRandom"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quickcheck-text" = callPackage @@ -215892,7 +212929,6 @@ self: { description = "A reflective batch tester for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quickwebapp" = callPackage @@ -215942,7 +212978,6 @@ self: { description = "Meta-package for Quipper"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quipper-algorithms" = callPackage @@ -215967,7 +213002,6 @@ self: { description = "A set of algorithms implemented in Quipper"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quipper-all" = callPackage @@ -215984,7 +213018,6 @@ self: { description = "Meta-package for Quipper"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quipper-cabal" = callPackage @@ -215997,7 +213030,6 @@ self: { description = "Some functions to aid in the creation of Cabal packages for Quipper"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quipper-core" = callPackage @@ -216036,7 +213068,6 @@ self: { description = "Miscellaneous code snippets that illustrate various Quipper features"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quipper-language" = callPackage @@ -216058,7 +213089,6 @@ self: { description = "Quipper, an embedded functional programming language for quantum computation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quipper-libraries" = callPackage @@ -216082,7 +213112,6 @@ self: { description = "The standard libraries for Quipper"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quipper-rendering" = callPackage @@ -216100,7 +213129,6 @@ self: { description = "An embedded, scalable functional programming language for quantum computing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quipper-tools" = callPackage @@ -216123,7 +213151,6 @@ self: { description = "Miscellaneous stand-alone tools for Quipper"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quipper-utils" = callPackage @@ -216172,7 +213199,6 @@ self: { description = "Binary serialisation support for Quivers"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quiver-bytestring" = callPackage @@ -216185,7 +213211,6 @@ self: { description = "Quiver combinators for bytestring streaming"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quiver-cell" = callPackage @@ -216198,7 +213223,6 @@ self: { description = "Quiver combinators for cellular data processing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quiver-csv" = callPackage @@ -216215,7 +213239,6 @@ self: { description = "Quiver combinators for cellular CSV data processing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quiver-enumerator" = callPackage @@ -216228,7 +213251,6 @@ self: { description = "Bridge between Quiver and Iteratee paradigms"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quiver-groups" = callPackage @@ -216242,7 +213264,6 @@ self: { description = "Group and chunk values within a Quiver"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quiver-http" = callPackage @@ -216261,7 +213282,6 @@ self: { description = "Adapter to stream over HTTP(s) with quiver"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quiver-instances" = callPackage @@ -216278,7 +213298,6 @@ self: { description = "Extra instances for Quiver"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quiver-interleave" = callPackage @@ -216292,7 +213311,6 @@ self: { description = "Interleave values from multiple Quivers"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quiver-sort" = callPackage @@ -216317,7 +213335,6 @@ self: { description = "Sort the values in a quiver"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "quokka" = callPackage @@ -216400,7 +213417,6 @@ self: { description = "Command line binary for working with the Qux language"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "r-glpk-phonetic-languages-ukrainian-durations" = callPackage @@ -216475,8 +213491,6 @@ self: { ]; description = "The raaz cryptographic library"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rabocsv2qif" = callPackage @@ -216702,7 +213716,6 @@ self: { description = "Compiler and editor for the esolang rail"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rails-session" = callPackage @@ -216727,7 +213740,6 @@ self: { description = "Decrypt Ruby on Rails sessions in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rainbow" = callPackage @@ -216759,7 +213771,6 @@ self: { description = "Tests and QuickCheck generators to accompany rainbow"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rainbox" = callPackage @@ -216821,7 +213832,6 @@ self: { description = "distributed-process node"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rakhana" = callPackage @@ -216923,8 +213933,6 @@ self: { benchmarkHaskellDepends = [ base criterion deepseq ]; description = "Random access list with a list compatible interface"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rallod" = callPackage @@ -216938,7 +213946,6 @@ self: { description = "'$' in reverse"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "raml" = callPackage @@ -217175,7 +214182,6 @@ self: { description = "A simple random generator library for effin"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "random-extras" = callPackage @@ -217255,7 +214261,6 @@ self: { description = "Random variate generation from hypergeometric distributions"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "random-names" = callPackage @@ -217493,7 +214498,6 @@ self: { description = "A Range type with vector-space instances"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ranged-list" = callPackage @@ -217645,7 +214649,6 @@ self: { description = "A modular text editor"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rasa-example-config" = callPackage @@ -217666,7 +214669,6 @@ self: { description = "Example user config for Rasa"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rasa-ext-bufs" = callPackage @@ -217682,7 +214684,6 @@ self: { description = "Rasa Ext for useful buffer utilities"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rasa-ext-cmd" = callPackage @@ -217698,7 +214699,6 @@ self: { description = "Rasa Ext for running commands"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rasa-ext-cursors" = callPackage @@ -217715,7 +214715,6 @@ self: { description = "Rasa Ext adding cursor(s)"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rasa-ext-files" = callPackage @@ -217733,7 +214732,6 @@ self: { description = "Rasa Ext for filesystem actions"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rasa-ext-logger" = callPackage @@ -217746,7 +214744,6 @@ self: { description = "Rasa Ext for logging state/actions"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rasa-ext-slate" = callPackage @@ -217764,7 +214761,6 @@ self: { description = "Rasa extension for rendering to terminal with vty"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rasa-ext-status-bar" = callPackage @@ -217777,7 +214773,6 @@ self: { description = "Rasa Ext for populating status-bar"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rasa-ext-style" = callPackage @@ -217790,7 +214785,6 @@ self: { description = "Rasa Ext managing rendering styles"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rasa-ext-views" = callPackage @@ -217808,7 +214802,6 @@ self: { description = "Rasa Ext managing rendering views"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rasa-ext-vim" = callPackage @@ -217828,7 +214821,6 @@ self: { description = "Rasa Ext for vim bindings"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rascal" = callPackage @@ -217977,7 +214969,6 @@ self: { description = "Client for rating.chgk.info API and CSV tables (documentation in Russian)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rating-systems" = callPackage @@ -218136,7 +215127,6 @@ self: { description = "Resource-Aware Feldspar"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "raw-strings-qq" = callPackage @@ -218179,7 +215169,6 @@ self: { description = "Anonymous extensible records"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rawstring-qm" = callPackage @@ -218229,7 +215218,6 @@ self: { description = "Common text/parsing tools for Razom language packages"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rbpcp-api" = callPackage @@ -218266,7 +215254,6 @@ self: { description = "Mask nucleotide (EST) sequences in Fasta format"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rbst" = callPackage @@ -218315,7 +215302,6 @@ self: { description = "Reservoir Computing, fast RNNs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rclient" = callPackage @@ -218427,7 +215413,6 @@ self: { description = "A Haskell wrapper for Rdio's API"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rdtsc" = callPackage @@ -218495,7 +215480,6 @@ self: { description = "Allow react-flux stores to send requests to a servant server"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "react-haskell" = callPackage @@ -218603,7 +215587,6 @@ self: { description = "Programmatically edit MIDI events via ALSA and reactive-banana"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reactive-banana" = callPackage @@ -218645,7 +215628,6 @@ self: { description = "home (etc) automation using reactive-banana"; license = lib.licenses.agpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reactive-banana-bunch" = callPackage @@ -218662,7 +215644,6 @@ self: { description = "Extend reactive-banana to multiple events per time point"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reactive-banana-gi-gtk" = callPackage @@ -218680,7 +215661,6 @@ self: { description = "Simple reactive programming with GTK GObject Introspection"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reactive-banana-sdl" = callPackage @@ -218698,7 +215678,6 @@ self: { description = "Reactive Banana bindings for SDL"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reactive-banana-sdl2" = callPackage @@ -218712,7 +215691,6 @@ self: { description = "Reactive Banana integration with SDL2"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reactive-banana-threepenny" = callPackage @@ -218728,7 +215706,6 @@ self: { description = "Examples for the reactive-banana library, using threepenny-gui"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reactive-banana-wx" = callPackage @@ -218747,7 +215724,6 @@ self: { description = "Examples for the reactive-banana library, using wxHaskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reactive-fieldtrip" = callPackage @@ -218765,7 +215741,6 @@ self: { description = "Connect Reactive and FieldTrip"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reactive-glut" = callPackage @@ -218782,7 +215757,6 @@ self: { description = "Connects Reactive and GLUT"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reactive-haskell" = callPackage @@ -218826,7 +215800,6 @@ self: { description = "Process MIDI events via reactive-banana and JACK"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reactive-midyim" = callPackage @@ -218847,7 +215820,6 @@ self: { description = "Process MIDI events via reactive-banana"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reactive-thread" = callPackage @@ -218901,7 +215873,6 @@ self: { description = "Reactor - task parallel reactive programming"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "read-bounded" = callPackage @@ -219067,7 +216038,6 @@ self: { description = "Readline with variables (setX/getY) wrapped in state vars"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "readme-lhs" = callPackage @@ -219105,7 +216075,6 @@ self: { description = "Read and pretty print Python bytecode (.pyc) files."; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "readshp" = callPackage @@ -219191,7 +216160,6 @@ self: { description = "Animation library based on SVGs"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reanimate-svg" = callPackage @@ -219380,7 +216348,6 @@ self: { description = "Instances of \"aeson\" classes for the \"record\" types"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "record-dot-preprocessor" = callPackage @@ -219440,7 +216407,6 @@ self: { description = "Utilities for working with OpenGL's GLSL shading language and Nikita Volkov's \"Record\"s"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "record-hasfield" = callPackage @@ -219473,7 +216439,6 @@ self: { description = "Compiler preprocessor introducing a syntactic extension for anonymous records"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "record-syntax" = callPackage @@ -219498,7 +216463,6 @@ self: { description = "A library for parsing and processing the Haskell syntax sprinkled with anonymous records"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "record-wrangler" = callPackage @@ -219559,7 +216523,6 @@ self: { description = "Template Haskell declarations for the records package"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "recover-rtti" = callPackage @@ -219610,8 +216573,6 @@ self: { testHaskellDepends = [ base HUnit template-haskell transformers ]; description = "Representing common recursion patterns as higher-order functions"; license = lib.licenses.bsd2; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "recursion-schemes-ext" = callPackage @@ -219631,8 +216592,6 @@ self: { ]; description = "Amateur addenda to recursion-schemes"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "recursion-schemes-ix" = callPackage @@ -219754,7 +216713,6 @@ self: { description = "Library for interfacing with Reddit's API"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "redesigned-carnival" = callPackage @@ -219936,7 +216894,6 @@ self: { description = "Simplify a set of equations by removing redundancies"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reducers" = callPackage @@ -220161,7 +217118,6 @@ self: { description = "A command-line tool for pasting to https://www.refheap.com"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "refined" = callPackage @@ -220323,7 +217279,6 @@ self: { description = "Continuous animations support for reflex"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reflex-backend-socket" = callPackage @@ -220350,7 +217305,6 @@ self: { description = "Reflex bindings for TCP sockets"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reflex-backend-wai" = callPackage @@ -220372,7 +217326,6 @@ self: { description = "Reflex interface to `wai`"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reflex-basic-host" = callPackage @@ -220414,9 +217367,7 @@ self: { ]; description = "Functional Reactive Web Apps with Reflex"; license = lib.licenses.bsd3; - platforms = [ - "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" - ]; + platforms = [ "armv7l-linux" "i686-linux" "x86_64-linux" ]; maintainers = with lib.maintainers; [ maralorn ]; }) {}; @@ -220454,6 +217405,7 @@ self: { description = "A playground for experimenting with infrastructure and common code for reflex applications"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "reflex-dom-core" = callPackage @@ -220513,7 +217465,7 @@ self: { executableHaskellDepends = [ base reflex-dom text ]; description = "A reflex-dom widget to draw on a canvas with a fragment shader program"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; + platforms = [ "armv7l-linux" "i686-linux" "x86_64-linux" ]; }) {}; "reflex-dom-helpers" = callPackage @@ -220531,6 +217483,7 @@ self: { description = "Html tag helpers for reflex-dom"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "reflex-dom-pandoc" = callPackage @@ -220690,7 +217643,6 @@ self: { description = "A GHCi widget library for use in reflex applications"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reflex-gi-gtk" = callPackage @@ -220763,7 +217715,6 @@ self: { description = "A simple scene-graph using reflex and gloss"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reflex-jsx" = callPackage @@ -220781,6 +217732,7 @@ self: { description = "Use jsx-like syntax in Reflex"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "reflex-libtelnet" = callPackage @@ -220814,8 +217766,6 @@ self: { ]; description = "Localization library for reflex"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reflex-localize-dom" = callPackage @@ -220833,8 +217783,7 @@ self: { ]; description = "Helper widgets for reflex-localize"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; + platforms = [ "armv7l-linux" "i686-linux" "x86_64-linux" ]; }) {}; "reflex-monad-auth" = callPackage @@ -220894,7 +217843,6 @@ self: { description = "Reflex FRP interface for running system processes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reflex-sdl2" = callPackage @@ -221153,7 +218101,6 @@ self: { description = "Tools for maintaining a database"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reg-alloc" = callPackage @@ -221193,7 +218140,6 @@ self: { description = "Register allocation by graph colorization"; license = lib.licenses.mpl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reg-alloc-types" = callPackage @@ -221313,7 +218259,6 @@ self: { description = "Replaces/Enhances Text.Regex. Implementing regular expression matching using Brzozowski's Deriviatives"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "regex-dfa" = callPackage @@ -221503,7 +218448,6 @@ self: { description = "Text-based PCRE API for regex-base"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "regex-pderiv" = callPackage @@ -221521,7 +218465,6 @@ self: { description = "Replaces/Enhances Text.Regex. Implementing regular expression matching using Antimirov's partial derivatives."; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "regex-posix" = callPackage @@ -221757,8 +218700,6 @@ self: { ]; description = "Types that can only be constructed if they match a regular expression"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "regex-xmlschema" = callPackage @@ -221771,7 +218712,6 @@ self: { description = "A regular expression library for W3C XML Schema regular expressions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "regexchar" = callPackage @@ -221828,7 +218768,6 @@ self: { description = "Regular Expressions on Tries"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "regexpr" = callPackage @@ -221884,7 +218823,6 @@ self: { description = "Regional memory pointers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "regions" = callPackage @@ -221918,7 +218856,6 @@ self: { description = "Monads-fd instances for the RegionT monad transformer"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "regions-monadstf" = callPackage @@ -221935,7 +218872,6 @@ self: { description = "Monads-tf instances for the RegionT monad transformer"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "regions-mtl" = callPackage @@ -221948,7 +218884,6 @@ self: { description = "mtl instances for the RegionT monad transformer"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "register-machine-typelevel" = callPackage @@ -222017,7 +218952,6 @@ self: { description = "utilities to work with Hedgehog generators and `registry`"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "regress" = callPackage @@ -222071,7 +219005,6 @@ self: { description = "Additional functions for regular: arbitrary, coarbitrary, and binary get/put"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "regular-web" = callPackage @@ -222088,7 +219021,6 @@ self: { description = "Generic programming for the web"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "regular-xmlpickler" = callPackage @@ -222101,7 +219033,6 @@ self: { description = "Generic generation of HXT XmlPickler instances using Regular"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reheat" = callPackage @@ -222117,7 +219048,6 @@ self: { description = "to make notes and reduce impact on idle time on writing other programms"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rehoo" = callPackage @@ -222420,7 +219350,6 @@ self: { description = "Durations and generalized time parsing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "releaser" = callPackage @@ -222686,7 +219615,6 @@ self: { description = "Remote Monad implementation of the JSON RPC protocol"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "remote-json-client" = callPackage @@ -222705,7 +219633,6 @@ self: { description = "Web client wrapper for remote-json"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "remote-json-server" = callPackage @@ -222724,7 +219651,6 @@ self: { description = "Web server wrapper for remote-json"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "remote-monad" = callPackage @@ -222782,7 +219708,6 @@ self: { description = "A library for client-server applications based on custom protocols"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "render-utf8" = callPackage @@ -222798,8 +219723,6 @@ self: { ]; description = "Simple Utf8 wrapper for ByteString Builder with conversion classes"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "renderable" = callPackage @@ -222903,7 +219826,6 @@ self: { description = "Bulk array representations and operators"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "repa-bytestring" = callPackage @@ -222934,7 +219856,6 @@ self: { description = "Packing and unpacking flat tables"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "repa-devil" = callPackage @@ -222983,7 +219904,6 @@ self: { description = "Examples using the Repa array library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "repa-fftw" = callPackage @@ -223023,7 +219943,6 @@ self: { description = "Data-parallel data flows"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "repa-io" = callPackage @@ -223071,7 +219990,6 @@ self: { description = "Data Flow Fusion GHC Plugin"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "repa-scalar" = callPackage @@ -223134,7 +220052,6 @@ self: { description = "Stream functions not present in the vector library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "repa-v4l2" = callPackage @@ -223155,7 +220072,6 @@ self: { description = "Provides high-level access to webcams"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "repl" = callPackage @@ -223270,7 +220186,6 @@ self: { description = "Initial project template from stack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "repline" = callPackage @@ -223333,7 +220248,6 @@ self: { description = "Render overloaded expressions to their textual representation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "repr-tree-syb" = callPackage @@ -223396,7 +220310,6 @@ self: { description = "Tries from representations of polynomial functors"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reprinter" = callPackage @@ -223414,8 +220327,6 @@ self: { testToolDepends = [ hspec-discover ]; description = "Scrap Your Reprinter"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reproject" = callPackage @@ -223510,7 +220421,6 @@ self: { description = "Provides OAuth2 authentication for use with Req"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "req-url-extra" = callPackage @@ -223640,8 +220550,6 @@ self: { ]; description = "Regular-expressions extended with fixpoints for context-free powers"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rerebase" = callPackage @@ -223720,8 +220628,6 @@ self: { ]; description = "More understandable exceptions"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "reserve" = callPackage @@ -223787,7 +220693,6 @@ self: { description = "Compute total resistance of a cube of resistors"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "resolv_0_1_1_2" = callPackage @@ -223934,7 +220839,6 @@ self: { description = "Fork of resource-pool, with a MonadCatchIO constraint"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "resource-pool-monad" = callPackage @@ -223967,7 +220871,6 @@ self: { description = "Allocate resources which are guaranteed to be released"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "resourcet" = callPackage @@ -224024,7 +220927,6 @@ self: { description = "process and route HTTP requests and generate responses on top of WAI"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rest-client" = callPackage @@ -224047,7 +220949,6 @@ self: { description = "Utility library for use in generated API client libraries"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rest-core" = callPackage @@ -224076,7 +220977,6 @@ self: { description = "Rest API library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rest-example" = callPackage @@ -224100,7 +221000,6 @@ self: { description = "Example project for rest"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rest-gen" = callPackage @@ -224129,7 +221028,6 @@ self: { description = "Documentation and client generation from rest definition"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rest-happstack" = callPackage @@ -224148,7 +221046,6 @@ self: { description = "Rest driver for Happstack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rest-snap" = callPackage @@ -224167,7 +221064,6 @@ self: { description = "Rest driver for Snap"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rest-stringmap" = callPackage @@ -224185,7 +221081,6 @@ self: { description = "Maps with stringy keys that can be transcoded to JSON and XML"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rest-types" = callPackage @@ -224206,7 +221101,6 @@ self: { description = "Silk Rest Framework Types"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rest-wai" = callPackage @@ -224227,7 +221121,6 @@ self: { description = "Rest driver for WAI applications"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "restartable" = callPackage @@ -224261,7 +221154,6 @@ self: { ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "restless-git" = callPackage @@ -224299,7 +221191,6 @@ self: { description = "Running worker processes under system resource restrictions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "restyle" = callPackage @@ -224411,7 +221302,6 @@ self: { description = "Useful tools for modeling data with rethinkdb"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rethinkdb-wereHamster" = callPackage @@ -224593,7 +221483,6 @@ self: { description = "open file and rewrite it with new contents"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rewrite-inspector" = callPackage @@ -224627,7 +221516,6 @@ self: { description = "Generic rewriting library for regular datatypes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rex" = callPackage @@ -224664,7 +221552,6 @@ self: { description = "Github resume generator"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rfc" = callPackage @@ -224699,7 +221586,6 @@ self: { description = "Robert Fischer's Common library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rfc-env" = callPackage @@ -224712,7 +221598,6 @@ self: { description = "Environment variable support from the Robert Fischer Commons"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rfc-http-client" = callPackage @@ -224731,7 +221616,6 @@ self: { description = "The HTTP client extensions from the Robert Fischer Commons"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rfc-prelude" = callPackage @@ -224774,7 +221658,6 @@ self: { description = "The PostgreSQL extensions from the Robert Fischer Commons"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rfc-redis" = callPackage @@ -224787,7 +221670,6 @@ self: { description = "The Redis extensions from the Robert Fischer Commons"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rfc-servant" = callPackage @@ -224810,7 +221692,6 @@ self: { description = "The Servant extensions from the Robert Fischer Commons"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rfc1413-server" = callPackage @@ -224894,8 +221775,6 @@ self: { ]; description = "A dynamic/unbounded alternative to Bounded Enum"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rgb-color-model" = callPackage @@ -224981,7 +221860,6 @@ self: { description = "Haskell rhythm game tutorial"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "riak" = callPackage @@ -225084,7 +221962,6 @@ self: { description = "Static site generator based on Shake"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rib-core" = callPackage @@ -225153,6 +222030,7 @@ self: { description = "api extensions for nvim-hs"; license = "unknown"; hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "ribosome-root" = callPackage @@ -225266,7 +222144,6 @@ self: { description = "Handy metrics that don't belong to ridley"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "riemann" = callPackage @@ -225366,8 +222243,6 @@ self: { testHaskellDepends = [ base HUnit primitive QuickCheck ]; description = "mutable ring buffers with atomic updates in GHC Haskell"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rings" = callPackage @@ -225481,7 +222356,6 @@ self: { description = "A library for process pools coupled with asynchronous message queues"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "riot" = callPackage @@ -225502,7 +222376,6 @@ self: { description = "Riot is an Information Organisation Tool"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) ncurses;}; "ripple" = callPackage @@ -225561,7 +222434,6 @@ self: { description = "RISC-V"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "risc386" = callPackage @@ -225577,8 +222449,6 @@ self: { executableToolDepends = [ alex happy ]; description = "Reduced instruction set i386 simulator"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "riscv-isa" = callPackage @@ -225642,7 +222512,6 @@ self: { description = "A project management tool for Haskell applications"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rivet-adaptor-postgresql" = callPackage @@ -225792,7 +222661,6 @@ self: { description = "Ring-LWE/LWR challenges using Lol"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rmonad" = callPackage @@ -225810,7 +222678,6 @@ self: { description = "Restricted monad library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rncryptor" = callPackage @@ -225840,7 +222707,6 @@ self: { description = "Haskell implementation of the RNCryptor file format"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rng-utils" = callPackage @@ -225880,7 +222746,6 @@ self: { description = "Simple projects generator"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "robin" = callPackage @@ -225992,7 +222857,6 @@ self: { description = "Gloss interactive demo for roc-cluster package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "roc-id" = callPackage @@ -226038,7 +222902,6 @@ self: { description = "A build system for incremental, parallel, and demand-driven computations"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rocksdb-haskell" = callPackage @@ -226061,8 +222924,6 @@ self: { ]; description = "Haskell bindings to RocksDB"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) rocksdb;}; "rocksdb-haskell-jprupp" = callPackage @@ -226083,8 +222944,6 @@ self: { ]; description = "Haskell bindings for RocksDB"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) rocksdb;}; "rocksdb-query" = callPackage @@ -226104,8 +222963,6 @@ self: { ]; description = "RocksDB database querying library for Haskell"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "roguestar" = callPackage @@ -226241,7 +223098,6 @@ self: { description = "Simple CLI tool to perform commons tasks such as tracking deploys"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rollbar-client" = callPackage @@ -226316,7 +223172,6 @@ self: { description = "Provides error reporting capabilities to WAI based applications through Rollbar API"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rollbar-yesod" = callPackage @@ -226339,7 +223194,6 @@ self: { description = "Provides error reporting capabilities to Yesod applications through Rollbar API"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "roller" = callPackage @@ -226458,7 +223312,6 @@ self: { description = "RON-Schema"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ron-storage" = callPackage @@ -226477,7 +223330,6 @@ self: { description = "RON Storage"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "roots" = callPackage @@ -226600,7 +223452,6 @@ self: { description = "Trees with polymorphic paths to nodes, combining properties of Rose Trees and Tries"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rosebud" = callPackage @@ -226662,7 +223513,6 @@ self: { description = "Haskell support for the ROS robotics framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rosmsg" = callPackage @@ -226700,7 +223550,6 @@ self: { description = "ROS message management tools"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rospkg" = callPackage @@ -226801,8 +223650,6 @@ self: { testHaskellDepends = [ base long-double ]; description = "Correctly-rounded arbitrary-precision floating-point arithmetic"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) gmp; inherit (pkgs) mpfr;}; "rounded-hw" = callPackage @@ -226828,7 +223675,6 @@ self: { description = "Directed rounding for built-in floating types"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rounding" = callPackage @@ -226912,7 +223758,6 @@ self: { description = "Bidirectional (de-)serialization for XML"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "route-generator" = callPackage @@ -226948,7 +223793,6 @@ self: { description = "A library and utilities for creating a route"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "row" = callPackage @@ -227037,7 +223881,6 @@ self: { description = "type safe rpcs provided as basic IO actions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rpc-framework" = callPackage @@ -227078,7 +223921,6 @@ self: { description = "Receiver Policy Framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rpm" = callPackage @@ -227157,7 +223999,6 @@ self: { description = "The RogueStar Animation and Graphics Library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rsagl-frp" = callPackage @@ -227174,7 +224015,6 @@ self: { description = "The RogueStar Animation and Graphics Library: Functional Reactive Programming"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rsagl-math" = callPackage @@ -227192,7 +224032,6 @@ self: { description = "The RogueStar Animation and Graphics Library: Mathematics"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rset" = callPackage @@ -227264,8 +224103,6 @@ self: { ]; description = "Streaming parser/renderer for the RSS standard"; license = lib.licenses.cc0; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rss2irc" = callPackage @@ -227333,7 +224170,6 @@ self: { description = "Haskell bindings for RTCM"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rtld" = callPackage @@ -227558,7 +224394,6 @@ self: { description = "Ruler tool for UHC"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ruler-core" = callPackage @@ -227577,7 +224412,6 @@ self: { ]; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "run-haskell-module" = callPackage @@ -227600,8 +224434,6 @@ self: { libraryHaskellDepends = [ base primitive primitive-unlifted ]; description = "runST without boxing penalty"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rungekutta" = callPackage @@ -227695,7 +224527,6 @@ self: { description = "Runtime generation of Arbitrary values"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rv" = callPackage @@ -227713,8 +224544,6 @@ self: { benchmarkHaskellDepends = [ base criterion ]; description = "RISC-V"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "rvar" = callPackage @@ -227823,7 +224652,6 @@ self: { description = "simple general-purpose s-expressions"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "s3-signer" = callPackage @@ -228199,7 +225027,6 @@ self: { description = "Safe arithmetic operations"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "safe-plugins" = callPackage @@ -228392,7 +225219,6 @@ self: { description = "Type-safe file handling"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "safer-file-handles-bytestring" = callPackage @@ -228410,7 +225236,6 @@ self: { description = "Extends safer-file-handles with ByteString operations"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "safer-file-handles-text" = callPackage @@ -228427,7 +225252,6 @@ self: { description = "Extends safer-file-handles with Text operations"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "saferoute" = callPackage @@ -228457,7 +225281,6 @@ self: { description = "Obtain homogeneous values from arbitrary values, transforming or culling data"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sajson" = callPackage @@ -228504,7 +225327,6 @@ self: { description = "Compression command-line tool"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sakuraio-platform" = callPackage @@ -228638,7 +225460,6 @@ self: { description = "Quickcheck implementations for some NaCl data"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) libsodium;}; "salve" = callPackage @@ -228672,7 +225493,6 @@ self: { description = "Modular web application framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "salvia-demo" = callPackage @@ -228696,7 +225516,6 @@ self: { description = "Demo Salvia servers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "salvia-extras" = callPackage @@ -228718,7 +225537,6 @@ self: { description = "Collection of non-fundamental handlers for the Salvia web server"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "salvia-protocol" = callPackage @@ -228755,7 +225573,6 @@ self: { description = "Session support for the Salvia webserver"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "salvia-websocket" = callPackage @@ -228773,7 +225590,6 @@ self: { description = "Websocket implementation for the Salvia Webserver"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sample-frame" = callPackage @@ -228831,7 +225647,6 @@ self: { description = "Binding to the C samtools library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) zlib;}; "samtools-conduit" = callPackage @@ -228853,7 +225668,6 @@ self: { description = "Conduit interface to SAM/BAM format files through samtools"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "samtools-enumerator" = callPackage @@ -228870,7 +225684,6 @@ self: { description = "Enumerator interface to SamTools library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "samtools-iteratee" = callPackage @@ -228888,7 +225701,6 @@ self: { description = "Iteratee interface to SamTools library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sandi" = callPackage @@ -229119,7 +225931,6 @@ self: { description = "A universal quickfix toolkit and his protocol"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sasl" = callPackage @@ -229137,7 +225948,6 @@ self: { description = "SASL implementation using simple-pipe"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sat" = callPackage @@ -229171,7 +225981,6 @@ self: { description = "A minimal SAT solver"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "satchmo" = callPackage @@ -229208,7 +226017,6 @@ self: { description = "driver for external satchmo backends"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "satchmo-examples" = callPackage @@ -229227,7 +226035,6 @@ self: { description = "examples that show how to use satchmo"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "satchmo-funsat" = callPackage @@ -229244,7 +226051,6 @@ self: { description = "funsat driver as backend for satchmo"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "satchmo-minisat" = callPackage @@ -229257,7 +226063,6 @@ self: { description = "minisat driver as backend for satchmo"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "satchmo-toysat" = callPackage @@ -229274,7 +226079,6 @@ self: { description = "toysat driver as backend for satchmo"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "savage" = callPackage @@ -229498,7 +226302,6 @@ self: { description = "Low-level Starcraft II API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sc2-proto" = callPackage @@ -229537,7 +226340,6 @@ self: { description = "Support and utility library for sc2hs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sc2hs" = callPackage @@ -229579,7 +226381,6 @@ self: { description = "Haskell bindings to sc3-rdu (sc3 rd ugens)"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scalable-server" = callPackage @@ -229598,7 +226399,6 @@ self: { description = "Library for writing fast/scalable TCP-based services"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scaleimage" = callPackage @@ -229659,7 +226459,6 @@ self: { description = "Test webhooks locally"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scalpel" = callPackage @@ -229712,7 +226511,6 @@ self: { description = "scalpel scrapers for search engines"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scan" = callPackage @@ -229745,8 +226543,6 @@ self: { ]; description = "Metadata types for Albedo Scanners"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scan-vector-machine" = callPackage @@ -229760,7 +226556,6 @@ self: { description = "An implementation of the Scan Vector Machine instruction set in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scanf" = callPackage @@ -230006,7 +226801,6 @@ self: { description = "Encoding-independent schemas for Haskell data types"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "schemas" = callPackage @@ -230062,7 +226856,6 @@ self: { description = "JSON-biased spec and validation tool"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scholdoc" = callPackage @@ -230108,7 +226901,6 @@ self: { description = "Converts ScholarlyMarkdown documents to HTML5/LaTeX/Docx format"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scholdoc-citeproc" = callPackage @@ -230143,7 +226935,6 @@ self: { description = "Scholdoc fork of pandoc-citeproc"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scholdoc-texmath" = callPackage @@ -230167,7 +226958,6 @@ self: { description = "Scholdoc fork of texmath"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scholdoc-types" = callPackage @@ -230319,7 +227109,6 @@ self: { description = "Scientific notation intended for tokenization"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scion" = callPackage @@ -230346,7 +227135,6 @@ self: { description = "Haskell IDE library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scion-browser" = callPackage @@ -230382,7 +227170,6 @@ self: { description = "Command-line interface for browsing and searching packages documentation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scons2dot" = callPackage @@ -230416,7 +227203,6 @@ self: { description = "An interactive renderer for plotting time-series data"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scope-cairo" = callPackage @@ -230441,7 +227227,6 @@ self: { description = "An interactive renderer for plotting time-series data"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scottish" = callPackage @@ -230622,7 +227407,6 @@ self: { description = "Easy Mustache templating support for Scotty"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scotty-haxl" = callPackage @@ -230798,7 +227582,6 @@ self: { description = "An SCP protocol implementation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scrabble-bot" = callPackage @@ -230819,7 +227602,6 @@ self: { description = "Scrabble play generation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scrapbook" = callPackage @@ -230844,7 +227626,6 @@ self: { description = "collect posts of site that is wrote in config yaml using feed or scraping"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "scrapbook-core" = callPackage @@ -231100,7 +227881,6 @@ self: { description = "Distributed SDE solver"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sdf2p1-parser" = callPackage @@ -231572,7 +228352,6 @@ self: { description = "PostgreSQL backend for Seakale"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "seakale-tests" = callPackage @@ -231589,7 +228368,6 @@ self: { description = "Helpers to test code using Seakale"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "seal-module" = callPackage @@ -231850,7 +228628,6 @@ self: { description = "Example of writing \"secure\" file removal in Haskell rather than C"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "secure-sockets" = callPackage @@ -231911,7 +228688,6 @@ self: { description = "Sedna C API XML Binding"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {sedna = null;}; "seitz-symbol" = callPackage @@ -231932,7 +228708,6 @@ self: { description = "Read and Display Seitz Symbol"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "selda" = callPackage @@ -232090,7 +228865,6 @@ self: { description = "Run the selenium standalone server for usage with webdriver"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "self-extract" = callPackage @@ -232111,7 +228885,6 @@ self: { description = "A Haskell library to make self-extracting executables"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "selfrestart" = callPackage @@ -232219,7 +228992,6 @@ self: { description = "Weakened partial isomorphisms, reversible computations"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "semialign" = callPackage @@ -232459,7 +229231,6 @@ self: { description = "Semirings, ring-like structures used for dynamic programming applications"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "semiring-num" = callPackage @@ -232486,7 +229257,6 @@ self: { description = "Basic semiring class and instances"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "semiring-simple" = callPackage @@ -232644,7 +229414,6 @@ self: { description = "Distributed sensor network for the raspberry pi"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sensu-run" = callPackage @@ -232682,7 +229451,6 @@ self: { description = "Easily generating message of japanese natural language"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sentiwordnet-parser" = callPackage @@ -232769,7 +229537,6 @@ self: { description = "SmartyPants for Korean language"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "separated" = callPackage @@ -232817,7 +229584,6 @@ self: { description = "Dynamic strictness control, including space leak repair"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "seqalign" = callPackage @@ -232872,7 +229638,6 @@ self: { description = "Handle sequence locations for bioinformatics"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "seqloc-datafiles" = callPackage @@ -232907,7 +229672,6 @@ self: { description = "Read and write BED and GTF format genome annotations"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sequence" = callPackage @@ -233023,7 +229787,6 @@ self: { description = "A sequence labeler based on Collins's sequence perceptron"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "serf" = callPackage @@ -233205,7 +229968,6 @@ self: { description = "Simple project template from stack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "serv" = callPackage @@ -233220,7 +229982,6 @@ self: { description = "Dependently typed API framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "serv-wai" = callPackage @@ -233246,7 +230007,6 @@ self: { description = "Dependently typed API servers with Serv"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant" = callPackage @@ -233419,8 +230179,6 @@ self: { testToolDepends = [ hspec-discover ]; description = "servant-docs/servant-auth compatibility"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-auth-hmac" = callPackage @@ -233526,7 +230284,6 @@ self: { description = "Servant based API and server for token based authorisation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-auth-token-acid" = callPackage @@ -233549,7 +230306,6 @@ self: { description = "Acid-state backend for servant-auth-token server"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-auth-token-api" = callPackage @@ -233590,7 +230346,6 @@ self: { description = "Leveldb backend for servant-auth-token server"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-auth-token-persistent" = callPackage @@ -233611,7 +230366,6 @@ self: { description = "Persistent backend for servant-auth-token server"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-auth-token-rocksdb" = callPackage @@ -233635,7 +230389,6 @@ self: { description = "RocksDB backend for servant-auth-token server"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-auth-wordpress" = callPackage @@ -233652,7 +230405,6 @@ self: { description = "Authenticate Routes Using Wordpress Cookies"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-avro" = callPackage @@ -233693,8 +230445,6 @@ self: { ]; description = "Generate benchmark files from a Servant API"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-blaze" = callPackage @@ -233728,8 +230478,6 @@ self: { ]; description = "Servant CSV content-type for cassava"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-checked-exceptions" = callPackage @@ -233754,8 +230502,6 @@ self: { ]; description = "Checked exceptions for Servant APIs"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-checked-exceptions-core" = callPackage @@ -233777,8 +230523,6 @@ self: { testHaskellDepends = [ base doctest Glob ]; description = "Checked exceptions for Servant APIs"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-cli" = callPackage @@ -233807,7 +230551,6 @@ self: { description = "Command line interface for Servant API clients"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-client" = callPackage @@ -233904,7 +230647,6 @@ self: { description = "Automatically derive API client functions with named and optional parameters"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-conduit" = callPackage @@ -233945,7 +230687,6 @@ self: { description = "Generate servant client library for C#"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-db" = callPackage @@ -233985,7 +230726,6 @@ self: { description = "Derive a postgres client to database API specified by servant-db"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-dhall" = callPackage @@ -234085,7 +230825,6 @@ self: { description = "Combinators for rendering EDE templates in servant web applications"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-ekg" = callPackage @@ -234182,7 +230921,6 @@ self: { description = "Servant support for Server-Sent events"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-examples" = callPackage @@ -234206,7 +230944,6 @@ self: { description = "Example programs for servant"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-exceptions" = callPackage @@ -234477,7 +231214,6 @@ self: { description = "Generate HTTP2 clients from Servant API descriptions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-iCalendar" = callPackage @@ -234494,8 +231230,6 @@ self: { ]; description = "Servant support for iCalendar"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-jquery" = callPackage @@ -234678,7 +231412,6 @@ self: { description = "Matrix parameter combinator for servant"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-mock" = callPackage @@ -234741,8 +231474,6 @@ self: { ]; description = "multipart/form-data (e.g file upload) support for servant"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-named" = callPackage @@ -234927,7 +231658,6 @@ self: { description = "Utilities for using servant in a polysemy stack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-pool" = callPackage @@ -234960,7 +231690,6 @@ self: { description = "Useful functions and instances for using servant with a PostgreSQL context"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-proto-lens" = callPackage @@ -235106,8 +231835,6 @@ self: { libraryHaskellDepends = [ base servant-client-core servant-rawm ]; description = "The client implementation of servant-rawm"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-rawm-docs" = callPackage @@ -235123,8 +231850,6 @@ self: { ]; description = "Documentation generator for 'RawM' endpoints"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-rawm-server" = callPackage @@ -235298,8 +232023,6 @@ self: { doHaddock = false; description = "Generates a servant API module"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-server" = callPackage @@ -235353,7 +232076,6 @@ self: { description = "Automatically derive API server functions with named and optional parameters"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-smsc-ru" = callPackage @@ -235416,7 +232138,6 @@ self: { description = "A family of combinators for defining webservices APIs and serving them"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-stache" = callPackage @@ -235509,7 +232230,6 @@ self: { description = "Client instances for the 'servant-streaming' package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-streaming-docs" = callPackage @@ -235528,7 +232248,6 @@ self: { description = "Client instances for the 'servant-docs' package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-streaming-server" = callPackage @@ -235556,7 +232275,6 @@ self: { description = "Server instances for the 'servant-streaming' package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-subscriber" = callPackage @@ -235628,7 +232346,6 @@ self: { description = "Swagger Tags for Servant"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-swagger-ui" = callPackage @@ -235792,7 +232509,6 @@ self: { description = "Servant Integration for Waargonaut JSON Package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-wasm" = callPackage @@ -235908,7 +232624,6 @@ self: { description = "Client library for servant-zeppelin combinators"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-zeppelin-server" = callPackage @@ -235933,7 +232648,6 @@ self: { description = "Server library for servant-zeppelin combinators"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "servant-zeppelin-swagger" = callPackage @@ -235956,7 +232670,6 @@ self: { description = "Swagger instances for servant-zeppelin combinators"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "server-generic" = callPackage @@ -236025,8 +232738,6 @@ self: { ]; description = "Secure, modular server-side sessions"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "serversession-backend-acid-state" = callPackage @@ -236047,8 +232758,6 @@ self: { ]; description = "Storage backend for serversession using acid-state"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "serversession-backend-persistent" = callPackage @@ -236117,8 +232826,6 @@ self: { ]; description = "Snap bindings for serversession"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "serversession-frontend-wai" = callPackage @@ -236136,8 +232843,6 @@ self: { ]; description = "wai-session bindings for serversession"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "serversession-frontend-yesod" = callPackage @@ -236306,7 +233011,6 @@ self: { description = "Session types distributed"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "set-cover" = callPackage @@ -236409,7 +233113,6 @@ self: { description = "Treating files as sets to perform rapid set manipulation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "setenv" = callPackage @@ -236617,8 +233320,6 @@ self: { ]; description = "Invertible grammar combinators for S-expressions"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sexp-show" = callPackage @@ -236800,7 +233501,6 @@ self: { description = "SGF (Smart Game Format) parser"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sgrep" = callPackage @@ -236815,7 +233515,6 @@ self: { description = "Sgrep - grep Fasta files for sequences matching a regular expression"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sh2md" = callPackage @@ -236877,7 +233576,6 @@ self: { description = "SHA-1 Hash"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "shade" = callPackage @@ -237262,7 +233960,6 @@ self: { description = "Shake rules for CSS"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "shake-pack" = callPackage @@ -237414,7 +234111,6 @@ self: { description = "simple and interactive command-line build tool"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "shakers" = callPackage @@ -237582,7 +234278,6 @@ self: { description = "Parser and related tools for ESRI shapefile format"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "shapely-data" = callPackage @@ -237602,7 +234297,6 @@ self: { description = "Generics using @(,)@ and @Either@, with algebraic operations and typed conversions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "shapes" = callPackage @@ -237789,7 +234483,6 @@ self: { description = "Test webhooks locally"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "shell-conduit" = callPackage @@ -237918,7 +234611,6 @@ self: { description = "Extra functionality for shellmate"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "shellmet" = callPackage @@ -238283,8 +234975,6 @@ self: { testHaskellDepends = [ base doctest ]; description = "Link shortcuts for use in text markup"; license = lib.licenses.mpl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "shorten-strings" = callPackage @@ -238400,7 +235090,6 @@ self: { description = "A simple gtk based Russian Roulette game"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "shower" = callPackage @@ -238443,7 +235132,6 @@ self: { description = "Web automation library in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "shplit" = callPackage @@ -238494,7 +235182,6 @@ self: { description = "Shuffle tool for UHC"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "shunya-library" = callPackage @@ -238551,7 +235238,6 @@ self: { description = "An interface to the Silicon Labs Si5351 clock chip"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sibe" = callPackage @@ -238578,7 +235264,6 @@ self: { description = "Machine Learning algorithms"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sieve" = callPackage @@ -238676,7 +235361,6 @@ self: { description = "Thom polynomials of second order Thom-Boardman singularities"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sign" = callPackage @@ -238699,8 +235383,6 @@ self: { ]; description = "Arithmetic over signs and sets of signs"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "signable" = callPackage @@ -238730,7 +235412,6 @@ self: { description = "Deterministic serialisation and signatures with proto-lens support"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "signable-haskell-protoc" = callPackage @@ -238781,7 +235462,6 @@ self: { description = "Synchronous signal processing for DSLs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "signature" = callPackage @@ -238800,7 +235480,6 @@ self: { description = "Hmac sha256 signature json and http payload"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "signed-multiset" = callPackage @@ -238838,7 +235517,6 @@ self: { description = "A Haskell clone of OpenBSD signify"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "silently" = callPackage @@ -238862,8 +235540,6 @@ self: { libraryHaskellDepends = [ base prettyprinter ]; description = "Prettyprinting transformers"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "silvi" = callPackage @@ -238882,7 +235558,6 @@ self: { description = "A generator for different kinds of data"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "simd" = callPackage @@ -238914,7 +235589,6 @@ self: { description = "stochastic simulation engine"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "simple" = callPackage @@ -239032,7 +235706,6 @@ self: { description = "A simple C value type"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "simple-cabal" = callPackage @@ -239217,7 +235890,6 @@ self: { description = "Simplified interface for firewire cameras"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "simple-form" = callPackage @@ -239436,7 +236108,6 @@ self: { description = "Simple parsing/pretty printing for Nix expressions"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "simple-observer" = callPackage @@ -239487,7 +236158,6 @@ self: { description = "Simplified Pascal language to SSVM compiler"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "simple-pipe" = callPackage @@ -239865,7 +236535,6 @@ self: { description = "Lenses for simpleirc types"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "simplelru" = callPackage @@ -240042,7 +236711,6 @@ self: { description = "Simulate sequencing with different models for priming and errors"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "simtreelo" = callPackage @@ -240254,7 +236922,6 @@ self: { description = "A promoted and singled version of the base library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "singletons-presburger" = callPackage @@ -240385,7 +237052,6 @@ self: { description = "Encode and decode CSV files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "siren-json" = callPackage @@ -240411,7 +237077,6 @@ self: { description = "Siren Tools for Haskell"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sirkel" = callPackage @@ -240429,7 +237094,6 @@ self: { description = "Sirkel, a Chord DHT"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sitemap" = callPackage @@ -240736,7 +237400,6 @@ self: { description = "a tool to access the OSX keychain"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "skeletons" = callPackage @@ -240756,7 +237419,6 @@ self: { description = "Manage project skeletons"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "skell" = callPackage @@ -240875,7 +237537,6 @@ self: { description = "Skylark client"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "skylighting" = callPackage @@ -241142,8 +237803,6 @@ self: { ]; description = "Bindings for the Slack web API"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "slate" = callPackage @@ -241286,7 +237945,6 @@ self: { description = "ws convert markdown to reveal-js"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "slim" = callPackage @@ -241325,7 +237983,6 @@ self: { description = "SLIP-0032: Extended serialization format for BIP-32 wallets"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "slist" = callPackage @@ -241488,8 +238145,6 @@ self: { executableHaskellDepends = [ base ]; description = "Handle molecular sequences"; license = lib.licenses.gpl3Plus; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "small-bytearray-builder" = callPackage @@ -241503,7 +238158,6 @@ self: { description = "Serialize to bytes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "smallarray" = callPackage @@ -241649,7 +238303,6 @@ self: { description = "A Unicode text type, optimized for low memory overhead"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "smaoin" = callPackage @@ -241790,7 +238443,6 @@ self: { description = "Web based flash card for Word Smart I and II vocabularies"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "smash" = callPackage @@ -241898,7 +238550,6 @@ self: { description = "Symbolic Model Checking for Dynamic Epistemic Logic"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sme" = callPackage @@ -241957,7 +238608,6 @@ self: { description = "Parse arrays of tokens"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "smith-cli" = callPackage @@ -241982,7 +238632,6 @@ self: { description = "Command line tool for ."; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "smith-client" = callPackage @@ -242007,7 +238656,6 @@ self: { description = "API client for ."; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "smoothie" = callPackage @@ -242126,7 +238774,6 @@ self: { description = "Dump the communication with an SMT solver for debugging purposes"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "smtlib2-pipe" = callPackage @@ -242149,7 +238796,6 @@ self: { description = "A type-safe interface to communicate with an SMT solver"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "smtlib2-quickcheck" = callPackage @@ -242166,7 +238812,6 @@ self: { description = "Helper functions to create SMTLib expressions in QuickCheck"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "smtlib2-timing" = callPackage @@ -242179,7 +238824,6 @@ self: { description = "Get timing informations for SMT queries"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "smtp-mail" = callPackage @@ -242413,7 +239057,6 @@ self: { description = "Command-line tool to manage Snap AuthManager database"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snap-blaze" = callPackage @@ -242518,7 +239161,6 @@ self: { description = "Serve Elm files through the Snap web framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snap-error-collector" = callPackage @@ -242569,7 +239211,6 @@ self: { description = "A collection of useful helpers and utilities for Snap web applications"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snap-language" = callPackage @@ -242780,7 +239421,6 @@ self: { description = "Snap Framework utilities"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snap-web-routes" = callPackage @@ -242838,7 +239478,6 @@ self: { description = "Generic action log snaplet for the Snap Framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-amqp" = callPackage @@ -242879,7 +239518,6 @@ self: { description = "Provides an Acid-State backend for the Auth Snaplet"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-coffee" = callPackage @@ -242898,7 +239536,6 @@ self: { description = "CoffeeScript for Snap, auto-compilation and pre-compilation"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-css-min" = callPackage @@ -243015,7 +239652,6 @@ self: { description = "A Hasql snaplet"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-haxl" = callPackage @@ -243032,7 +239668,6 @@ self: { description = "Snaplet for Facebook's Haxl"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-hdbc" = callPackage @@ -243054,7 +239689,6 @@ self: { description = "HDBC snaplet for Snap Framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-hslogger" = callPackage @@ -243133,7 +239767,6 @@ self: { description = "Lexical Style Sheets - Snap Web Framework adaptor"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-mandrill" = callPackage @@ -243151,7 +239784,6 @@ self: { description = "Snap framework snaplet for the Mandrill API library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-mongoDB" = callPackage @@ -243172,7 +239804,6 @@ self: { description = "Snap Framework MongoDB support as Snaplet"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-mongodb-minimalistic" = callPackage @@ -243210,7 +239841,6 @@ self: { description = "mysql-simple snaplet for the Snap Framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-oauth" = callPackage @@ -243237,7 +239867,6 @@ self: { description = "snaplet-oauth"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-persistent" = callPackage @@ -243305,7 +239934,6 @@ self: { description = "Postmark snaplet for the Snap Framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-purescript" = callPackage @@ -243322,8 +239950,6 @@ self: { ]; description = "Automatic (re)compilation of purescript projects"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-recaptcha" = callPackage @@ -243342,7 +239968,6 @@ self: { description = "A ReCAPTCHA verification snaplet with Heist integration and connection sharing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-redis" = callPackage @@ -243362,8 +239987,6 @@ self: { ]; description = "Redis support for Snap Framework"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-redson" = callPackage @@ -243384,7 +240007,6 @@ self: { description = "CRUD for JSON data with Redis storage"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-rest" = callPackage @@ -243403,7 +240025,6 @@ self: { description = "REST resources for the Snap web framework"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-riak" = callPackage @@ -243422,7 +240043,6 @@ self: { description = "A Snaplet for the Riak database"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-sass" = callPackage @@ -243477,7 +240097,6 @@ self: { description = "Snaplet for Sedna Bindings. Essentailly a rip of snaplet-hdbc."; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-ses-html" = callPackage @@ -243548,7 +240167,6 @@ self: { description = "Snaplet for JWT authentication with snaplet-sqlite-simple"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-stripe" = callPackage @@ -243568,7 +240186,6 @@ self: { description = "Stripe snaplet for the Snap Framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-tasks" = callPackage @@ -243586,7 +240203,6 @@ self: { description = "Snaplet for Snap Framework enabling developers to administrative tasks akin to Rake tasks from Ruby On Rails framework"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snaplet-typed-sessions" = callPackage @@ -243633,7 +240249,6 @@ self: { description = "A snaplet that communicates with wordpress over its api"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snappy" = callPackage @@ -243688,7 +240303,6 @@ self: { description = "An enumeratee that uses Google's snappy compression library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snappy-lazy" = callPackage @@ -243722,7 +240336,6 @@ self: { description = "Audio file reading/writing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sneakyterm" = callPackage @@ -243800,7 +240413,6 @@ self: { description = "The Simple Nice-Looking Manual Generator"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snmp" = callPackage @@ -243820,7 +240432,6 @@ self: { description = "SNMP protocol library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snorkels" = callPackage @@ -243858,7 +240469,6 @@ self: { description = "encode any binary instance to white space"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snowball" = callPackage @@ -243907,7 +240517,6 @@ self: { description = "twitter's snowflake"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snowflake-server" = callPackage @@ -243927,7 +240536,6 @@ self: { description = "snowflake http server"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "snowglobe" = callPackage @@ -244110,8 +240718,6 @@ self: { transformers unordered-containers vector ]; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "socket-sctp" = callPackage @@ -244234,7 +240840,6 @@ self: { description = "High-level network sockets"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sockets-and-pipes" = callPackage @@ -244390,7 +240995,6 @@ self: { description = "Swagger generation for Solga"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "solr" = callPackage @@ -244416,7 +241020,6 @@ self: { description = "A minimal Solr client library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "solve" = callPackage @@ -244614,7 +241217,6 @@ self: { description = "Haskell EDSL for Souffle"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "souffle-haskell" = callPackage @@ -244685,7 +241287,6 @@ self: { description = "Audio delay line"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "soundgen" = callPackage @@ -244700,7 +241301,6 @@ self: { description = "sound generator"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "source-code-server" = callPackage @@ -244725,7 +241325,6 @@ self: { description = "The server backend for the source code iPhone app"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "source-constraints" = callPackage @@ -245011,7 +241610,6 @@ self: { description = "Distributed Apache Spark applications in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sparql-protocol" = callPackage @@ -245058,7 +241656,6 @@ self: { description = "Unified streaming data-dependency framework for web apps"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "spars" = callPackage @@ -245176,7 +241773,6 @@ self: { description = "Sparse bitmaps for pattern match coverage"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sparsecheck" = callPackage @@ -245206,7 +241802,6 @@ self: { description = "Lightweight parsing library based on partial functions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "spartacon" = callPackage @@ -245238,7 +241833,6 @@ self: { description = "brainless form validation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "spatial-math" = callPackage @@ -245410,7 +242004,6 @@ self: { description = "Create specialized types from polymorphic ones using TH"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "species" = callPackage @@ -245430,7 +242023,6 @@ self: { description = "Computational combinatorial species"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "spectral-clustering" = callPackage @@ -245449,7 +242041,6 @@ self: { description = "Library for spectral clustering"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "speculate" = callPackage @@ -245491,7 +242082,6 @@ self: { description = "Merged into 'speculation'. Use that instead."; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "speechmatics" = callPackage @@ -245523,7 +242113,6 @@ self: { description = "Speechmatics api client"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "speedy-slice" = callPackage @@ -245563,7 +242152,6 @@ self: { description = "Spelling suggestion tool with library and command-line interfaces"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "spherical" = callPackage @@ -245591,7 +242179,6 @@ self: { description = "Orbotix Sphero client library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sphinx" = callPackage @@ -245624,7 +242211,6 @@ self: { description = "Sphinx CLI and demo of Haskell Sphinx library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sphinxesc" = callPackage @@ -245662,7 +242248,6 @@ self: { description = "An FRP-based game engine written in Haskell"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "spike" = callPackage @@ -245803,7 +242388,6 @@ self: { description = "A parallel implementation of the Sorokina/Zeilfelder spline scheme"; license = lib.licenses.agpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "splines" = callPackage @@ -245826,7 +242410,6 @@ self: { description = "B-Splines, other splines, and NURBS"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "splint" = callPackage @@ -246115,7 +242698,6 @@ self: { description = "JSON API to HTML website wrapper"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "spritz" = callPackage @@ -246154,7 +242736,6 @@ self: { description = "HTTP proxy for authenticating users via OAuth2"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sproxy-web" = callPackage @@ -246181,7 +242762,6 @@ self: { description = "Web interface to sproxy database"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sproxy2" = callPackage @@ -246208,7 +242788,6 @@ self: { description = "Secure HTTP proxy for authenticating users via OAuth2"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "spsa" = callPackage @@ -246291,7 +242870,6 @@ self: { description = "mysql backend for sql-simple"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sql-simple-pool" = callPackage @@ -246309,7 +242887,6 @@ self: { description = "conection pool for sql-simple"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sql-simple-postgresql" = callPackage @@ -246326,7 +242903,6 @@ self: { description = "postgresql backend for sql-simple"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sql-simple-sqlite" = callPackage @@ -246339,7 +242915,6 @@ self: { description = "sqlite backend for sql-simple"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sql-words" = callPackage @@ -246466,7 +243041,6 @@ self: { description = "Typed extension to sqlite simple"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sqlvalue-list" = callPackage @@ -246618,8 +243192,6 @@ self: { ]; description = "A file-packing application"; license = "GPL"; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sr-extra" = callPackage @@ -246648,7 +243220,6 @@ self: { description = "Module limbo"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "srcinst" = callPackage @@ -246729,7 +243300,6 @@ self: { description = "Simple SCGI Library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sscript" = callPackage @@ -246837,7 +243407,6 @@ self: { description = "Check sshd configuration for adherence to best practices"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sshtun" = callPackage @@ -246886,7 +243455,6 @@ self: { description = "HTTP proxy for S3"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sstable" = callPackage @@ -246906,7 +243474,6 @@ self: { description = "SSTables in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ssv" = callPackage @@ -247019,7 +243586,6 @@ self: { description = "Trees whose branches are resistant to change"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stache" = callPackage @@ -247250,7 +243816,6 @@ self: { description = "Initial project template from stack"; license = lib.licenses.isc; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stack-lib" = callPackage @@ -247310,7 +243875,6 @@ self: { description = "A program for extending Stack to add distributed capabilities"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stack-prism" = callPackage @@ -247380,7 +243944,6 @@ self: { description = "Initial project template from stack"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stack-tag" = callPackage @@ -247539,7 +244102,6 @@ self: { description = "Dummy package forcing installation of other Stackage packages"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stackage-build-plan" = callPackage @@ -247565,7 +244127,6 @@ self: { description = "Calculate and print (in different formats) Stackage build plans"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stackage-cabal" = callPackage @@ -247587,7 +244148,6 @@ self: { description = "A CLI executable for cabal-based stackage commands"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stackage-cli" = callPackage @@ -247731,7 +244291,6 @@ self: { description = "Tool for querying Stackage"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stackage-sandbox" = callPackage @@ -247753,7 +244312,6 @@ self: { description = "Work with shared stackage sandboxes"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stackage-setup" = callPackage @@ -247778,7 +244336,6 @@ self: { description = "An executable for downloading a Haskell setup"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stackage-to-hackage" = callPackage @@ -247864,7 +244421,6 @@ self: { description = "A more secure version of cabal upload which uses HTTPS"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stackage2nix" = callPackage @@ -247896,7 +244452,6 @@ self: { description = "Convert Stack files into Nix build instructions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stackcollapse-ghc" = callPackage @@ -248269,7 +244824,6 @@ self: { description = "Typeclass instances for monad transformer stacks with an ST thread at the bottom"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stateref" = callPackage @@ -248376,7 +244930,6 @@ self: { description = "Serialisable static pointers to functions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "static-hash" = callPackage @@ -248455,8 +245008,6 @@ self: { testToolDepends = [ markdown-unlit ]; description = "Lists, Texts, ByteStrings and Vectors of statically known length"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "staticanalysis" = callPackage @@ -248631,7 +245182,6 @@ self: { description = "Statsd UDP client"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "statsd-datadog" = callPackage @@ -248671,7 +245221,6 @@ self: { description = "A lovely [Dog]StatsD implementation"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "status-notifier-item" = callPackage @@ -249448,7 +245997,6 @@ self: { description = "Control communication among retrying transactions"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stochastic" = callPackage @@ -249483,8 +246031,6 @@ self: { testHaskellDepends = [ base bytestring HUnit ]; description = "Library for the IEX Trading API"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stomp-conduit" = callPackage @@ -249698,7 +246244,6 @@ self: { description = "Conversion between storablevector and stream-fusion lists with fusion"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "store" = callPackage @@ -249880,7 +246425,6 @@ self: { description = "A library for stratux"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stratux-demo" = callPackage @@ -249904,7 +246448,6 @@ self: { description = "A demonstration of the stratux library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stratux-http" = callPackage @@ -249921,7 +246464,6 @@ self: { description = "A library for using HTTP with stratux"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stratux-types" = callPackage @@ -249956,7 +246498,6 @@ self: { description = "A library for using websockets with stratux"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stream" = callPackage @@ -250097,7 +246638,6 @@ self: { description = "Streaming conversion from/to base64"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "streaming-benchmarks" = callPackage @@ -250123,8 +246663,6 @@ self: { ]; description = "Benchmarks to compare streaming packages"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "streaming-binary" = callPackage @@ -250181,7 +246719,6 @@ self: { description = "Streaming interface for Brotli (RFC7932) compression"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "streaming-bytestring" = callPackage @@ -250224,8 +246761,6 @@ self: { ]; description = "Cassava support for the streaming ecosystem"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "streaming-commons" = callPackage @@ -250273,7 +246808,6 @@ self: { description = "Concurrency support for the streaming ecosystem"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "streaming-conduit" = callPackage @@ -250346,7 +246880,6 @@ self: { description = "online streaming fft"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "streaming-histogram" = callPackage @@ -250508,7 +247041,6 @@ self: { description = "Streaming support for running system process"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "streaming-sort" = callPackage @@ -250531,7 +247063,6 @@ self: { description = "Sorting streams"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "streaming-utils" = callPackage @@ -250811,7 +247342,6 @@ self: { description = "A simple, flexible and composable web-router"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "strelka-core" = callPackage @@ -250888,8 +247418,6 @@ self: { ]; description = "Strict variants of the types provided in base"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "strict-concurrency" = callPackage @@ -250980,7 +247508,6 @@ self: { description = "A collection of commonly used strict data structures"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "strict-ghc-plugin" = callPackage @@ -251395,7 +247922,6 @@ self: { description = "Type-level Chars and Strings, with decidable equality"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stringable" = callPackage @@ -251662,7 +248188,6 @@ self: { description = "Listen for Stripe webhook events with Scotty"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stripe-servant" = callPackage @@ -251731,8 +248256,6 @@ self: { ]; description = "Use the Stripe API via Wreq"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stripeapi" = callPackage @@ -251865,7 +248388,6 @@ self: { description = "Instantiate structural induction schemas for algebraic data types"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "structural-traversal" = callPackage @@ -251957,7 +248479,6 @@ self: { description = "Structured MongoDB interface"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "structures" = callPackage @@ -252054,7 +248575,6 @@ self: { description = "A revival of the classic game Stunts (LambdaCube tech demo)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stutter" = callPackage @@ -252083,7 +248603,6 @@ self: { description = "(Stutter Text|String)-Utterer"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stylish-cabal" = callPackage @@ -252165,8 +248684,6 @@ self: { ]; description = "Apply CSS styles to a document tree"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "stylized" = callPackage @@ -252219,8 +248736,6 @@ self: { ]; description = "An applicative functor that seamlessly talks to HTML inputs"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sub-state" = callPackage @@ -252318,7 +248833,6 @@ self: { description = "Type safe interface for programming in subcategories of Hask"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "subleq-toolchain" = callPackage @@ -252426,7 +248940,6 @@ self: { description = "Match / replace substrings with a parser combinators"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "subtitleParser" = callPackage @@ -252503,8 +249016,6 @@ self: { libraryHaskellDepends = [ base ]; description = "An applicative functor to manage successors"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "suffix-array" = callPackage @@ -252655,7 +249166,6 @@ self: { description = "Tool for scaffolding fully configured batteries-included production-level Haskell projects using TUI"; license = lib.licenses.mpl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sump" = callPackage @@ -252674,7 +249184,6 @@ self: { description = "A Haskell interface to SUMP-compatible logic analyzers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sundown" = callPackage @@ -252745,7 +249254,6 @@ self: { description = "Tests for Sunroof"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sunroof-server" = callPackage @@ -252768,7 +249276,6 @@ self: { description = "Monadic Javascript Compiler - Server Utilities"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "super-user-spark" = callPackage @@ -252851,7 +249358,6 @@ self: { description = "Haskell SuperCollider utilities"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "supercollider-midi" = callPackage @@ -252875,7 +249381,6 @@ self: { description = "Demonstrate how to control SuperCollider via ALSA-MIDI"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "superconstraints" = callPackage @@ -252893,7 +249398,6 @@ self: { description = "Access an instance's constraints"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "superdoc" = callPackage @@ -253118,7 +249622,6 @@ self: { description = "Encode and decode separated values (CSV, PSV, ...)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sv-cassava" = callPackage @@ -253141,7 +249644,6 @@ self: { description = "Integration to use sv with cassava's parser"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sv-core" = callPackage @@ -253189,7 +249691,6 @@ self: { description = "sv-core + svfactor"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "svfactor" = callPackage @@ -253288,7 +249789,6 @@ self: { description = "Code generation tool for Quartz code from a SVG"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "svgcairo" = callPackage @@ -253331,7 +249831,6 @@ self: { description = "Optimise SVGs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "svgutils" = callPackage @@ -253541,7 +250040,6 @@ self: { description = "Transparently swapping data from in-memory structures to disk"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) tokyocabinet;}; "swearjure" = callPackage @@ -253562,7 +250060,6 @@ self: { description = "Clojure without alphanumerics"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sweet-egison" = callPackage @@ -253586,7 +250083,6 @@ self: { description = "Shallow embedding implementation of non-linear pattern matching"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "swf" = callPackage @@ -253681,6 +250177,8 @@ self: { ]; description = "SwissTable hash map"; license = lib.licenses.bsd3; + hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "switch" = callPackage @@ -253698,7 +250196,6 @@ self: { description = "Nintendo Switch Controller Library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sws" = callPackage @@ -253722,8 +250219,6 @@ self: { ]; description = "A simple web server for serving directories"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sxml" = callPackage @@ -253974,7 +250469,6 @@ self: { description = "Lambda calculus visualization"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "sym" = callPackage @@ -254001,7 +250495,6 @@ self: { description = "Plot permutations; an addition to the sym package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "symantic" = callPackage @@ -254042,7 +250535,6 @@ self: { description = "Library for reading and writing Atom"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "symantic-base" = callPackage @@ -254120,8 +250612,6 @@ self: { ]; description = "Symantic combinators for deriving clients or a server from an HTTP API"; license = lib.licenses.gpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "symantic-http-client" = callPackage @@ -254140,8 +250630,6 @@ self: { ]; description = "symantic-http applied to the derivation of HTTP clients"; license = lib.licenses.gpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "symantic-http-demo" = callPackage @@ -254168,8 +250656,6 @@ self: { ]; description = "Demo for symantic-http and its companion libraries"; license = lib.licenses.gpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "symantic-http-pipes" = callPackage @@ -254191,8 +250677,6 @@ self: { ]; description = "Streaming support through pipes for symantic-http"; license = lib.licenses.gpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "symantic-http-server" = callPackage @@ -254211,8 +250695,6 @@ self: { ]; description = "symantic-http applied to the derivation of HTTP servers"; license = lib.licenses.gpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "symantic-http-test" = callPackage @@ -254265,7 +250747,6 @@ self: { description = "Symantics for common types"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "symantic-parser" = callPackage @@ -254348,7 +250829,6 @@ self: { description = "Data serialization, communication, and operation verification implementation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "symbol" = callPackage @@ -254454,7 +250934,6 @@ self: { description = "Derivation of symbols and coordinate triplets Library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "symon" = callPackage @@ -254561,7 +251040,6 @@ self: { description = "Haskell bindings for the Syncthing REST API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "synt" = callPackage @@ -254610,8 +251088,6 @@ self: { benchmarkHaskellDepends = [ base criterion deepseq ]; description = "Generic representation and manipulation of abstract syntax"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "syntactical" = callPackage @@ -254641,7 +251117,6 @@ self: { description = "Reversible parsing and pretty-printing"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "syntax-attoparsec" = callPackage @@ -254658,7 +251133,6 @@ self: { description = "Syntax instances for Attoparsec"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "syntax-example" = callPackage @@ -254678,7 +251152,6 @@ self: { description = "Example application using syntax, a library for abstract syntax descriptions"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "syntax-example-json" = callPackage @@ -254698,7 +251171,6 @@ self: { description = "Example JSON parser/pretty-printer"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "syntax-pretty" = callPackage @@ -254714,7 +251186,6 @@ self: { description = "Syntax instance for pretty, the pretty printing library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "syntax-printer" = callPackage @@ -254732,7 +251203,6 @@ self: { description = "Text and ByteString printers for 'syntax'"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "syntax-trees" = callPackage @@ -254786,7 +251256,6 @@ self: { description = "Working with Google's SyntaxNet output files - CoNLL, Tree"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "synthesizer" = callPackage @@ -254952,7 +251421,6 @@ self: { description = "Efficient signal processing using runtime compilation"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "synthesizer-midi" = callPackage @@ -255380,7 +251848,6 @@ self: { description = "An application that regularly logs system stats for later analysis"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "syz" = callPackage @@ -255423,7 +251890,6 @@ self: { description = "tic-tac-toe Rexports for client"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "t3-game" = callPackage @@ -255477,7 +251943,6 @@ self: { description = "Transito Abierto: convenience library when using Takusen and Oracle"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tabl" = callPackage @@ -255726,6 +252191,7 @@ self: { platforms = [ "aarch64-linux" "armv7l-linux" "i686-linux" "x86_64-linux" ]; + hydraPlatforms = lib.platforms.none; }) {inherit (pkgs) gtk3;}; "tag-bits" = callPackage @@ -255755,7 +252221,6 @@ self: { description = "streamlined html tag parser"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tagchup" = callPackage @@ -255855,7 +252320,6 @@ self: { description = "Lists tagged with a type-level natural number representing their length"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tagged-th" = callPackage @@ -255870,7 +252334,6 @@ self: { description = "QuasiQuoter and Template Haskell splices for creating proxies at higher-kinds"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tagged-timers" = callPackage @@ -256093,7 +252556,6 @@ self: { description = "Tagsoup Navigate"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tagsoup-parsec" = callPackage @@ -256141,7 +252603,6 @@ self: { description = "Black magic tagsoup"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tagstream-conduit" = callPackage @@ -256307,7 +252768,6 @@ self: { description = "An implementation of Typed Assembly Language (Morrisett, Walker, Crary, Glew)"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tamarin-prover" = callPackage @@ -256338,7 +252798,6 @@ self: { description = "The Tamarin prover for security protocol analysis"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tamarin-prover-term" = callPackage @@ -256358,7 +252817,6 @@ self: { description = "Term manipulation library for the tamarin prover"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tamarin-prover-theory" = callPackage @@ -256381,7 +252839,6 @@ self: { description = "Term manipulation library for the tamarin prover"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tamarin-prover-utils" = callPackage @@ -256595,7 +253052,6 @@ self: { description = "Generate test-suites from refinement types"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) z3;}; "tart" = callPackage @@ -256638,7 +253094,6 @@ self: { description = "A command line tool for keeping track of tasks you worked on"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "task-distribution" = callPackage @@ -256676,7 +253131,6 @@ self: { description = "Distributed processing of changing tasks"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "taskell" = callPackage @@ -256831,7 +253285,6 @@ self: { description = "BDD tests language and tasty provider"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tasty-bench" = callPackage @@ -256864,8 +253317,6 @@ self: { ]; description = "Check multiple items during a tasty test"; license = lib.licenses.isc; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tasty-dejafu" = callPackage @@ -257016,7 +253467,6 @@ self: { description = "Tasty Tests for groundhog converters"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tasty-hedgehog" = callPackage @@ -257112,8 +253562,6 @@ self: { ]; description = "Render tasty output to HTML"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tasty-hunit" = callPackage @@ -257193,7 +253641,6 @@ self: { description = "automated integration of QuickCheck properties into tasty suites"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tasty-jenkins-xml" = callPackage @@ -257214,7 +253661,6 @@ self: { description = "Render tasty output to both console and XML for Jenkins"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tasty-json" = callPackage @@ -257264,7 +253710,6 @@ self: { description = "Test common laws"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tasty-leancheck" = callPackage @@ -257294,7 +253739,6 @@ self: { description = "Tasty TestTrees for Lens validation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tasty-lua" = callPackage @@ -257426,8 +253870,6 @@ self: { ]; description = "A fancy test runner, including support for golden tests"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tasty-smallcheck" = callPackage @@ -257614,7 +254056,6 @@ self: { description = "Meta tic-tac-toe ncurses game"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tau" = callPackage @@ -257657,7 +254098,6 @@ self: { description = "Transactional variables and data structures with IO hooks"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tcache-AWS" = callPackage @@ -257693,7 +254133,6 @@ self: { description = "TokyoCabinet CLI interface"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tce-conf" = callPackage @@ -257826,7 +254265,6 @@ self: { description = "Test framework wrapper"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tdigest" = callPackage @@ -257869,8 +254307,6 @@ self: { ]; description = "Chart generation from tdigest"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tdlib" = callPackage @@ -257899,7 +254335,6 @@ self: { description = "complete binding to the Telegram Database Library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) tdlib;}; "tdlib-gen" = callPackage @@ -257929,7 +254364,6 @@ self: { description = "Codegen for TDLib"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tdlib-types" = callPackage @@ -257951,7 +254385,6 @@ self: { description = "Types and Functions generated from tdlib api spec"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tdoc" = callPackage @@ -258046,7 +254479,6 @@ self: { description = "Bleeding edge prelude"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "technique" = callPackage @@ -258173,7 +254605,6 @@ self: { description = "Telegram Bot microframework for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "telegram-bot-simple" = callPackage @@ -258205,8 +254636,6 @@ self: { ]; description = "Easy to use library for building Telegram bots"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "telegram-raw-api" = callPackage @@ -258232,7 +254661,6 @@ self: { description = "Servant bindings to the Telegram bot API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "telegram-types" = callPackage @@ -258255,7 +254683,6 @@ self: { description = "Types used in Telegram bot API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "telegraph" = callPackage @@ -258843,7 +255270,6 @@ self: { description = "Haskell wrappers for Core Tensorflow Ops"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tensorflow-logging" = callPackage @@ -258873,7 +255299,6 @@ self: { description = "TensorBoard related functionality"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tensorflow-mnist" = callPackage @@ -258958,7 +255383,6 @@ self: { description = "Friendly layer around TensorFlow bindings"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tensorflow-proto" = callPackage @@ -259082,7 +255506,6 @@ self: { description = "reactive-banana + termbox"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "termbox-bindings" = callPackage @@ -259196,7 +255619,6 @@ self: { description = "Text data type for styled terminal output, including all standard ANSI effects (bold, italic, blinking) and ANSI / 256 / truecolor colors support for Unix and Windows (whenever possible)"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "termination-combinators" = callPackage @@ -259352,7 +255774,6 @@ self: { description = "A Haskell GIS Programming Environment"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {terralib4c = null; translib = null;}; "tersmu" = callPackage @@ -259403,8 +255824,6 @@ self: { ]; description = "Tesla API client"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "test-fixture" = callPackage @@ -259579,7 +255998,6 @@ self: { description = "test-sandbox support for the test-framework package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "test-framework-skip" = callPackage @@ -259712,8 +256130,6 @@ self: { ]; description = "Testing framework"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "test-lib" = callPackage @@ -259827,7 +256243,6 @@ self: { description = "Lightweight development enviroments using test-sandbox"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "test-sandbox-hunit" = callPackage @@ -259840,7 +256255,6 @@ self: { description = "HUnit convenience functions for use with test-sandbox"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "test-sandbox-quickcheck" = callPackage @@ -259857,7 +256271,6 @@ self: { description = "QuickCheck convenience functions for use with test-sandbox"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "test-shouldbe" = callPackage @@ -259892,7 +256305,6 @@ self: { description = "Simple Perl inspired testing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "testCom" = callPackage @@ -259948,7 +256360,6 @@ self: { description = "Create tests and benchmarks together"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "testcontainers" = callPackage @@ -260710,7 +257121,6 @@ self: { description = "Utils for text"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "text-position" = callPackage @@ -260977,7 +257387,6 @@ self: { description = "An efficient finite map from Text to values, based on bytestring-trie"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "text-utf7" = callPackage @@ -261033,8 +257442,6 @@ self: { testHaskellDepends = [ base HTF text ]; description = "Various text utilities"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "text-xml-generic" = callPackage @@ -261151,7 +257558,6 @@ self: { description = "A simple Haskell program to provide tags for Haskell code completion in TextMate"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "textocat-api" = callPackage @@ -261309,7 +257715,6 @@ self: { description = "Alpha equivalence for TH Exp"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "th-bang-compat" = callPackage @@ -261398,7 +257803,6 @@ self: { description = "Test instance context"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "th-data-compat" = callPackage @@ -261596,7 +258000,6 @@ self: { description = "A place to collect orphan instances for Template Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "th-kinds" = callPackage @@ -261900,7 +258303,6 @@ self: { description = "Graph of the subtype relation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "th-utilities" = callPackage @@ -261962,7 +258364,6 @@ self: { description = "Minimalistic actor library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "themoviedb" = callPackage @@ -262064,7 +258465,6 @@ self: { description = "A simple client for the TheoremQuest theorem proving game"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "these" = callPackage @@ -262170,7 +258570,6 @@ self: { description = "Command-line spelling word suggestion tool"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "thock" = callPackage @@ -262661,7 +259060,6 @@ self: { description = "Image thumbnail creation"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "thyme" = callPackage @@ -262730,6 +259128,7 @@ self: { description = "A desktop bar based on WebKit"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; + broken = true; }) {inherit (pkgs) gtk3; inherit (pkgs) webkitgtk;}; "tibetan-utils" = callPackage @@ -262763,7 +259162,6 @@ self: { description = "Useful if reading \"Why FP matters\" by John Hughes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ticker" = callPackage @@ -262801,7 +259199,6 @@ self: { description = "A port of @Data.Binary@"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tictactoe3d" = callPackage @@ -262870,7 +259267,6 @@ self: { description = "Serial support for tidal"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tidal-vis" = callPackage @@ -262985,7 +259381,6 @@ self: { description = "Tiny and Incrementally-Growing HTTP library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tikzsd" = callPackage @@ -263049,7 +259444,6 @@ self: { description = "The Timber Compiler"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "time_1_11_1_2" = callPackage @@ -263137,7 +259531,6 @@ self: { description = "Yet another time library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "time-http" = callPackage @@ -263162,7 +259555,6 @@ self: { description = "Parse and format HTTP/1.1 Date and Time strings"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "time-interval" = callPackage @@ -263186,7 +259578,6 @@ self: { description = "IO Access for time"; license = lib.licenses.gpl2Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "time-lens" = callPackage @@ -263442,7 +259833,6 @@ self: { description = "Distributed systems execution emulation"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "timecalc" = callPackage @@ -263676,7 +260066,6 @@ self: { description = "Prints timestamps after each line evaluated"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "timer-wheel" = callPackage @@ -263926,7 +260315,6 @@ self: { ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "timing-convenience" = callPackage @@ -264008,7 +260396,6 @@ self: { description = "TinyMesh - communicating with auto-meshing sensor network"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tinyXml" = callPackage @@ -264103,7 +260490,6 @@ self: { description = "Convert from Haskell to Tip"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tip-lib" = callPackage @@ -264128,7 +260514,6 @@ self: { description = "tons of inductive problems - support library and tools"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tiphys" = callPackage @@ -264174,7 +260559,6 @@ self: { description = "Testing Infrastructure for Temporal AbstractioNs - GUI to debug temporal programs"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "titan-debug-yampa" = callPackage @@ -264480,7 +260864,6 @@ self: { description = "TLS extra default values and helpers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tls-session-manager" = callPackage @@ -264518,8 +260901,6 @@ self: { executableHaskellDepends = [ base ]; description = "Handle phylogenetic trees"; license = lib.licenses.gpl3Plus; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tmapchan" = callPackage @@ -264630,7 +261011,6 @@ self: { description = "A simple daily journal program"; license = lib.licenses.isc; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tnet" = callPackage @@ -264705,7 +261085,6 @@ self: { description = "Instances for the ToString class"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "toboggan" = callPackage @@ -264725,7 +261104,6 @@ self: { description = "Twitter bot generator"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "todo" = callPackage @@ -264765,7 +261143,6 @@ self: { description = "Easy-to-use TODOs manager"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tofromxml" = callPackage @@ -264968,7 +261345,6 @@ self: { executableHaskellDepends = [ base bytestring gf iconv ]; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tokyocabinet-haskell" = callPackage @@ -265191,8 +261567,6 @@ self: { ]; description = "tonatona plugin for google-server-api"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tonatona-logger" = callPackage @@ -265318,7 +261692,6 @@ self: { description = "Cluster single cells and analyze cell clade relationships"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "toodles" = callPackage @@ -265398,7 +261771,6 @@ self: { description = "Top (typed oriented protocol) API"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "topkata" = callPackage @@ -265418,7 +261790,6 @@ self: { description = "OpenGL Arcade Game"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "topograph" = callPackage @@ -265520,7 +261891,6 @@ self: { description = "Finitely represented total maps"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "total-maps" = callPackage @@ -265600,7 +261970,6 @@ self: { description = "A Tox protocol implementation in Haskell"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "toxcore-c" = callPackage @@ -265627,7 +261996,6 @@ self: { description = "Haskell bindings to the C reference implementation of Tox"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {toxcore = null;}; "toxiproxy-haskell" = callPackage @@ -265705,7 +262073,6 @@ self: { description = "Assorted decision procedures for SAT, SMT, Max-SAT, PB, MIP, etc"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tpar" = callPackage @@ -265743,7 +262110,6 @@ self: { description = "simple, parallel job scheduling"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tpb" = callPackage @@ -265770,7 +262136,6 @@ self: { description = "Applications for interacting with the Pushbullet API"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tpdb" = callPackage @@ -265922,8 +262287,6 @@ self: { ]; description = "Distributed tracing"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tracing-control" = callPackage @@ -266117,7 +262480,6 @@ self: { description = "Tools and a library for working with Trajectory"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "trans-fx-core" = callPackage @@ -266202,7 +262564,6 @@ self: { description = "Text transformer and interpreter"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "transfer-db" = callPackage @@ -266232,7 +262593,6 @@ self: { description = "ODBC database transfer"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "transformations" = callPackage @@ -266254,7 +262614,6 @@ self: { description = "Generic representation of tree transformations"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "transformers_0_5_6_2" = callPackage @@ -266365,7 +262724,6 @@ self: { description = "Sensible conversions between some of the monad transformers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "transformers-eff" = callPackage @@ -266547,7 +262905,6 @@ self: { description = "transient with secure communications"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "translatable-intset" = callPackage @@ -266615,7 +262972,6 @@ self: { description = "Type Safe Web Routing"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "trasa-client" = callPackage @@ -266633,7 +262989,6 @@ self: { description = "Type safe http requests"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "trasa-extra" = callPackage @@ -266652,7 +263007,6 @@ self: { description = "Extra functions for trasa"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "trasa-form" = callPackage @@ -266672,7 +263026,6 @@ self: { description = "generate forms using lucid, ditto and trasa"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "trasa-reflex" = callPackage @@ -266707,7 +263060,6 @@ self: { description = "Type safe web server"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "trasa-th" = callPackage @@ -266725,7 +263077,6 @@ self: { description = "Template Haskell to generate trasa routes"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "traversal-template" = callPackage @@ -267184,7 +263535,6 @@ self: { description = "Treemap related commands for producing foldable TreeMap HTML"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "treersec" = callPackage @@ -267266,7 +263616,6 @@ self: { description = "A PostgreSQL Database Migrator"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "trek-db" = callPackage @@ -267291,7 +263640,6 @@ self: { description = "A PostgreSQL Database Migrator"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "trek-lens" = callPackage @@ -267386,7 +263734,6 @@ self: { description = "triangulation of polygons"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "trie-simple" = callPackage @@ -267436,7 +263783,6 @@ self: { description = "Various trie implementations in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "trifecta" = callPackage @@ -267515,7 +263861,6 @@ self: { description = "Search for, annotate and trim poly-A tail"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tripLL" = callPackage @@ -267576,8 +263921,6 @@ self: { libraryHaskellDepends = [ base ]; description = "Constraints that any type, resp. no type fulfills"; license = lib.licenses.gpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tropical" = callPackage @@ -267647,7 +263990,6 @@ self: { description = "Audio file compressor-limiter"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "trurl" = callPackage @@ -267671,7 +264013,6 @@ self: { description = "Haskell template code generator"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "truthful" = callPackage @@ -267712,7 +264053,6 @@ self: { description = "A Transaction Framework for Happstack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tsetchan" = callPackage @@ -267920,7 +264260,6 @@ self: { description = "An API binding Web.Spock to Database.Beam"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ttask" = callPackage @@ -268122,7 +264461,6 @@ self: { description = "A simple tun/tap library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tup-functor" = callPackage @@ -268138,7 +264476,6 @@ self: { description = "Homogeneous tuples"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tuple" = callPackage @@ -268213,7 +264550,6 @@ self: { description = "Morph between tuples, or convert them from and to HLists"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tuple-ops" = callPackage @@ -268226,7 +264562,6 @@ self: { description = "various operations on n-ary tuples via GHC.Generics"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tuple-sop" = callPackage @@ -268347,7 +264682,6 @@ self: { description = "An implementation of Turing Machine and Automaton"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "turkish-deasciifier" = callPackage @@ -268471,8 +264805,6 @@ self: { ]; description = "An equational theorem prover"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "twee-lib" = callPackage @@ -268516,8 +264848,6 @@ self: { benchmarkHaskellDepends = [ base bytestring criterion megaparsec ]; description = "Command-line tool for twitter"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "twentefp" = callPackage @@ -268547,7 +264877,6 @@ self: { description = "Used as Lab Assignments Environment at the University of Twente"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "twentefp-eventloop-trees" = callPackage @@ -268560,7 +264889,6 @@ self: { description = "Tree type and show functions for lab assignment of University of Twente. Contains RoseTree and RedBlackTree"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "twentefp-graphs" = callPackage @@ -268573,7 +264901,6 @@ self: { description = "Lab Assignments Environment at Univeriteit Twente"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "twentefp-number" = callPackage @@ -268600,7 +264927,6 @@ self: { description = "RoseTree type and show functions for lab assignment of University of Twente"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "twentefp-trees" = callPackage @@ -268613,7 +264939,6 @@ self: { description = "Tree type and show functions for lab assignment of University of Twente. Contains RoseTree and ParseTree"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "twentefp-websockets" = callPackage @@ -268664,7 +264989,6 @@ self: { description = "Rubik's cube solver"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "twfy-api-client" = callPackage @@ -268745,7 +265069,6 @@ self: { description = "Unix Command-Line Twitter and Identica Client"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "twilight-stm" = callPackage @@ -268758,7 +265081,6 @@ self: { description = "STM library with safe irrevocable I/O and inconsistency repair"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "twilio" = callPackage @@ -268806,7 +265128,6 @@ self: { description = "Twilio API interaction"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "twiml" = callPackage @@ -268918,7 +265239,6 @@ self: { description = "A Haskell-based CLI Twitter client"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "twitter-conduit" = callPackage @@ -268949,8 +265269,6 @@ self: { testToolDepends = [ hspec-discover ]; description = "Twitter API package with conduit interface and Streaming API support"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "twitter-enumerator" = callPackage @@ -268970,7 +265288,6 @@ self: { description = "Twitter API package with enumerator interface and Streaming API support"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "twitter-feed" = callPackage @@ -269065,8 +265382,6 @@ self: { testHaskellDepends = [ base smallcheck tasty tasty-smallcheck ]; description = "Text"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "txt-sushi" = callPackage @@ -269181,7 +265496,6 @@ self: { description = "Runtime type assertions for testing"; license = lib.licenses.isc; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "type-booleans" = callPackage @@ -269209,7 +265523,6 @@ self: { description = "Utilities for caching type families results. Sometimes complex type families take long time to compile, so it is proficient to cache them and use the final result without the need of re-computation."; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "type-cereal" = callPackage @@ -269227,7 +265540,6 @@ self: { description = "Type-level serialization of type constructors"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "type-combinators" = callPackage @@ -269259,7 +265571,6 @@ self: { description = "Quasiquoters for the 'type-combinators' package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "type-combinators-singletons" = callPackage @@ -269272,7 +265583,6 @@ self: { description = "Interop between /type-combinators/ and /singletons/"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "type-digits" = callPackage @@ -269285,7 +265595,6 @@ self: { description = "Arbitrary-base type-level digits"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "type-eq" = callPackage @@ -269702,7 +266011,6 @@ self: { description = "Type-level comparison operator"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "type-ord-spine-cereal" = callPackage @@ -269719,7 +266027,6 @@ self: { description = "Generic type-level comparison of types"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "type-prelude" = callPackage @@ -269746,7 +266053,6 @@ self: { description = "Type-level sets"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "type-settheory" = callPackage @@ -269816,7 +266122,6 @@ self: { description = "Type structure analysis"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "type-sub-th" = callPackage @@ -269842,7 +266147,6 @@ self: { description = "Substitute types for other types with Template Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "type-tree" = callPackage @@ -270011,7 +266315,6 @@ self: { description = "Bridge between encoding and typed-encoding packages"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "typed-process" = callPackage @@ -270051,7 +266354,6 @@ self: { description = "Typed and composable spreadsheets"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "typed-streams" = callPackage @@ -270074,7 +266376,6 @@ self: { description = "A stream based replacement for lists"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "typed-uuid" = callPackage @@ -270214,7 +266515,6 @@ self: { description = "Useful type level operations (type families and related operators)"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "typelevel-rewrite-rules" = callPackage @@ -270232,7 +266532,6 @@ self: { description = "Solve type equalities using custom type-level rewrite rules"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "typelevel-tensor" = callPackage @@ -270287,8 +266586,6 @@ self: { testToolDepends = [ hspec-discover ]; description = "Type level numbers using existing Nat functionality"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "typeof" = callPackage @@ -270411,7 +266708,6 @@ self: { description = "A documentation generator for TypeScript Definition files"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "typical" = callPackage @@ -270489,7 +266785,6 @@ self: { description = "Typson Beam Integration"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "typson-core" = callPackage @@ -270530,7 +266825,6 @@ self: { description = "Typson Esqueleto Integration"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "typson-selda" = callPackage @@ -270554,7 +266848,6 @@ self: { description = "Typson Selda Integration"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "tyro" = callPackage @@ -270644,7 +266937,6 @@ self: { description = "Haskell Universal Two Factor helper toolbox library thing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uAgda" = callPackage @@ -270723,7 +267015,6 @@ self: { description = "Uber client for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uberlast" = callPackage @@ -270767,7 +267058,6 @@ self: { description = "The Ucam-Webauth protocol, used by Raven"; license = "(BSD-3-Clause OR Apache-2.0)"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ucam-webauth-types" = callPackage @@ -270974,7 +267264,6 @@ self: { description = "Part of UHC packaged as cabal/hackage installable library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uhc-util" = callPackage @@ -270995,7 +267284,6 @@ self: { description = "UHC utilities"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uhexdump" = callPackage @@ -271148,7 +267436,6 @@ self: { description = "A fast, cache-efficient, concurrent bloom filter"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "unagi-chan" = callPackage @@ -271248,7 +267535,6 @@ self: { description = "Generic support for programming with names and binders"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "unbound-generics" = callPackage @@ -271463,8 +267749,6 @@ self: { libraryHaskellDepends = [ base ]; description = "Tiny package providing unescaping versions of show and print"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "unexceptionalio" = callPackage @@ -271562,7 +267846,6 @@ self: { description = "Event handling for the uniform workbench"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uni-graphs" = callPackage @@ -271579,7 +267862,6 @@ self: { description = "Graphs"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uni-htk" = callPackage @@ -271597,7 +267879,6 @@ self: { description = "Graphical User Interface for Haskell Programs"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uni-posixutil" = callPackage @@ -271614,7 +267895,6 @@ self: { description = "Posix utilities for the uniform workbench"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uni-reactor" = callPackage @@ -271630,7 +267910,6 @@ self: { description = "Reactors for the uniform workbench"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uni-uDrawGraph" = callPackage @@ -271648,7 +267927,6 @@ self: { description = "Graphs binding"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uni-util" = callPackage @@ -271752,7 +268030,6 @@ self: { description = "Unicode normalization using the ICU library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) icu;}; "unicode-prelude" = callPackage @@ -271937,6 +268214,8 @@ self: { ]; description = "Uniform file handling operations"; license = lib.licenses.gpl2Only; + hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "uniform-io" = callPackage @@ -271957,7 +268236,6 @@ self: { description = "Uniform IO over files, network, anything"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) openssl;}; "uniform-pair" = callPackage @@ -272023,6 +268301,7 @@ self: { ]; description = "A uniform base to build apps on"; license = lib.licenses.gpl2Only; + hydraPlatforms = lib.platforms.none; }) {}; "union" = callPackage @@ -272041,8 +268320,6 @@ self: { benchmarkHaskellDepends = [ base criterion deepseq lens ]; description = "Extensible type-safe unions"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "union-find" = callPackage @@ -272297,7 +268574,6 @@ self: { description = "Usage examples for the uniqueness-periods-vector series of packages"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uniqueness-periods-vector-filters" = callPackage @@ -272570,8 +268846,6 @@ self: { ]; description = "A class for finite and recursively enumerable types"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "universe-base" = callPackage @@ -272609,8 +268883,6 @@ self: { libraryHaskellDepends = [ base universe-base ]; description = "Universe instances for types from the base package"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "universe-instances-extended" = callPackage @@ -272628,8 +268900,6 @@ self: { ]; description = "Universe instances for types from selected extra packages"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "universe-instances-trans" = callPackage @@ -272643,8 +268913,6 @@ self: { libraryHaskellDepends = [ base universe-base ]; description = "Universe instances for types from the transformers and mtl packages"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "universe-reverse-instances" = callPackage @@ -272696,7 +268964,6 @@ self: { description = "Construct a Dec's ancestor list"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "universum" = callPackage @@ -272772,7 +269039,6 @@ self: { description = "Comprehensive bindings to fcntl(2)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "unix-handle" = callPackage @@ -272880,7 +269146,6 @@ self: { description = "Straightforward bindings to the posix API"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "unix-time" = callPackage @@ -273115,8 +269380,6 @@ self: { ]; description = "Generalization of io-streams to MonadUnliftIO"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "unlit" = callPackage @@ -273315,7 +269578,6 @@ self: { description = "maybes of numeric values with fewer indirections"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "unpacked-maybe-text" = callPackage @@ -273344,7 +269606,6 @@ self: { description = "An unpacked these data type"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "unpacked-validation" = callPackage @@ -273362,7 +269623,6 @@ self: { description = "An unpacked validation data type"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "unparse-attoparsec" = callPackage @@ -273384,7 +269644,6 @@ self: { description = "An attoparsec roundtrip"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "unroll-ghc-plugin" = callPackage @@ -273467,7 +269726,6 @@ self: { description = "Solve Boggle-like word games"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "unsequential" = callPackage @@ -273580,7 +269838,6 @@ self: { description = "Command-line tool to generate paths for moving upward in a file system"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "up-grade" = callPackage @@ -273717,7 +269974,6 @@ self: { description = "Talk to Urbit from Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "urbit-api" = callPackage @@ -273735,7 +269991,6 @@ self: { description = "Talk to Urbit from Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "urbit-hob" = callPackage @@ -273752,7 +270007,6 @@ self: { description = "Hoon-style atom manipulation and printing functions"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ureader" = callPackage @@ -273777,7 +270031,6 @@ self: { description = "Minimalistic CLI RSS reader"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "urembed" = callPackage @@ -273799,7 +270052,6 @@ self: { description = "Ur/Web static content generator"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uri" = callPackage @@ -273929,7 +270181,6 @@ self: { description = "Read and write URIs (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uri-enumerator-file" = callPackage @@ -273949,7 +270200,6 @@ self: { description = "uri-enumerator backend for the file scheme (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uri-parse" = callPackage @@ -274044,7 +270294,6 @@ self: { description = "Memory efficient url type and parser"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "url-decoders" = callPackage @@ -274168,7 +270417,6 @@ self: { description = "Painfully simple URL deployment"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "urn" = callPackage @@ -274247,7 +270495,6 @@ self: { description = "Communicate with USB devices"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "usb-enumerator" = callPackage @@ -274265,7 +270512,6 @@ self: { description = "Iteratee enumerators for the usb package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "usb-hid" = callPackage @@ -274280,7 +270526,6 @@ self: { description = "Parser and request Library for USB HIDs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "usb-id-database" = callPackage @@ -274301,7 +270546,6 @@ self: { description = "A database of USB identifiers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "usb-iteratee" = callPackage @@ -274319,7 +270563,6 @@ self: { description = "Iteratee enumerators for the usb package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "usb-safe" = callPackage @@ -274337,7 +270580,6 @@ self: { description = "Type-safe communication with USB devices"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "useragents" = callPackage @@ -274367,8 +270609,6 @@ self: { ]; description = "The UserId type and useful instances for web development"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "users" = callPackage @@ -274604,7 +270844,6 @@ self: { description = "Exceptional utilities"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "util-logict" = callPackage @@ -274670,7 +270909,6 @@ self: { description = "Utilities for stateful primitive types and types based on them"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "util-universe" = callPackage @@ -274734,7 +270972,6 @@ self: { description = "Utilities for compiler construction: example programs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uu-cco-hut-parsing" = callPackage @@ -274747,7 +270984,6 @@ self: { description = "Utilities for compiler construction: Feedback wrapper around parser in uulib"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uu-cco-uu-parsinglib" = callPackage @@ -274760,7 +270996,6 @@ self: { description = "Utilities for compiler construction: Feedback wrapper around parser in uu-parsinglib"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uu-interleaved" = callPackage @@ -274886,8 +271121,6 @@ self: { libraryHaskellDepends = [ base diagrams-lib SVGFonts ]; description = "Utility for drawing attribute grammar pictures with the diagrams package"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uuagd" = callPackage @@ -274961,7 +271194,6 @@ self: { description = "UUID parsing using byteverse packages"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uuid-crypto" = callPackage @@ -274981,7 +271213,6 @@ self: { description = "Reversable and secure encoding of object ids as uuids"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uuid-le" = callPackage @@ -275008,6 +271239,8 @@ self: { ]; description = "Orphan instances for the UUID datatype"; license = lib.licenses.bsd3; + hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "uuid-quasi" = callPackage @@ -275099,7 +271332,6 @@ self: { description = "Efficient algorithms for uvector unboxed arrays"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "uxadt" = callPackage @@ -275141,7 +271373,6 @@ self: { description = "interface to Video For Linux Two (V4L2)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "v4l2-examples" = callPackage @@ -275156,7 +271387,6 @@ self: { description = "video for linux two examples"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vabal" = callPackage @@ -275179,7 +271409,6 @@ self: { description = "the cabal companion"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vabal-lib" = callPackage @@ -275229,7 +271458,6 @@ self: { description = "Visualize live Haskell data structures using vacuum, graphviz and cairo"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vacuum-graphviz" = callPackage @@ -275242,7 +271470,6 @@ self: { description = "A library for transforming vacuum graphs into GraphViz output"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vacuum-opengl" = callPackage @@ -275263,7 +271490,6 @@ self: { description = "Visualize live Haskell data structures using vacuum, graphviz and OpenGL"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vacuum-ubigraph" = callPackage @@ -275276,7 +271502,6 @@ self: { description = "Visualize Haskell data structures using vacuum and Ubigraph"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vado" = callPackage @@ -275352,8 +271577,6 @@ self: { testHaskellDepends = [ base hspec QuickCheck ]; description = "Input validation combinator library"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "validated-literals" = callPackage @@ -275745,7 +271968,6 @@ self: { description = "variable-precision floating point"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "variables" = callPackage @@ -275777,6 +271999,8 @@ self: { benchmarkHaskellDepends = [ base criterion mmorph mtl ]; description = "Abstractions for working with variadic functions"; license = lib.licenses.bsd3; + hydraPlatforms = lib.platforms.none; + broken = true; }) {}; "variation" = callPackage @@ -275945,7 +272169,6 @@ self: { description = "patricia tries modeled above VCache"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vcard" = callPackage @@ -275960,7 +272183,6 @@ self: { description = "A library for parsing/printing vCards from/to various formats"; license = "LGPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vcatt" = callPackage @@ -276052,7 +272274,6 @@ self: { description = "GUI library for source code management systems"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vcswrapper" = callPackage @@ -276160,7 +272381,6 @@ self: { description = "Accelerate instances for vect-floating types"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vect-opengl" = callPackage @@ -276384,7 +272604,6 @@ self: { description = "Storable vectors with cpu-independent representation"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vector-extras" = callPackage @@ -276490,7 +272709,6 @@ self: { description = "Instances of the Data.Collections classes for Data.Vector.*"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vector-mmap" = callPackage @@ -276688,7 +272906,6 @@ self: { description = "Text implementation based on unboxed char vector"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vector-th-unbox" = callPackage @@ -276747,8 +272964,6 @@ self: { ]; description = "Easily view Vega or Vega-Lite visualizations"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "venzone" = callPackage @@ -276776,7 +272991,6 @@ self: { description = "ASCII platform-adventure game"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "verbalexpressions" = callPackage @@ -276845,7 +273059,6 @@ self: { description = "JSON instances and JSON Schema for verdict"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "verifiable-expressions" = callPackage @@ -276861,8 +273074,9 @@ self: { ]; description = "An intermediate language for Hoare logic style verification"; license = lib.licenses.asl20; - hydraPlatforms = lib.platforms.none; - broken = true; + platforms = [ + "armv7l-linux" "i686-linux" "x86_64-darwin" "x86_64-linux" + ]; }) {}; "verify" = callPackage @@ -276974,7 +273188,6 @@ self: { description = "Servant combinators for the versioning library"; license = lib.licenses.asl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "versions" = callPackage @@ -277037,7 +273250,6 @@ self: { description = "types for ingesting vflow data with aeson"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vformat" = callPackage @@ -277116,7 +273328,6 @@ self: { description = "VFR waypoints, as published in the AIP (ERSA)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vgrep" = callPackage @@ -277148,8 +273359,6 @@ self: { ]; description = "A pager for grep"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vhd" = callPackage @@ -277281,7 +273490,6 @@ self: { description = "An extensible dead-man's switch system"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vimeta" = callPackage @@ -277308,8 +273516,6 @@ self: { ]; description = "Frontend for video metadata tagging tools"; license = lib.licenses.bsd2; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vimus" = callPackage @@ -277480,7 +273686,6 @@ self: { description = "Initial project template from stack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vinyl-plus" = callPackage @@ -277591,7 +273796,6 @@ self: { description = "An XMMS2 client"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "visual-graphrewrite" = callPackage @@ -277620,7 +273824,6 @@ self: { description = "Visualize the graph-rewrite steps of a Haskell program"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "visual-prof" = callPackage @@ -277784,7 +273987,6 @@ self: { description = "Phase vocoder"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vocoder-audio" = callPackage @@ -277804,7 +274006,6 @@ self: { description = "Phase vocoder for conduit-audio"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vocoder-conduit" = callPackage @@ -277827,7 +274028,6 @@ self: { description = "Phase vocoder for Conduit"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vocoder-dunai" = callPackage @@ -277850,7 +274050,6 @@ self: { description = "Phase vocoder for Dunai and Rhine"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "voicebase" = callPackage @@ -277876,7 +274075,6 @@ self: { description = "Upload audio files to voicebase to get a transcription"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "void" = callPackage @@ -278160,7 +274358,6 @@ self: { description = "Extra vty-ui functionality not included in the core library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vulkan" = callPackage @@ -278185,8 +274382,6 @@ self: { libraryHaskellDepends = [ base ]; description = "Low-level low-overhead vulkan api bindings"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "vulkan-utils" = callPackage @@ -278250,7 +274445,6 @@ self: { description = "JSON wrangling"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wacom-daemon" = callPackage @@ -278321,7 +274515,6 @@ self: { description = "A haskell binding of the Web Audio API ala blank-canvas"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wai" = callPackage @@ -278442,7 +274635,6 @@ self: { description = "Command line runner for Wai apps (using Warp) with TLS, CGI, socket activation & graceful shutdown"; license = lib.licenses.publicDomain; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wai-conduit" = callPackage @@ -278527,7 +274719,6 @@ self: { description = "A web server for the development of WAI compliant web applications"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wai-digestive-functors" = callPackage @@ -278746,8 +274937,6 @@ self: { ]; description = "Wrap WAI applications to run on AWS Lambda"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wai-handler-launch" = callPackage @@ -278794,7 +274983,6 @@ self: { description = "Web Application Interface handler using snap-server. (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wai-handler-webkit" = callPackage @@ -279117,7 +275305,6 @@ self: { description = "Caching middleware for WAI"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wai-middleware-cache-redis" = callPackage @@ -279137,7 +275324,6 @@ self: { description = "Redis backend for wai-middleware-cache"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wai-middleware-caching" = callPackage @@ -279244,7 +275430,6 @@ self: { description = "Wai Middleware for Consul"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wai-middleware-content-type" = callPackage @@ -279278,7 +275463,6 @@ self: { description = "Route to different middlewares based on the incoming Accept header"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wai-middleware-crowd" = callPackage @@ -279525,7 +275709,6 @@ self: { description = "Middleware that communicates to Rollbar"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wai-middleware-route" = callPackage @@ -279547,7 +275730,6 @@ self: { description = "Wai dispatch middleware"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wai-middleware-slack-verify" = callPackage @@ -279698,8 +275880,6 @@ self: { ]; description = "WAI Middleware to validate the request and response bodies"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wai-middleware-verbs" = callPackage @@ -280156,7 +276336,6 @@ self: { description = "Thrift transport layer for Wai"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wai-throttler" = callPackage @@ -280332,7 +276511,6 @@ self: { description = "A generator of comics based on some ascertainable data about the requester"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wallpaper" = callPackage @@ -280545,7 +276723,6 @@ self: { description = "Warp and Wai Library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wasm" = callPackage @@ -280728,7 +276905,6 @@ self: { description = "Parse WaveSurfer files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wavy" = callPackage @@ -280750,7 +276926,6 @@ self: { description = "Process WAVE files in Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wcwidth" = callPackage @@ -280904,7 +277079,6 @@ self: { description = "Bindings for the Mongrel2 web server"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "web-output" = callPackage @@ -280945,7 +277119,6 @@ self: { description = "Monoidally construct web pages"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "web-plugins" = callPackage @@ -281014,7 +277187,6 @@ self: { description = "representations of a web page"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "web-routes" = callPackage @@ -281121,7 +277293,6 @@ self: { description = "portable, type-safe URL routing"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "web-routes-th" = callPackage @@ -281186,7 +277357,6 @@ self: { description = "simple routing library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "web3" = callPackage @@ -281227,7 +277397,6 @@ self: { description = "Web3 API for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "webapi" = callPackage @@ -281255,7 +277424,6 @@ self: { description = "WAI based library for web api"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "webapp" = callPackage @@ -281299,8 +277467,6 @@ self: { ]; description = "Web Authentication API"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "webby" = callPackage @@ -281407,7 +277573,6 @@ self: { description = "Build a WAI Application from Webcrank Resources"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "webdriver" = callPackage @@ -281518,7 +277683,6 @@ self: { description = "Bindings to the WebDriver API"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "webex-teams-api" = callPackage @@ -281861,7 +278025,6 @@ self: { description = "HTTP server library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "webshow" = callPackage @@ -282146,7 +278309,6 @@ self: { description = "Writer monad which uses semiring constraint"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "weighted-regexp" = callPackage @@ -282258,7 +278420,6 @@ self: { description = "A chat interface for playing werewolf in Slack"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "what4" = callPackage @@ -282297,7 +278458,6 @@ self: { description = "Solver-agnostic symbolic values support for issuing queries"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wheb-mongo" = callPackage @@ -282310,7 +278470,6 @@ self: { description = "MongoDB plugin for Wheb"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wheb-redis" = callPackage @@ -282323,7 +278482,6 @@ self: { description = "Redis connection for Wheb"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wheb-strapped" = callPackage @@ -282336,7 +278494,6 @@ self: { description = "Strapped templates for Wheb"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "which" = callPackage @@ -282409,7 +278566,6 @@ self: { description = "Whitespace, an esoteric programming language"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "whois" = callPackage @@ -282494,7 +278650,6 @@ self: { description = "Instances for wide-word"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wigner-symbols" = callPackage @@ -282563,7 +278718,6 @@ self: { description = "Wikipedia EPUB E-Book construction from Firefox history"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wild-bind" = callPackage @@ -282600,8 +278754,6 @@ self: { ]; description = "Graphical indicator for WildBind"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wild-bind-task-x11" = callPackage @@ -282618,8 +278770,6 @@ self: { testHaskellDepends = [ base ]; description = "Task to install and export everything you need to use WildBind in X11"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wild-bind-x11" = callPackage @@ -282724,7 +278874,6 @@ self: { description = "Implements Windows Live Web Authentication and Delegated Authentication"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "winerror" = callPackage @@ -282775,8 +278924,6 @@ self: { ]; description = "A compact, well-typed seralisation format for Haskell values"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "winio" = callPackage @@ -282794,7 +278941,6 @@ self: { description = "I/O library for Windows"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {kernel32 = null; ws2_32 = null;}; "wire-streams" = callPackage @@ -283148,7 +279294,6 @@ self: { description = "ANSI Terminal support with wl-pprint-extras"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wl-pprint-console" = callPackage @@ -283203,7 +279348,6 @@ self: { description = "A color pretty printer with terminfo support"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wl-pprint-text" = callPackage @@ -283234,7 +279378,6 @@ self: { description = "Haskell bindings for the wlc library"; license = lib.licenses.isc; hydraPlatforms = lib.platforms.none; - broken = true; }) {wlc = null;}; "wobsurv" = callPackage @@ -283271,7 +279414,6 @@ self: { description = "A simple and highly performant HTTP file server"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "woe" = callPackage @@ -283341,7 +279483,6 @@ self: { description = "Amazon Simple Workflow Service Wrapper"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "woot" = callPackage @@ -283372,8 +279513,6 @@ self: { testHaskellDepends = [ base smallcheck tasty tasty-smallcheck ]; description = "Words of arbitrary size"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "word-trie" = callPackage @@ -283499,8 +279638,6 @@ self: { benchmarkHaskellDepends = [ base criterion pandoc text ]; description = "Get word counts and distributions"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wordcloud" = callPackage @@ -283738,7 +279875,6 @@ self: { description = "Utilities (e.g. Googling the clipboard contents) for the `workflow` pacakge"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "workflow-osx" = callPackage @@ -283783,7 +279919,6 @@ self: { description = "manipulate `workflow-types:Workflow`'s"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "workflow-types" = callPackage @@ -283803,7 +279938,6 @@ self: { description = "Automate keyboard\\/mouse\\/clipboard\\/application interaction"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "workflow-windows" = callPackage @@ -283907,7 +280041,6 @@ self: { description = "Lazy wrapper to HaXML, HXT, TagSoup via custom XML tree structure"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wrecker" = callPackage @@ -283947,7 +280080,6 @@ self: { description = "An HTTP Performance Benchmarker"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wrecker-ui" = callPackage @@ -283981,7 +280113,6 @@ self: { description = "A web interface for Wrecker, the HTTP Performance Benchmarker"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wreq" = callPackage @@ -284143,7 +280274,6 @@ self: { description = "Colour space transformations and metrics"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "write-buffer-core" = callPackage @@ -284205,7 +280335,6 @@ self: { description = "WriteT and RWST monad transformers (Reexport with all dependencies)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "writer-cps-lens" = callPackage @@ -284319,7 +280448,6 @@ self: { description = "A simple CLI utility for interacting with a websocket"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ws-chans" = callPackage @@ -284403,8 +280531,6 @@ self: { ]; description = "Terminal emulator over websockets"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wsjtx-udp" = callPackage @@ -284444,7 +280570,6 @@ self: { description = "A-little-higher-level WebSocket client"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wstunnel" = callPackage @@ -284502,7 +280627,6 @@ self: { description = "GTK tools within Wojcik Tool Kit"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wu-wei" = callPackage @@ -284519,7 +280643,6 @@ self: { description = "Unimportant Unix adminstration tool"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wumpus-basic" = callPackage @@ -284536,7 +280659,6 @@ self: { description = "Basic objects and system code built on Wumpus-Core"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wumpus-core" = callPackage @@ -284568,7 +280690,6 @@ self: { description = "High-level drawing objects built on Wumpus-Basic"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wumpus-microprint" = callPackage @@ -284585,7 +280706,6 @@ self: { description = "Microprints - \"greek-text\" pictures"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wumpus-tree" = callPackage @@ -284603,7 +280723,6 @@ self: { description = "Drawing trees"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wuss" = callPackage @@ -284646,7 +280765,6 @@ self: { description = "Try to avoid the asteroids with your space ship"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wxFruit" = callPackage @@ -284662,7 +280780,6 @@ self: { description = "An implementation of Fruit using wxHaskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wxSimpleCanvas" = callPackage @@ -284675,7 +280792,6 @@ self: { description = "Simple zoomable canvas for wxHaskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wxc" = callPackage @@ -284755,7 +280871,6 @@ self: { description = "An example of how to implement a basic notepad with wxHaskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wxturtle" = callPackage @@ -284772,7 +280887,6 @@ self: { description = "turtle like LOGO with wxHaskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "wybor" = callPackage @@ -284813,7 +280927,6 @@ self: { description = "An autoresponder for Dragon Go Server"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "x-dsp" = callPackage @@ -285110,7 +281223,6 @@ self: { description = "A wget-like utility for retrieving files from XDCC bots on IRC"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xdg-basedir" = callPackage @@ -285172,8 +281284,6 @@ self: { ]; description = "Parse Graphviz xdot files and interactively view them using GTK and Cairo"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xeno" = callPackage @@ -285314,7 +281424,6 @@ self: { description = "Atom cache for XHB"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xhb-ewmh" = callPackage @@ -285332,7 +281441,6 @@ self: { description = "EWMH utilities for XHB"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xhtml_3000_2_2_1" = callPackage @@ -285589,8 +281697,6 @@ self: { testHaskellDepends = [ base ]; description = "Xlsx table cell value extraction utility"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xlsx-templater" = callPackage @@ -285657,7 +281763,6 @@ self: { description = "Parse XML catalog files (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xml-conduit" = callPackage @@ -285808,7 +281913,6 @@ self: { description = "Pure-Haskell utilities for dealing with XML with the enumerator package. (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xml-enumerator-combinators" = callPackage @@ -285827,7 +281931,6 @@ self: { description = "Parser combinators for xml-enumerator and compatible XML parsers"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xml-extractors" = callPackage @@ -285986,7 +282089,6 @@ self: { description = "Monadic extensions to the xml package"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xml-optics" = callPackage @@ -286043,7 +282145,6 @@ self: { description = "XML parser which uses simple-pipe"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xml-prettify" = callPackage @@ -286081,7 +282182,6 @@ self: { description = "Push XML from/to client to/from server over XMPP or HTTP"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xml-query" = callPackage @@ -286112,7 +282212,6 @@ self: { description = "A binding for the \"xml-query\" and \"xml-conduit\" libraries"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xml-query-xml-types" = callPackage @@ -286137,7 +282236,6 @@ self: { description = "An interpreter of \"xml-query\" queries for the \"xml-types\" documents"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xml-to-json" = callPackage @@ -286195,7 +282293,6 @@ self: { description = "Typed XML encoding for an xml-conduit backend"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xml-tydom-core" = callPackage @@ -286281,7 +282378,6 @@ self: { description = "Convert BLAST output in XML format to CSV or HTML"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xmlbf" = callPackage @@ -286414,7 +282510,6 @@ self: { description = "Show tv channels in the terminal"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xmms2-client" = callPackage @@ -286432,7 +282527,6 @@ self: { description = "An XMMS2 client library"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xmms2-client-glib" = callPackage @@ -286446,7 +282540,6 @@ self: { description = "An XMMS2 client library — GLib integration"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xmobar" = callPackage @@ -286583,7 +282676,6 @@ self: { description = "Third party extensions for xmonad"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xmonad-contrib-gpl" = callPackage @@ -286796,7 +282888,6 @@ self: { description = "XMPP implementation using simple-PIPE"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xor" = callPackage @@ -286880,7 +282971,6 @@ self: { description = "text builder for xournal file format"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xournal-convert" = callPackage @@ -286903,7 +282993,6 @@ self: { description = "convert utility for xoj files"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xournal-parser" = callPackage @@ -286924,7 +283013,6 @@ self: { description = "Xournal file parser"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xournal-render" = callPackage @@ -286943,7 +283031,6 @@ self: { description = "Xournal file renderer"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xournal-types" = callPackage @@ -287121,7 +283208,6 @@ self: { description = "eXtended & Typed Controls for wxHaskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "xtest" = callPackage @@ -287369,7 +283455,6 @@ self: { description = "Enumerator-based interface to YAJL, an event-based JSON implementation"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yak" = callPackage @@ -287433,7 +283518,6 @@ self: { description = "A wrapper of servant"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yam-app" = callPackage @@ -287493,7 +283577,6 @@ self: { description = "Yam DataSource Middleware"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yam-job" = callPackage @@ -287520,7 +283603,6 @@ self: { description = "Yam Logger"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yam-redis" = callPackage @@ -287538,7 +283620,6 @@ self: { description = "Yam Redis Middleware"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yam-servant" = callPackage @@ -287578,7 +283659,6 @@ self: { description = "Yam transaction"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yam-transaction-odbc" = callPackage @@ -287592,7 +283672,6 @@ self: { ]; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yam-transaction-postgresql" = callPackage @@ -287637,7 +283716,6 @@ self: { description = "Yam Web"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yamemo" = callPackage @@ -287796,7 +283874,6 @@ self: { description = "Scotty server backend for yaml-rpc"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yaml-rpc-snap" = callPackage @@ -287814,7 +283891,6 @@ self: { description = "Snap server backend for yaml-rpc"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yaml-union" = callPackage @@ -287869,7 +283945,6 @@ self: { description = "Flexible declarative YAML parsing toolkit"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yaml2owl" = callPackage @@ -288031,8 +284106,6 @@ self: { ]; description = "Testing library for Yampa"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yampa2048" = callPackage @@ -288205,7 +284278,6 @@ self: { description = "Image IO for Yarr library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) libdevil;}; "yasi" = callPackage @@ -288225,8 +284297,6 @@ self: { testToolDepends = [ tasty-discover ]; description = "Yet another string interpolator"; license = lib.licenses.cc0; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yate" = callPackage @@ -288266,7 +284336,6 @@ self: { description = "yet another visual editor"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yaya" = callPackage @@ -288363,7 +284432,6 @@ self: { description = "Additional utilities to work with Yhc Core"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yeamer" = callPackage @@ -288400,7 +284468,6 @@ self: { description = "Yesod-based server for interactive presentation slides"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yeganesh" = callPackage @@ -288479,7 +284546,6 @@ self: { description = "YesQL-style SQL database abstraction (legacy compatibility wrapper)"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yeshql-core" = callPackage @@ -288642,7 +284708,6 @@ self: { description = "Automatically generate article previews for a yesod site"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-auth" = callPackage @@ -288895,7 +284960,6 @@ self: { description = "LDAP Authentication for Yesod"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-auth-ldap-mediocre" = callPackage @@ -288955,7 +285019,6 @@ self: { description = "A yesod-auth plugin for LTI 1.3"; license = lib.licenses.lgpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-auth-nopassword" = callPackage @@ -289012,8 +285075,6 @@ self: { testHaskellDepends = [ base hspec uri-bytestring ]; description = "OAuth 2.0 authentication plugins"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-auth-pam" = callPackage @@ -289133,7 +285194,6 @@ self: { description = "Helper functions for using yesod with colonnade"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-comments" = callPackage @@ -289196,7 +285256,6 @@ self: { description = "Continuations for Yesod"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-core" = callPackage @@ -289413,7 +285472,6 @@ self: { description = "Example programs using the Yesod Web Framework. (deprecated)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) sqlite;}; "yesod-fast-devel" = callPackage @@ -289456,8 +285514,6 @@ self: { ]; description = "Utilities for using the Fay Haskell-to-JS compiler with Yesod"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-fb" = callPackage @@ -289700,7 +285756,6 @@ self: { description = "Code for using the ip package with yesod"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-job-queue" = callPackage @@ -289798,7 +285853,6 @@ self: { description = "Yesod library for MangoPay API access"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-markdown" = callPackage @@ -289817,8 +285871,6 @@ self: { testHaskellDepends = [ base blaze-html hspec text ]; description = "Tools for using markdown in a yesod application"; license = lib.licenses.gpl2Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-media-simple" = callPackage @@ -289875,8 +285927,6 @@ self: { time unliftio unliftio-core wai-extra yesod yesod-core yesod-test ]; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-paginate" = callPackage @@ -289947,7 +285997,6 @@ self: { description = "Yesod plugin to use PayPal with the paypal-rest-client library"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-persistent" = callPackage @@ -290061,7 +286110,6 @@ self: { description = "Meta package for Yesod (deprecated)"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-pnotify" = callPackage @@ -290117,7 +286165,6 @@ self: { description = "PureScript integration for Yesod"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-raml" = callPackage @@ -290166,7 +286213,6 @@ self: { description = "The raml helper executable"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-raml-docs" = callPackage @@ -290184,7 +286230,6 @@ self: { description = "A html documentation generator library for RAML"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-raml-mock" = callPackage @@ -290209,7 +286254,6 @@ self: { description = "A mock-handler generator library from RAML"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-recaptcha" = callPackage @@ -290303,7 +286347,6 @@ self: { description = "generate TypeScript routes for Yesod"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-rst" = callPackage @@ -290376,7 +286419,6 @@ self: { description = "Redis-Powered Sessions for Haskell"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yesod-sitemap" = callPackage @@ -291245,7 +287287,6 @@ self: { description = "CUI FTP client like 'ftp', 'ncftp'"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yjftp-libs" = callPackage @@ -291260,7 +287301,6 @@ self: { description = "CUI FTP client like 'ftp', 'ncftp'"; license = "GPL"; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yjsvg" = callPackage @@ -291312,8 +287352,6 @@ self: { libraryHaskellDepends = [ base free mtl ]; description = "A truly tiny monadic parsing library"; license = lib.licenses.mit; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yoda" = callPackage @@ -291360,7 +287398,6 @@ self: { description = "Generic Programming with Disbanded Data Types"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "york-lava" = callPackage @@ -291373,7 +287410,6 @@ self: { description = "A library for digital circuit description"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "youtube" = callPackage @@ -291415,7 +287451,6 @@ self: { description = "A YQL engine to execute Open Data Tables"; license = lib.licenses.bsd2; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yst" = callPackage @@ -291468,8 +287503,6 @@ self: { testHaskellDepends = [ base MonadRandom random yu-utils ]; description = "Auth module for Yu"; license = lib.licenses.gpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yu-core" = callPackage @@ -291500,7 +287533,6 @@ self: { description = "The launcher for Yu"; license = lib.licenses.gpl3Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yu-tool" = callPackage @@ -291543,8 +287575,6 @@ self: { ]; description = "Utils for Yu"; license = lib.licenses.gpl3Only; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yuiGrid" = callPackage @@ -291581,7 +287611,6 @@ self: { description = "A transcendental HTML parser gently wrapping the HXT library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yx" = callPackage @@ -291594,8 +287623,6 @@ self: { testHaskellDepends = [ array base bytestring hspec mtl ]; description = "Row-major coordinates"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "yxdb-utils" = callPackage @@ -291749,7 +287776,6 @@ self: { description = "lojban parser (zasni gerna)"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "zbar" = callPackage @@ -291763,8 +287789,6 @@ self: { libraryToolDepends = [ c2hs ]; description = "zbar bindings in Haskell"; license = lib.licenses.bsd3; - hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) zbar;}; "zcache" = callPackage @@ -291956,7 +287980,6 @@ self: { description = "Zephyr, tree-shaking for the PureScript language"; license = lib.licenses.mpl20; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "zero" = callPackage @@ -291990,7 +288013,6 @@ self: { description = "Post to 0bin services"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "zeromq-haskell" = callPackage @@ -292028,7 +288050,6 @@ self: { description = "Conduit bindings for zeromq3-haskell"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "zeromq3-haskell" = callPackage @@ -292052,7 +288073,6 @@ self: { description = "Bindings to ZeroMQ 3.x"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) zeromq;}; "zeromq4-clone-pattern" = callPackage @@ -292186,7 +288206,6 @@ self: { description = "ZeroTH - remove unnecessary TH dependencies"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "zettelkast" = callPackage @@ -292254,7 +288273,6 @@ self: { description = "zifter-cabal"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "zifter-git" = callPackage @@ -292267,7 +288285,6 @@ self: { description = "zifter-git"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "zifter-google-java-format" = callPackage @@ -292284,7 +288301,6 @@ self: { description = "zifter-google-java-format"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "zifter-hindent" = callPackage @@ -292301,7 +288317,6 @@ self: { description = "zifter-hindent"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "zifter-hlint" = callPackage @@ -292317,7 +288332,6 @@ self: { description = "zifter-hlint"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "zifter-stack" = callPackage @@ -292338,7 +288352,6 @@ self: { description = "zifter-stack"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "zigbee-znet25" = callPackage @@ -292569,7 +288582,6 @@ self: { description = "Generic zipper for families of recursive datatypes"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "zipper-extra" = callPackage @@ -292613,7 +288625,6 @@ self: { description = "A simple lens-based, generic, heterogenous, type-checked zipper library"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ziptastic-client" = callPackage @@ -292636,7 +288647,6 @@ self: { description = "A type-safe client for the Ziptastic API for doing forward and reverse geocoding"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "ziptastic-core" = callPackage @@ -292719,7 +288729,6 @@ self: { description = "Enumerator interface for zlib compression"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "zlib-lens" = callPackage @@ -292770,7 +288779,6 @@ self: { description = "Command-line tool for ZeroMQ"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "zmidi-core" = callPackage @@ -292884,7 +288892,6 @@ self: { description = "A streamable, seekable, zoomable cache file format"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "zoom-cache-pcm" = callPackage @@ -292902,7 +288909,6 @@ self: { description = "Library for zoom-cache PCM audio codecs"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "zoom-cache-sndfile" = callPackage @@ -292923,7 +288929,6 @@ self: { description = "Tools for generating zoom-cache-pcm files"; license = lib.licenses.lgpl21Only; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "zoom-refs" = callPackage @@ -292951,7 +288956,6 @@ self: { description = "A haskell binding to Apache Zookeeper C library(mt) using Haskell Z project"; license = lib.licenses.bsd3; hydraPlatforms = lib.platforms.none; - broken = true; }) {inherit (pkgs) zookeeper_mt;}; "zot" = callPackage @@ -293152,7 +289156,6 @@ self: { description = "A lisp processor, An inline-lisp, in Haskell"; license = lib.licenses.mit; hydraPlatforms = lib.platforms.none; - broken = true; }) {}; "zuul" = callPackage