Skip to content

Commit 02089f0

Browse files
committed
Update nix-tools dependencies to build with GHC 9.10.1 (input-output-hk#2263)
* Update nix-tools dependencies to build with GHC 9.10.1 - Re-organise some of nix-tools modules - Vendor-in custom ProjectPlanOutput - Bump pinned haskell.nix * Bump Cabal-syntax commit * Restore nix-tools support for GHC 9.2
1 parent 8a8c57c commit 02089f0

File tree

10 files changed

+560
-170
lines changed

10 files changed

+560
-170
lines changed

materialized/nix-tools/.plan.nix/nix-tools.nix

Lines changed: 71 additions & 43 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

materialized/nix-tools/default.nix

Lines changed: 1 addition & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

nix-tools/nix-tools/hackage2nix/Main.hs

Lines changed: 23 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -1,16 +1,20 @@
1+
{-# LANGUAGE CPP #-}
12
{-# LANGUAGE OverloadedStrings #-}
23
{-# LANGUAGE NamedFieldPuns #-}
34
{-# LANGUAGE LambdaCase #-}
45

5-
module Main where
6+
module Main (main) where
67

78
import Cabal2Nix
89
import Cabal2Nix.Util ( quoted )
10+
#if !MIN_VERSION_base(4, 17, 0)
911
import Control.Applicative ( liftA2 )
12+
#endif
1013
import Control.Monad.Trans.State.Strict
1114
import Crypto.Hash.SHA256 ( hash )
1215
import qualified Data.ByteString.Base16 as Base16
1316
import qualified Data.ByteString.Char8 as BS
17+
import Data.Char ( isUpper )
1418
import Data.Foldable ( toList
1519
, for_
1620
)
@@ -53,7 +57,6 @@ import System.Environment ( getArgs )
5357
import System.FilePath ( (</>)
5458
, (<.>)
5559
)
56-
import Data.Char (isUpper)
5760

5861
-- Avoid issues with case insensitive file systems by escaping upper case
5962
-- characters with a leading _ character.
@@ -67,27 +70,31 @@ main :: IO ()
6770
main = do
6871
out:rest <- getArgs
6972
(inp, src) <- case rest of
70-
[tarball, url, hash] -> return (tarball, Just $ Repo url (Just hash))
73+
[tarball, url, sha256] -> return (tarball, Just $ Repo url (Just sha256))
7174
[tarball, url] -> return (tarball, Just $ Repo url Nothing)
7275
[tarball] -> return (tarball, Nothing)
7376
[] -> hackageTarball >>= \tarball -> return (tarball, Nothing)
77+
_ -> error "Usage: hackage2nix [tarball [url [hash]]]"
7478

7579
db <- U.readTarball Nothing inp
7680

7781
let (nixFiles, cabalFiles) =
7882
runState (fmap (toList . (Seq.sortOn fst)) $ foldMapWithKeyA package2nix db) mempty
7983
createDirectoryIfMissing False out
80-
writeFile (out </> "default.nix") $
81-
"with builtins; mapAttrs (_: mapAttrs (_: data: rec {\n\
82-
\ inherit (data) sha256;\n\
83-
\ revisions = data.revisions // {\n\
84-
\ default = revisions.\"${data.revisions.default}\";\n\
85-
\ };\n\
86-
\})) {\n"
87-
-- Import all the per package nix files
88-
<> mconcat (map (\(pname, _) ->
89-
" " <> quoted pname <> " = import ./nix/" <> escapeUpperCase pname <> ".nix;\n") nixFiles)
90-
<> "}\n"
84+
writeFile (out </> "default.nix") $ unlines [
85+
"with builtins; mapAttrs (_: mapAttrs (_: data: rec {",
86+
" inherit (data) sha256;",
87+
" revisions = data.revisions // {",
88+
" default = revisions.\"${data.revisions.default}\";",
89+
" };",
90+
"})) {",
91+
-- Import all the per package nix files
92+
unlines [
93+
" " <> quoted pname <> " = import ./nix/" <> escapeUpperCase pname <> ".nix;"
94+
| (pname, _) <- nixFiles
95+
],
96+
"}"
97+
]
9198

9299
createDirectoryIfMissing False (out </> "nix")
93100
for_ nixFiles $ \(pname, nix) ->
@@ -127,9 +134,9 @@ version2nix pname vnum (U.VersionData { U.cabalFileRevisions, U.metaFile }) =
127134
do
128135
revisionBindings <- sequenceA
129136
$ zipWith (revBindingJson pname vnum) cabalFileRevisions [0 ..]
130-
let hash = decodeUtf8 $ fromString $ P.parseMetaData pname vnum metaFile Map.! "sha256"
137+
let sha256 = decodeUtf8 $ fromString $ P.parseMetaData pname vnum metaFile Map.! "sha256"
131138
return $ Seq.singleton (quoted (fromPretty vnum), mkNonRecSet
132-
[ "sha256" $= mkStr hash
139+
[ "sha256" $= mkStr sha256
133140
, "revisions" $= mkNonRecSet
134141
( map (uncurry ($=)) revisionBindings
135142
++ ["default" $= mkStr (fst (last revisionBindings))]

0 commit comments

Comments
 (0)