Skip to content

Commit

Permalink
Adds --full option to plan2nix and stack2nix (#58)
Browse files Browse the repository at this point in the history
* Add attributes needed to clean components source

* Add more details useful for cleaning source dirs

* Use command line flag everywhere (missed a spot)
  • Loading branch information
hamishmack authored and angerman committed Jul 29, 2019
1 parent 11c8f24 commit a2a4aa2
Show file tree
Hide file tree
Showing 7 changed files with 102 additions and 50 deletions.
8 changes: 4 additions & 4 deletions cabal2nix/Main.hs
Expand Up @@ -48,10 +48,10 @@ main = getArgs >>= \case
(Just (DerivationSource{..}, genBindings)) -> genBindings derivHash
_ -> return ()
[path,file] -> doesDirectoryExist file >>= \case
False -> print . prettyNix =<< cabal2nix (Just (Path path)) (OnDisk file)
False -> print . prettyNix =<< cabal2nix MinimalDetails (Just (Path path)) (OnDisk file)
True -> print . prettyNix =<< cabalexprs file
[file] -> doesDirectoryExist file >>= \case
False -> print . prettyNix =<< cabal2nix (Just (Path ".")) (OnDisk file)
False -> print . prettyNix =<< cabal2nix MinimalDetails (Just (Path ".")) (OnDisk file)
True -> print . prettyNix =<< cabalexprs file
_ -> putStrLn "call with cabalfile (Cabal2Nix file.cabal)."

Expand All @@ -72,7 +72,7 @@ cabalFromPath url rev subdir path = do
subdir' = if subdir == "." then Nothing
else Just subdir
src = Just $ Git url rev (Just sha256) subdir'
print . prettyNix =<< cabal2nix src cabalFile
print . prettyNix =<< cabal2nix MinimalDetails src cabalFile

findCabalFiles :: FilePath -> IO [CabalFile]
findCabalFiles path = doesFileExist (path </> Hpack.packageConfig) >>= \case
Expand Down Expand Up @@ -103,7 +103,7 @@ expr p pkg version = do
doesFileExist (cabalFilePath cabal) >>= \case
True ->
do createDirectoryIfMissing True pkg'
writeDoc nix =<< prettyNix <$> cabal2nix Nothing cabal
writeDoc nix =<< prettyNix <$> cabal2nix MinimalDetails Nothing cabal
pure $ version' $= mkRelPath nix
False -> pure $ version' $= mkNull

Expand Down
2 changes: 1 addition & 1 deletion hackage2nix/Main.hs
Expand Up @@ -56,7 +56,7 @@ main = do
createDirectoryIfMissing False (out </> "hackage")

for_ cabalFiles $ \(cabalFile, pname, path) -> do
gpd <- cabal2nix Nothing $ InMemory Nothing pname $ BL.toStrict cabalFile
gpd <- cabal2nix MinimalDetails Nothing $ InMemory Nothing pname $ BL.toStrict cabalFile
writeFile (out </> path) $ show $ prettyNix gpd

type GPDWriter = State (Seq (BL.ByteString, String, FilePath))
Expand Down
127 changes: 87 additions & 40 deletions lib/Cabal2Nix.hs
Expand Up @@ -2,7 +2,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleInstances #-}

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

import Distribution.PackageDescription.Parsec (readGenericPackageDescription, parseGenericPackageDescription, runParseResult)
import Distribution.Verbosity (normal)
Expand All @@ -11,7 +11,7 @@ import Distribution.Pretty (pretty)
import Data.Char (toUpper)
import System.FilePath
import Data.ByteString (ByteString)
import Data.Maybe (catMaybes)
import Data.Maybe (catMaybes, maybeToList)

import Distribution.Types.CondTree
import Distribution.Types.Library
Expand All @@ -26,6 +26,8 @@ import Distribution.Types.VersionRange
import Distribution.Compiler
import Distribution.Types.PackageName (PackageName, mkPackageName)
import Distribution.Simple.BuildToolDepends (desugarBuildTool)
import Distribution.ModuleName (ModuleName)
import qualified Distribution.ModuleName as ModuleName

import Data.String (fromString, IsString)

Expand Down Expand Up @@ -76,17 +78,19 @@ cabalFilePkgName = dropExtension . takeFileName . cabalFilePath
genExtra :: CabalFileGenerator -> NExpr
genExtra Hpack = mkNonRecSet [ "cabal-generator" $= mkStr "hpack" ]

cabal2nix :: Maybe Src -> CabalFile -> IO NExpr
cabal2nix src = \case
(OnDisk path) -> gpd2nix src Nothing
data CabalDetailLevel = MinimalDetails | FullDetails deriving (Show, Eq)

cabal2nix :: CabalDetailLevel -> Maybe Src -> CabalFile -> IO NExpr
cabal2nix fileDetails src = \case
(OnDisk path) -> gpd2nix fileDetails src Nothing
<$> readGenericPackageDescription normal path
(InMemory gen _ body) -> gpd2nix src (genExtra <$> gen)
(InMemory gen _ body) -> gpd2nix fileDetails src (genExtra <$> gen)
<$> case runParseResult (parseGenericPackageDescription body) of
(_, Left (_, err)) -> error ("Failed to parse in-memory cabal file: " ++ show err)
(_, Right desc) -> pure desc

gpd2nix :: Maybe Src -> Maybe NExpr -> GenericPackageDescription -> NExpr
gpd2nix src extra gpd = mkFunction args $ toNix gpd $//? (toNix <$> src) $//? extra
gpd2nix :: CabalDetailLevel -> Maybe Src -> Maybe NExpr -> GenericPackageDescription -> NExpr
gpd2nix fileDetails src extra gpd = mkFunction args $ toNix' fileDetails gpd $//? (toNix <$> src) $//? extra
where args :: Params NExpr
args = mkParamset [ ("system", Nothing)
, ("compiler", Nothing)
Expand All @@ -96,22 +100,32 @@ gpd2nix src extra gpd = mkFunction args $ toNix gpd $//? (toNix <$> src) $//? ex
, (pkgconfPkgs, Nothing)]
True

class HasBuildInfo a where
class IsComponent a where
getBuildInfo :: a -> BuildInfo
getMainPath :: a -> Maybe FilePath
getMainPath _ = Nothing
modules :: a -> [ModuleName]
modules = otherModules . getBuildInfo

instance HasBuildInfo Library where
instance IsComponent Library where
getBuildInfo = libBuildInfo
modules a = otherModules (getBuildInfo a)
<> exposedModules a
<> signatures a

instance HasBuildInfo ForeignLib where
instance IsComponent ForeignLib where
getBuildInfo = foreignLibBuildInfo

instance HasBuildInfo Executable where
instance IsComponent Executable where
getBuildInfo = buildInfo
getMainPath Executable {modulePath = p} = Just p

instance HasBuildInfo TestSuite where
instance IsComponent TestSuite where
getBuildInfo = testBuildInfo
getMainPath TestSuite {testInterface = (TestSuiteExeV10 _ p)} = Just p
getMainPath _ = Nothing

instance HasBuildInfo Benchmark where
instance IsComponent Benchmark where
getBuildInfo = benchmarkBuildInfo

--- Clean the Tree from empty nodes
Expand Down Expand Up @@ -140,6 +154,9 @@ capitalize = transformFst toUpper
class ToNixExpr a where
toNix :: a -> NExpr

class ToNixExpr' a where
toNix' :: CabalDetailLevel -> a -> NExpr

class ToNixBinding a where
toNixBinding :: a -> Binding NExpr

Expand All @@ -166,44 +183,72 @@ instance ToNixExpr PackageIdentifier where
toNix ident = mkNonRecSet [ "name" $= mkStr (fromString (show (disp (pkgName ident))))
, "version" $= mkStr (fromString (show (disp (pkgVersion ident))))]

instance ToNixExpr PackageDescription where
toNix pd = mkNonRecSet $ [ "specVersion" $= mkStr (fromString (show (disp (specVersion pd))))
, "identifier" $= toNix (package pd)
, "license" $= mkStr (fromString (show (pretty (license pd))))

, "copyright" $= mkStr (fromString (copyright pd))
, "maintainer" $= mkStr (fromString (maintainer pd))
, "author" $= mkStr (fromString (author pd))

, "homepage" $= mkStr (fromString (homepage pd))
, "url" $= mkStr (fromString (pkgUrl pd))

, "synopsis" $= mkStr (fromString (synopsis pd))
, "description" $= mkStr (fromString (description pd))

, "buildType" $= mkStr (fromString (show (pretty (buildType pd))))
] ++
[ "setup-depends" $= toNix (BuildToolDependency . depPkgName <$> deps) | Just deps <- [setupDepends <$> setupBuildInfo pd ]]
instance ToNixExpr' PackageDescription where
toNix' detailLevel pd = mkNonRecSet $
[ "specVersion" $= mkStr (fromString (show (disp (specVersion pd))))
, "identifier" $= toNix (package pd)
, "license" $= mkStr (fromString (show (pretty (license pd))))

, "copyright" $= mkStr (fromString (copyright pd))
, "maintainer" $= mkStr (fromString (maintainer pd))
, "author" $= mkStr (fromString (author pd))

, "homepage" $= mkStr (fromString (homepage pd))
, "url" $= mkStr (fromString (pkgUrl pd))

, "synopsis" $= mkStr (fromString (synopsis pd))
, "description" $= mkStr (fromString (description pd))

, "buildType" $= mkStr (fromString (show (pretty (buildType pd))))
] ++
[ "setup-depends" $= toNix (BuildToolDependency . depPkgName <$> deps) | Just deps <- [setupDepends <$> setupBuildInfo pd ]] ++
if detailLevel == MinimalDetails
then []
else
[ "detailLevel" $= mkStr (fromString (show detailLevel))
, "licenseFiles" $= toNix (licenseFiles pd)
, "dataDir" $= mkStr (fromString (dataDir pd))
, "dataFiles" $= toNix (dataFiles pd)
, "extraSrcFiles" $= toNix (extraSrcFiles pd)
, "extraTmpFiles" $= toNix (extraTmpFiles pd)
, "extraDocFiles" $= toNix (extraDocFiles pd)
]

newtype SysDependency = SysDependency { unSysDependency :: String } deriving (Show, Eq, Ord)
newtype BuildToolDependency = BuildToolDependency { unBuildToolDependency :: PackageName } deriving (Show, Eq, Ord)

mkSysDep :: String -> SysDependency
mkSysDep = SysDependency

instance ToNixExpr GenericPackageDescription where
toNix gpd = mkNonRecSet [ "flags" $= (mkNonRecSet . fmap toNixBinding $ genPackageFlags gpd)
, "package" $= toNix (packageDescription gpd)
instance ToNixExpr' GenericPackageDescription where
toNix' detailLevel gpd = mkNonRecSet
[ "flags" $= (mkNonRecSet . fmap toNixBinding $ genPackageFlags gpd)
, "package" $= toNix' detailLevel (packageDescription gpd)
, "components" $= components ]
where _packageName :: IsString a => a
_packageName = fromString . show . disp . pkgName . package . packageDescription $ gpd
component :: IsComponent comp => UnqualComponentName -> CondTree ConfVar [Dependency] comp -> Binding NExpr
component unQualName comp
= quoted name $=
mkNonRecSet ([ "depends" $= toNix deps | Just deps <- [shakeTree . fmap ( targetBuildDepends . getBuildInfo) $ comp ] ] ++
[ "libs" $= toNix deps | Just deps <- [shakeTree . fmap ( fmap mkSysDep . extraLibs . getBuildInfo) $ comp ] ] ++
[ "frameworks" $= toNix deps | Just deps <- [shakeTree . fmap ( fmap mkSysDep . frameworks . getBuildInfo) $ comp ] ] ++
[ "pkgconfig" $= toNix deps | Just deps <- [shakeTree . fmap ( pkgconfigDepends . getBuildInfo) $ comp ] ] ++
[ "build-tools"$= toNix deps | Just deps <- [shakeTree . fmap ( toolDeps . getBuildInfo) $ comp ] ])
mkNonRecSet (
[ "depends" $= toNix deps | Just deps <- [shakeTree . fmap ( targetBuildDepends . getBuildInfo) $ comp ] ] ++
[ "libs" $= toNix deps | Just deps <- [shakeTree . fmap ( fmap mkSysDep . extraLibs . getBuildInfo) $ comp ] ] ++
[ "frameworks" $= toNix deps | Just deps <- [shakeTree . fmap ( fmap mkSysDep . frameworks . getBuildInfo) $ comp ] ] ++
[ "pkgconfig" $= toNix deps | Just deps <- [shakeTree . fmap ( pkgconfigDepends . getBuildInfo) $ comp ] ] ++
[ "build-tools" $= toNix deps | Just deps <- [shakeTree . fmap ( toolDeps . getBuildInfo) $ comp ] ] ++
if detailLevel == MinimalDetails
then []
else
[ "modules" $= toNix mods | Just mods <- [shakeTree . fmap (fmap ModuleName.toFilePath . modules) $ comp ] ] ++
[ "asmSources" $= toNix src | Just src <- [shakeTree . fmap (asmSources . getBuildInfo) $ comp ] ] ++
[ "cmmSources" $= toNix src | Just src <- [shakeTree . fmap (cmmSources . getBuildInfo) $ comp ] ] ++
[ "cSources" $= toNix src | Just src <- [shakeTree . fmap (cSources . getBuildInfo) $ comp ] ] ++
[ "cxxSources" $= toNix src | Just src <- [shakeTree . fmap (cxxSources . getBuildInfo) $ comp ] ] ++
[ "jsSources" $= toNix src | Just src <- [shakeTree . fmap (jsSources . getBuildInfo) $ comp ] ] ++
[ "hsSourceDirs" $= toNix dir | Just dir <- [shakeTree . fmap (hsSourceDirs . getBuildInfo) $ comp ] ] ++
[ "includeDirs" $= toNix dir | Just dir <- [shakeTree . fmap (includeDirs . getBuildInfo) $ comp] ] ++
[ "includes" $= toNix dir | Just dir <- [shakeTree . fmap (includes . getBuildInfo) $ comp] ] ++
[ "mainPath" $= toNix p | Just p <- [shakeTree . fmap (maybeToList . getMainPath) $ comp] ])
where name = fromString $ unUnqualComponentName unQualName
toolDeps = getToolDependencies (packageDescription gpd)
toBuildToolDep (ExeDependency pkg _ _) = BuildToolDependency pkg
Expand Down Expand Up @@ -292,3 +337,5 @@ instance (Foldable t, ToNixExpr (t a), ToNixExpr v, ToNixExpr c) => ToNixExpr (C

instance ToNixBinding Flag where
toNixBinding (MkFlag name _desc def _manual) = (fromString . show . pretty $ name) $= mkBool def


4 changes: 2 additions & 2 deletions plan2nix/Plan2Nix.hs
Expand Up @@ -90,7 +90,7 @@ plan2nix args (Plan { packages, extras, compilerVersion, compilerPackages }) = d
src = Just . C2N.Path $ relPath </> ".." </> (shortRelativePath cwd folder)
in do createDirectoryIfMissing True (takeDirectory nixFile)
writeDoc nixFile =<<
prettyNix <$> cabal2nix src cabalFile
prettyNix <$> cabal2nix (argDetailLevel args) src cabalFile
return $ fromString pkg $= mkPath False nix
(name, Just (Package v r flags (Just (DVCS (Git url rev) subdirs)))) ->
fmap concat . forM subdirs $ \subdir ->
Expand Down Expand Up @@ -153,7 +153,7 @@ plan2nix args (Plan { packages, extras, compilerVersion, compilerPackages }) = d
src = Just $ C2N.Git url rev (Just sha256) subdir'
createDirectoryIfMissing True (takeDirectory nixFile)
writeDoc nixFile =<<
prettyNix <$> cabal2nix src cabalFile
prettyNix <$> cabal2nix (argDetailLevel args) src cabalFile
liftIO $ appendCache (argCacheFile args) url rev subdir sha256 pkg nix
return $ fromString pkg $= mkPath False nix

Expand Down
4 changes: 3 additions & 1 deletion plan2nix/Plan2Nix/CLI.hs
Expand Up @@ -5,7 +5,7 @@ module Plan2Nix.CLI

import Options.Applicative hiding (option)
import Data.Semigroup ((<>))

import Cabal2Nix (CabalDetailLevel(..))

--------------------------------------------------------------------------------
-- CLI Arguments
Expand All @@ -14,6 +14,7 @@ data Args = Args
, argPlanJSON :: FilePath
, argCabalProject :: FilePath
, argCacheFile :: FilePath
, argDetailLevel :: CabalDetailLevel
} deriving Show

-- Argument Parser
Expand All @@ -23,6 +24,7 @@ args = Args
<*> strOption ( long "plan-json" <> value "dist-newstyle/cache/plan.json" <> showDefault <> metavar "FILE" <> help "Override plan.json location" )
<*> strOption ( long "cabal-project" <> value "cabal.project" <> showDefault <> metavar "FILE" <> help "Override path to cabal.project" )
<*> strOption ( long "cache" <> value ".nix-tools.cache" <> showDefault <> metavar "FILE" <> help "Dependency cache file" )
<*> flag MinimalDetails FullDetails ( long "full" <> help "Output details needed to determine what files are used" )

parsePlan2NixArgs :: IO Args
parsePlan2NixArgs = execParser opts
Expand Down
4 changes: 2 additions & 2 deletions stack2nix/Stack2nix.hs
Expand Up @@ -138,7 +138,7 @@ packages2nix args (Stack _ _ pkgs _) =
src = Just . C2N.Path $ relPath </> folder
in do createDirectoryIfMissing True (takeDirectory nixFile)
writeDoc nixFile =<<
prettyNix <$> cabal2nix src cabalFile
prettyNix <$> cabal2nix (argDetailLevel args) src cabalFile
return $ fromString pkg $= mkPath False nix
(DVCS (Git url rev) subdirs) ->
fmap concat . forM subdirs $ \subdir ->
Expand Down Expand Up @@ -174,7 +174,7 @@ packages2nix args (Stack _ _ pkgs _) =
src = Just $ C2N.Git url rev (Just sha256) subdir'
createDirectoryIfMissing True (takeDirectory nixFile)
writeDoc nixFile =<<
prettyNix <$> cabal2nix src cabalFile
prettyNix <$> cabal2nix (argDetailLevel args) src cabalFile
liftIO $ appendCache (argCacheFile args) url rev subdir sha256 pkg nix
return $ fromString pkg $= mkPath False nix

Expand Down
3 changes: 3 additions & 0 deletions stack2nix/Stack2nix/CLI.hs
Expand Up @@ -6,6 +6,7 @@ module Stack2nix.CLI

import Options.Applicative hiding (option)
import Data.Semigroup ((<>))
import Cabal2Nix (CabalDetailLevel(..))

data HpackUse
= IgnorePackageYaml
Expand All @@ -19,6 +20,7 @@ data Args = Args
, argStackYaml :: FilePath
, argHpackUse :: HpackUse
, argCacheFile :: FilePath
, argDetailLevel :: CabalDetailLevel
} deriving Show

-- Argument Parser
Expand All @@ -28,6 +30,7 @@ args = Args
<*> strOption ( long "stack-yaml" <> value "stack.yaml" <> showDefault <> metavar "FILE" <> help "Override project stack.yaml" )
<*> flag UsePackageYamlFirst IgnorePackageYaml (long "ignore-package-yaml" <> help "disable hpack run and use only cabal disregarding package.yaml existence")
<*> strOption ( long "cache" <> value ".stack-to-nix.cache" <> showDefault <> metavar "FILE" <> help "Dependency cache file" )
<*> flag MinimalDetails FullDetails ( long "full" <> help "Output details needed to determine what files are used" )

parseStack2nixArgs :: IO Args
parseStack2nixArgs = execParser opts
Expand Down

0 comments on commit a2a4aa2

Please sign in to comment.