Skip to content

Commit 3335e43

Browse files
committed
Include most of #6
#6 included "Per component building, and hackage DB", this PR only pulls in the relevant hackage-db logic. The per component building (nix) will be a separate PR.
1 parent 401f2c5 commit 3335e43

File tree

6 files changed

+119
-9
lines changed

6 files changed

+119
-9
lines changed

Diff for: .gitmodules

+3
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
[submodule "hackage-db"]
2+
path = hackage-db
3+
url = https://github.com/ElvishJerricco/hackage-db.git

Diff for: cabal.project

+1-1
Original file line numberDiff line numberDiff line change
@@ -1 +1 @@
1-
packages: .
1+
packages: . hackage-db

Diff for: hackage-db

Submodule hackage-db added at 84ca9fc

Diff for: hackage2nix/Main.hs

+87
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,87 @@
1+
{-# LANGUAGE OverloadedStrings #-}
2+
{-# LANGUAGE NamedFieldPuns #-}
3+
4+
module Main
5+
where
6+
7+
import Cabal2Nix
8+
import Cabal2Nix.Util ( quoted )
9+
import Crypto.Hash.SHA256 ( hash
10+
, hashlazy
11+
)
12+
import qualified Data.ByteString.Base16 as Base16
13+
import qualified Data.ByteString.Char8 as BS
14+
import qualified Data.ByteString.Lazy as BL
15+
import Data.Foldable ( toList )
16+
import qualified Data.Map as Map
17+
import qualified Data.Sequence as Seq
18+
import Data.String ( IsString(fromString) )
19+
import Data.Text.Encoding ( decodeUtf8 )
20+
import Distribution.Hackage.DB ( hackageTarball )
21+
import qualified Distribution.Hackage.DB.Parsed
22+
as P
23+
import Distribution.Hackage.DB.Parsed ( parseMetaData
24+
, parseVersionData
25+
)
26+
import Distribution.Hackage.DB.Unparsed
27+
import Distribution.Pretty ( prettyShow
28+
, Pretty
29+
)
30+
import Nix.Expr
31+
import Nix.Pretty ( prettyNix )
32+
import System.Directory ( createDirectoryIfMissing )
33+
import System.Environment ( getArgs )
34+
import System.FilePath ( (</>)
35+
, (<.>)
36+
)
37+
38+
main :: IO ()
39+
main = do
40+
[out] <- getArgs
41+
db <- readTarball Nothing =<< hackageTarball
42+
43+
let defaultNix = seqToSet $ Map.foldMapWithKey package2nix db
44+
createDirectoryIfMissing False out
45+
writeFile (out </> "default.nix") $ show $ prettyNix defaultNix
46+
47+
_ <- forWithKey db $ \pname (PackageData { versions }) ->
48+
forWithKey versions $ \vnum vdata@(VersionData { cabalFileRevisions }) ->
49+
let parsedVData = parseVersionData pname vnum vdata
50+
writeFiles gpd cabalFile revNum = do
51+
let dir = out </> packagePath pname </> fromPretty vnum
52+
revPath = dir </> revName revNum
53+
createDirectoryIfMissing True dir
54+
BL.writeFile (revPath <.> "cabal") cabalFile
55+
writeFile (revPath <.> "nix") $ show $ prettyNix $ gpd2nix Nothing Nothing gpd
56+
in sequence $ zipWith3 writeFiles
57+
(toList (P.cabalFileRevisions parsedVData))
58+
cabalFileRevisions
59+
[(0 :: Int) ..]
60+
return ()
61+
where
62+
forWithKey :: Applicative f => Map.Map k v -> (k -> v -> f x) -> f (Map.Map k x)
63+
forWithKey = flip Map.traverseWithKey
64+
seqToSet = mkNonRecSet . toList
65+
fromPretty :: (Pretty a, IsString b) => a -> b
66+
fromPretty = fromString . prettyShow
67+
package2nix pname (PackageData { versions }) =
68+
Seq.singleton $ quoted (fromPretty pname) $= seqToSet
69+
(Map.foldMapWithKey (version2nix pname) versions)
70+
version2nix pname vnum (VersionData { cabalFileRevisions, metaFile }) =
71+
Seq.singleton $ quoted (fromPretty vnum) $= mkRecSet
72+
( ("revision" $= mkSym (revName $ length cabalFileRevisions - 1))
73+
: ("sha256" $= mkStr (fromString $ parseMetaData pname vnum metaFile Map.! "sha256"))
74+
: zipWith (revBinding (packagePath pname) vnum) cabalFileRevisions [(0 :: Int) ..]
75+
)
76+
revName revNum = "r" <> fromString (show revNum)
77+
revBinding ppath vnum cabalFile revNum =
78+
let name :: (IsString a, Semigroup a) => a
79+
name = revName revNum
80+
revPath = "." </> ppath </> fromPretty vnum </> name
81+
in name $= mkNonRecSet
82+
[ "outPath" $= mkRelPath (revPath <.> "nix")
83+
, "cabalFile" $= mkRelPath (revPath <.> "cabal")
84+
, "cabalSha256" $= mkStr (decodeUtf8 $ Base16.encode $ hashlazy cabalFile)
85+
]
86+
packagePath pname =
87+
BS.unpack (BS.take 30 $ Base16.encode $ hash $ fromPretty pname) ++ "-" ++ fromPretty pname

Diff for: lib/Cabal2Nix.hs

+9-8
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
{-# LANGUAGE OverloadedStrings #-}
33
{-# LANGUAGE FlexibleInstances #-}
44

5-
module Cabal2Nix (cabal2nix, Src(..), CabalFile(..), CabalFileGenerator(..), cabalFilePath, cabalFilePkgName) where
5+
module Cabal2Nix (cabal2nix, gpd2nix, Src(..), CabalFile(..), CabalFileGenerator(..), cabalFilePath, cabalFilePkgName) where
66

77
import Distribution.PackageDescription.Parsec (readGenericPackageDescription, parseGenericPackageDescriptionMaybe)
88
import Distribution.Verbosity (normal)
@@ -48,7 +48,7 @@ pkgs, hsPkgs, flags :: Text
4848
pkgs = "pkgs"
4949
hsPkgs = "hsPkgs"
5050
pkgconfPkgs = "pkgconfPkgs"
51-
flags = "_flags"
51+
flags = "flags"
5252

5353
($//?) :: NExpr -> Maybe NExpr -> NExpr
5454
lhs $//? (Just e) = lhs $// e
@@ -76,13 +76,14 @@ genExtra Hpack = mkNonRecSet [ "cabal-generator" $= mkStr "hpack" ]
7676

7777
cabal2nix :: Maybe Src -> CabalFile -> IO NExpr
7878
cabal2nix src = \case
79-
(OnDisk path) -> fmap (go Nothing)
79+
(OnDisk path) -> fmap (gpd2nix Nothing src)
8080
$ readGenericPackageDescription normal path
81-
(InMemory gen path body) -> fmap (go (Just $ genExtra gen))
81+
(InMemory gen path body) -> fmap (gpd2nix (Just $ genExtra gen) src)
8282
$ maybe (error "Failed to parse in-memory cabal file") pure (parseGenericPackageDescriptionMaybe body)
83-
where go :: Maybe NExpr -> GenericPackageDescription -> NExpr
84-
go extra gpd = mkFunction args . lets gpd $ toNix gpd $//? (toNix <$> src) $//? extra
85-
args :: Params NExpr
83+
84+
gpd2nix :: Maybe NExpr -> Maybe Src -> GenericPackageDescription -> NExpr
85+
gpd2nix extra src gpd = mkFunction args . lets gpd $ toNix gpd $//? (toNix <$> src) $//? extra
86+
where args :: Params NExpr
8687
args = mkParamset [ ("system", Nothing)
8788
, ("compiler", Nothing)
8889
, ("flags", Just $ mkNonRecSet [])
@@ -184,7 +185,7 @@ mkSysDep :: String -> SysDependency
184185
mkSysDep = SysDependency
185186

186187
instance ToNixExpr GenericPackageDescription where
187-
toNix gpd = mkNonRecSet $ [ "flags" $= mkSym flags -- keep track of the final flags; and allow them to be inspected
188+
toNix gpd = mkNonRecSet $ [ "flags" $= (mkNonRecSet . fmap toNixBinding $ genPackageFlags gpd)
188189
, "package" $= (toNix (packageDescription gpd))
189190
, "components" $= components ]
190191
where packageName = fromString . show . disp . pkgName . package . packageDescription $ gpd

Diff for: nix-tools.cabal

+18
Original file line numberDiff line numberDiff line change
@@ -65,6 +65,24 @@ executable hashes-to-nix
6565
hs-source-dirs: hashes2nix
6666
default-language: Haskell2010
6767

68+
executable hackage-to-nix
69+
ghc-options: -Wall
70+
main-is: Main.hs
71+
build-depends: base >=4.11 && <4.12
72+
, nix-tools
73+
, hackage-db
74+
, hnix
75+
, Cabal
76+
, containers
77+
, bytestring
78+
, text
79+
, cryptohash-sha256
80+
, base16-bytestring
81+
, filepath
82+
, directory
83+
hs-source-dirs: hackage2nix
84+
default-language: Haskell2010
85+
6886
executable plan-to-nix
6987
ghc-options: -Wall
7088
main-is: Main.hs

0 commit comments

Comments
 (0)