Skip to content

Commit

Permalink
Include most of #6
Browse files Browse the repository at this point in the history
 #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.
  • Loading branch information
angerman committed Oct 30, 2018
1 parent 401f2c5 commit 3335e43
Show file tree
Hide file tree
Showing 6 changed files with 119 additions and 9 deletions.
3 changes: 3 additions & 0 deletions .gitmodules
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
[submodule "hackage-db"]
path = hackage-db
url = https://github.com/ElvishJerricco/hackage-db.git
2 changes: 1 addition & 1 deletion cabal.project
Original file line number Diff line number Diff line change
@@ -1 +1 @@
packages: .
packages: . hackage-db
1 change: 1 addition & 0 deletions hackage-db
Submodule hackage-db added at 84ca9f
87 changes: 87 additions & 0 deletions hackage2nix/Main.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,87 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NamedFieldPuns #-}

module Main
where

import Cabal2Nix
import Cabal2Nix.Util ( quoted )
import Crypto.Hash.SHA256 ( hash
, hashlazy
)
import qualified Data.ByteString.Base16 as Base16
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy as BL
import Data.Foldable ( toList )
import qualified Data.Map as Map
import qualified Data.Sequence as Seq
import Data.String ( IsString(fromString) )
import Data.Text.Encoding ( decodeUtf8 )
import Distribution.Hackage.DB ( hackageTarball )
import qualified Distribution.Hackage.DB.Parsed
as P
import Distribution.Hackage.DB.Parsed ( parseMetaData
, parseVersionData
)
import Distribution.Hackage.DB.Unparsed
import Distribution.Pretty ( prettyShow
, Pretty
)
import Nix.Expr
import Nix.Pretty ( prettyNix )
import System.Directory ( createDirectoryIfMissing )
import System.Environment ( getArgs )
import System.FilePath ( (</>)
, (<.>)
)

main :: IO ()
main = do
[out] <- getArgs
db <- readTarball Nothing =<< hackageTarball

let defaultNix = seqToSet $ Map.foldMapWithKey package2nix db
createDirectoryIfMissing False out
writeFile (out </> "default.nix") $ show $ prettyNix defaultNix

_ <- forWithKey db $ \pname (PackageData { versions }) ->
forWithKey versions $ \vnum vdata@(VersionData { cabalFileRevisions }) ->
let parsedVData = parseVersionData pname vnum vdata
writeFiles gpd cabalFile revNum = do
let dir = out </> packagePath pname </> fromPretty vnum
revPath = dir </> revName revNum
createDirectoryIfMissing True dir
BL.writeFile (revPath <.> "cabal") cabalFile
writeFile (revPath <.> "nix") $ show $ prettyNix $ gpd2nix Nothing Nothing gpd
in sequence $ zipWith3 writeFiles
(toList (P.cabalFileRevisions parsedVData))
cabalFileRevisions
[(0 :: Int) ..]
return ()
where
forWithKey :: Applicative f => Map.Map k v -> (k -> v -> f x) -> f (Map.Map k x)
forWithKey = flip Map.traverseWithKey
seqToSet = mkNonRecSet . toList
fromPretty :: (Pretty a, IsString b) => a -> b
fromPretty = fromString . prettyShow
package2nix pname (PackageData { versions }) =
Seq.singleton $ quoted (fromPretty pname) $= seqToSet
(Map.foldMapWithKey (version2nix pname) versions)
version2nix pname vnum (VersionData { cabalFileRevisions, metaFile }) =
Seq.singleton $ quoted (fromPretty vnum) $= mkRecSet
( ("revision" $= mkSym (revName $ length cabalFileRevisions - 1))
: ("sha256" $= mkStr (fromString $ parseMetaData pname vnum metaFile Map.! "sha256"))
: zipWith (revBinding (packagePath pname) vnum) cabalFileRevisions [(0 :: Int) ..]
)
revName revNum = "r" <> fromString (show revNum)
revBinding ppath vnum cabalFile revNum =
let name :: (IsString a, Semigroup a) => a
name = revName revNum
revPath = "." </> ppath </> fromPretty vnum </> name
in name $= mkNonRecSet
[ "outPath" $= mkRelPath (revPath <.> "nix")
, "cabalFile" $= mkRelPath (revPath <.> "cabal")
, "cabalSha256" $= mkStr (decodeUtf8 $ Base16.encode $ hashlazy cabalFile)
]
packagePath pname =
BS.unpack (BS.take 30 $ Base16.encode $ hash $ fromPretty pname) ++ "-" ++ fromPretty pname
17 changes: 9 additions & 8 deletions lib/Cabal2Nix.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleInstances #-}

module Cabal2Nix (cabal2nix, Src(..), CabalFile(..), CabalFileGenerator(..), cabalFilePath, cabalFilePkgName) where
module Cabal2Nix (cabal2nix, gpd2nix, Src(..), CabalFile(..), CabalFileGenerator(..), cabalFilePath, cabalFilePkgName) where

import Distribution.PackageDescription.Parsec (readGenericPackageDescription, parseGenericPackageDescriptionMaybe)
import Distribution.Verbosity (normal)
Expand Down Expand Up @@ -48,7 +48,7 @@ pkgs, hsPkgs, flags :: Text
pkgs = "pkgs"
hsPkgs = "hsPkgs"
pkgconfPkgs = "pkgconfPkgs"
flags = "_flags"
flags = "flags"

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

cabal2nix :: Maybe Src -> CabalFile -> IO NExpr
cabal2nix src = \case
(OnDisk path) -> fmap (go Nothing)
(OnDisk path) -> fmap (gpd2nix Nothing src)
$ readGenericPackageDescription normal path
(InMemory gen path body) -> fmap (go (Just $ genExtra gen))
(InMemory gen path body) -> fmap (gpd2nix (Just $ genExtra gen) src)
$ maybe (error "Failed to parse in-memory cabal file") pure (parseGenericPackageDescriptionMaybe body)
where go :: Maybe NExpr -> GenericPackageDescription -> NExpr
go extra gpd = mkFunction args . lets gpd $ toNix gpd $//? (toNix <$> src) $//? extra
args :: Params NExpr

gpd2nix :: Maybe NExpr -> Maybe Src -> GenericPackageDescription -> NExpr
gpd2nix extra src gpd = mkFunction args . lets gpd $ toNix gpd $//? (toNix <$> src) $//? extra
where args :: Params NExpr
args = mkParamset [ ("system", Nothing)
, ("compiler", Nothing)
, ("flags", Just $ mkNonRecSet [])
Expand Down Expand Up @@ -184,7 +185,7 @@ mkSysDep :: String -> SysDependency
mkSysDep = SysDependency

instance ToNixExpr GenericPackageDescription where
toNix gpd = mkNonRecSet $ [ "flags" $= mkSym flags -- keep track of the final flags; and allow them to be inspected
toNix gpd = mkNonRecSet $ [ "flags" $= (mkNonRecSet . fmap toNixBinding $ genPackageFlags gpd)
, "package" $= (toNix (packageDescription gpd))
, "components" $= components ]
where packageName = fromString . show . disp . pkgName . package . packageDescription $ gpd
Expand Down
18 changes: 18 additions & 0 deletions nix-tools.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -65,6 +65,24 @@ executable hashes-to-nix
hs-source-dirs: hashes2nix
default-language: Haskell2010

executable hackage-to-nix
ghc-options: -Wall
main-is: Main.hs
build-depends: base >=4.11 && <4.12
, nix-tools
, hackage-db
, hnix
, Cabal
, containers
, bytestring
, text
, cryptohash-sha256
, base16-bytestring
, filepath
, directory
hs-source-dirs: hackage2nix
default-language: Haskell2010

executable plan-to-nix
ghc-options: -Wall
main-is: Main.hs
Expand Down

0 comments on commit 3335e43

Please sign in to comment.