Skip to content

Commit

Permalink
Commit to Cabal 3.x.
Browse files Browse the repository at this point in the history
  • Loading branch information
peti committed Sep 21, 2019
1 parent 449ad2b commit 5efdfe0
Show file tree
Hide file tree
Showing 9 changed files with 62 additions and 41 deletions.
4 changes: 2 additions & 2 deletions cabal2nix.cabal
@@ -1,5 +1,5 @@
name: cabal2nix
version: 2.14.4
version: 2.15.0
synopsis: Convert Cabal files into Nix build instructions.
description:
Convert Cabal files into Nix build instructions. Users of Nix can install the latest
Expand Down Expand Up @@ -108,7 +108,7 @@ library
other-modules: Paths_cabal2nix
hs-source-dirs: src
build-depends: base > 4.11
, Cabal > 2.4
, Cabal > 3
, aeson > 1
, ansi-wl-pprint
, bytestring
Expand Down
15 changes: 8 additions & 7 deletions hackage2nix/Main.hs
Expand Up @@ -23,6 +23,7 @@ import Distribution.Nixpkgs.Haskell.Constraint
import Distribution.Nixpkgs.Haskell.FromCabal
import Distribution.Nixpkgs.Haskell.FromCabal.Configuration as Config
import Distribution.Nixpkgs.Haskell.FromCabal.Flags
import Distribution.Nixpkgs.Haskell.OrphanInstances ( )
import Distribution.Nixpkgs.Meta
import Distribution.Nixpkgs.PackageMap
import Distribution.Package
Expand Down Expand Up @@ -62,7 +63,7 @@ main = do
pinfo :: ParserInfo CLI
pinfo = info
( helper
<*> infoOption ("hackage2nix " ++ display Main.version) (long "version" <> help "Show version number")
<*> infoOption ("hackage2nix " ++ prettyShow Main.version) (long "version" <> help "Show version number")
<*> cliOptions
)
( fullDesc
Expand Down Expand Up @@ -92,7 +93,7 @@ main = do
latestVersionSet = Map.map Set.findMax (Map.filter (not . Set.null) (Map.mapWithKey (enforcePreferredVersions preferredVersions) hackage))

defaultPackageOverridesSet :: PackageSet
defaultPackageOverridesSet = Map.fromList [ (name, resolveConstraint c hackage) | c@(Dependency name _) <- defaultPackageOverrides config ]
defaultPackageOverridesSet = Map.fromList [ (name, resolveConstraint c hackage) | c@(Dependency name _ _) <- defaultPackageOverrides config ]

generatedDefaultPackageSet :: PackageSet
generatedDefaultPackageSet = (defaultPackageOverridesSet `Map.union` latestVersionSet) `Map.difference` corePackageSet
Expand All @@ -105,7 +106,7 @@ main = do

extraPackageSet :: PackageMultiSet
extraPackageSet = Map.unionsWith Set.union
[ Map.singleton name (Set.singleton (resolveConstraint c hackage)) | c@(Dependency name _) <- extraPackages config ]
[ Map.singleton name (Set.singleton (resolveConstraint c hackage)) | c@(Dependency name _ _) <- extraPackages config ]

db :: PackageMultiSet
db = Map.unionsWith Set.union [ Map.map Set.singleton generatedDefaultPackageSet
Expand All @@ -115,7 +116,7 @@ main = do
]

haskellResolver :: Dependency -> Bool
haskellResolver (Dependency name vrange)
haskellResolver (Dependency name vrange _)
| Just v <- Map.lookup name corePackageSet = v `withinRange` vrange
| Just v <- Map.lookup name generatedDefaultPackageSet = v `withinRange` vrange
| otherwise = False
Expand All @@ -137,7 +138,7 @@ main = do
let isInDefaultPackageSet, isHydraEnabled, isBroken :: Bool
isInDefaultPackageSet = (== Just v) (Map.lookup name generatedDefaultPackageSet)
isHydraEnabled = isInDefaultPackageSet && not (isBroken || name `Set.member` dontDistributePackages config)
isBroken = any (withinRange v) [ vr | Dependency pn vr <- brokenPackages config, pn == name ]
isBroken = any (withinRange v) [ vr | Dependency pn vr _ <- brokenPackages config, pn == name ]

droppedPlatforms :: Set Platform
droppedPlatforms = Map.findWithDefault mempty name (unsupportedPlatforms config)
Expand All @@ -164,7 +165,7 @@ main = do
& metaSection.homepage .~ ""

overrides :: Doc
overrides = fcat $ punctuate space [ disp b <> semi | b <- Set.toList (view (dependencies . each) drv `Set.union` view extraFunctionArgs drv), not (isFromHackage b) ]
overrides = fcat $ punctuate space [ pPrint b <> semi | b <- Set.toList (view (dependencies . each) drv `Set.union` view extraFunctionArgs drv), not (isFromHackage b) ]
return $ render $ nest 2 $
hang (doubleQuotes (text attr) <+> equals <+> text "callPackage") 2 (parens (pPrint drv)) <+> (braces overrides <> semi)

Expand Down Expand Up @@ -204,7 +205,7 @@ resolveConstraint c = fromMaybe (error msg) . resolveConstraint' c
]

resolveConstraint' :: Constraint -> Hackage -> Maybe Version
resolveConstraint' (Dependency name vrange) hackage
resolveConstraint' (Dependency name vrange _) hackage
| Just vset' <- Map.lookup name hackage
, vset <- Set.filter (`withinRange` vrange) vset'
, not (Set.null vset) = Just (Set.findMax vset)
Expand Down
18 changes: 8 additions & 10 deletions src/Cabal2nix.hs
Expand Up @@ -18,21 +18,21 @@ import Data.Monoid ( (<>) )
import qualified Data.Set as Set
import Data.String
import Data.Time
import qualified Distribution.Compat.ReadP as P
import Distribution.Compiler
import Distribution.Nixpkgs.Fetch
import Distribution.Nixpkgs.Haskell
import Distribution.Nixpkgs.Haskell.FromCabal
import Distribution.Nixpkgs.Haskell.FromCabal.Flags
import qualified Distribution.Nixpkgs.Haskell.FromCabal.PostProcess as PP (pkg)
import qualified Distribution.Nixpkgs.Haskell.Hackage as DB
import Distribution.Nixpkgs.Haskell.OrphanInstances ( )
import Distribution.Nixpkgs.Haskell.PackageSourceSpec
import Distribution.Nixpkgs.Meta
import Distribution.PackageDescription ( mkFlagName, mkFlagAssignment, FlagAssignment )
import Distribution.Package ( packageId )
import Distribution.PackageDescription ( mkFlagName, mkFlagAssignment, FlagAssignment )
import Distribution.Parsec as P
import Distribution.Simple.Utils ( lowercase )
import Distribution.System
import Distribution.Text
import Language.Nix
import Options.Applicative
import Paths_cabal2nix ( version )
Expand Down Expand Up @@ -94,8 +94,8 @@ options = Options
<*> optional (strOption $ long "hackage-db" <> metavar "PATH" <> help "path to the local hackage db in tar format")
<*> switch (long "shell" <> help "generate output suitable for nix-shell")
<*> many (strOption $ short 'f' <> long "flag" <> help "Cabal flag (may be specified multiple times)")
<*> option (readP parse) (long "compiler" <> help "compiler to use when evaluating the Cabal file" <> value buildCompilerId <> showDefaultWith display)
<*> option (maybeReader parsePlatform) (long "system" <> help "host system (in either short Nix format or full LLVM style) to use when evaluating the Cabal file" <> value buildPlatform <> showDefaultWith display)
<*> option parseCabal (long "compiler" <> help "compiler to use when evaluating the Cabal file" <> value buildCompilerId <> showDefaultWith prettyShow)
<*> option (maybeReader parsePlatform) (long "system" <> help "host system (in either short Nix format or full LLVM style) to use when evaluating the Cabal file" <> value buildPlatform <> showDefaultWith prettyShow)
<*> optional (strOption $ long "subpath" <> metavar "PATH" <> help "Path to Cabal file's directory relative to the URI (default is root directory)")
<*> optional (option utcTimeReader (long "hackage-snapshot" <> help "hackage snapshot time, ISO format"))
<*> pure (\i -> Just (binding # (i, path # [ident # "pkgs", i])))
Expand All @@ -110,10 +110,8 @@ utcTimeReader = eitherReader $ \arg ->
Nothing -> Left $ "Cannot parse date, ISO format used ('2017-11-20T12:18:35Z'): " ++ arg
Just utcTime -> Right utcTime

readP :: P.ReadP a a -> ReadM a
readP p = eitherReader $ \s -> case [ r' | (r',"") <- P.readP_to_S p s ] of
(r:_) -> Right r
_ -> Left ("invalid value " ++ show s)
parseCabal :: Parsec a => ReadM a
parseCabal = eitherReader eitherParsec

-- | Replicate the normalization performed by GHC_CONVERT_CPU in GHC's aclocal.m4
-- since the output of that is what Cabal parses.
Expand Down Expand Up @@ -164,7 +162,7 @@ parsePlatformParts = \case
pinfo :: ParserInfo Options
pinfo = info
( helper
<*> infoOption ("cabal2nix " ++ display version) (long "version" <> help "Show version number")
<*> infoOption ("cabal2nix " ++ prettyShow version) (long "version" <> help "Show version number")
<*> options
)
( fullDesc
Expand Down
2 changes: 1 addition & 1 deletion src/Distribution/Nixpkgs/Haskell/Constraint.hs
Expand Up @@ -9,7 +9,7 @@ import Distribution.Nixpkgs.Haskell.OrphanInstances ( )
type Constraint = Dependency

satisfiesConstraint :: PackageIdentifier -> Constraint -> Bool
satisfiesConstraint (PackageIdentifier pn v) (Dependency cn vr) = (pn /= cn) || (v `withinRange` vr)
satisfiesConstraint (PackageIdentifier pn v) (Dependency cn vr _) = (pn /= cn) || (v `withinRange` vr)

satisfiesConstraints :: PackageIdentifier -> [Constraint] -> Bool
satisfiesConstraints p = all (satisfiesConstraint p)
4 changes: 2 additions & 2 deletions src/Distribution/Nixpkgs/Haskell/Derivation.hs
Expand Up @@ -112,8 +112,8 @@ instance Pretty Derivation where
pPrint drv@MkDerivation {..} = funargs (map text ("mkDerivation" : toAscList inputs)) $$ vcat
[ text "mkDerivation" <+> lbrace
, nest 2 $ vcat
[ attr "pname" $ doubleQuotes $ disp (packageName _pkgid)
, attr "version" $ doubleQuotes $ disp (packageVersion _pkgid)
[ attr "pname" $ doubleQuotes $ pPrint (packageName _pkgid)
, attr "version" $ doubleQuotes $ pPrint (packageVersion _pkgid)
, pPrint _src
, onlyIf (_subpath /= ".") $ attr "postUnpack" postUnpack
, onlyIf (_revision > 0) $ attr "revision" $ doubleQuotes $ int _revision
Expand Down
14 changes: 7 additions & 7 deletions src/Distribution/Nixpkgs/Haskell/FromCabal.hs
Expand Up @@ -58,14 +58,14 @@ finalizeGenericPackageDescription haskellResolver arch compiler flags constraint
}

jailbroken :: HaskellResolver -> HaskellResolver
jailbroken resolver (Dependency pkg _) = resolver (Dependency pkg anyVersion)
jailbroken resolver (Dependency pkg _ _) = resolver (Dependency pkg anyVersion mempty)

withInternalLibs :: HaskellResolver -> HaskellResolver
withInternalLibs resolver d = depPkgName d `elem` internalNames || resolver d

internalNames :: [PackageName]
internalNames = [ unqualComponentNameToPackageName n | (n,_) <- condSubLibraries genDesc ]
++ [ unqualComponentNameToPackageName n | Just n <- libName <$> subLibraries (packageDescription genDesc) ]
++ [ unqualComponentNameToPackageName n | LSubLibName n <- libName <$> subLibraries (packageDescription genDesc) ]

in case finalize (jailbroken (withInternalLibs haskellResolver)) of
Left m -> case finalize (const True) of
Expand Down Expand Up @@ -119,7 +119,7 @@ fromPackageDescription haskellResolver nixpkgsResolver missingDeps flags Package
nixLicense = either fromSPDXLicense fromCabalLicense licenseRaw

resolveInHackage :: Identifier -> Binding
resolveInHackage i | (i^.ident) `elem` [ unPackageName n | (Dependency n _) <- missingDeps ] = bindNull i
resolveInHackage i | (i^.ident) `elem` [ unPackageName n | (Dependency n _ _) <- missingDeps ] = bindNull i
| otherwise = binding # (i, path # ["self",i]) -- TODO: "self" shouldn't be hardcoded.

-- TODO: This is all very confusing. Haskell packages refer to the Nixpkgs
Expand All @@ -144,11 +144,11 @@ fromPackageDescription haskellResolver nixpkgsResolver missingDeps flags Package
| otherwise = bindNull i

resolveInHackageThenNixpkgs :: Identifier -> Binding
resolveInHackageThenNixpkgs i | haskellResolver (Dependency (mkPackageName (i^.ident)) anyVersion) = resolveInHackage i
resolveInHackageThenNixpkgs i | haskellResolver (Dependency (mkPackageName (i^.ident)) anyVersion mempty) = resolveInHackage i
| otherwise = resolveInNixpkgs i

internalLibNames :: [PackageName]
internalLibNames = fmap unqualComponentNameToPackageName . catMaybes $ libName <$> subLibraries
internalLibNames = [ unqualComponentNameToPackageName n | LSubLibName n <- libName <$> subLibraries ]

doHaddockPhase :: Bool
doHaddockPhase | not (null internalLibNames) = False
Expand All @@ -158,15 +158,15 @@ fromPackageDescription haskellResolver nixpkgsResolver missingDeps flags Package
convertBuildInfo :: Cabal.BuildInfo -> Nix.BuildInfo
convertBuildInfo Cabal.BuildInfo {..} | not buildable = mempty
convertBuildInfo Cabal.BuildInfo {..} = mempty
& haskell .~ Set.fromList [ resolveInHackage (toNixName x) | (Dependency x _) <- targetBuildDepends, x `notElem` internalLibNames ]
& haskell .~ Set.fromList [ resolveInHackage (toNixName x) | (Dependency x _ _) <- targetBuildDepends, x `notElem` internalLibNames ]
& system .~ Set.fromList [ resolveInNixpkgs y | x <- extraLibs, y <- libNixName x ]
& pkgconfig .~ Set.fromList [ resolveInNixpkgs y | PkgconfigDependency x _ <- pkgconfigDepends, y <- libNixName (unPkgconfigName x) ]
& tool .~ Set.fromList (map resolveInHackageThenNixpkgs . concatMap buildToolNixName
$ [ unPackageName x | ExeDependency x _ _ <- buildToolDepends ] ++ [ x | LegacyExeDependency x _ <- buildTools ])

convertSetupBuildInfo :: Cabal.SetupBuildInfo -> Nix.BuildInfo
convertSetupBuildInfo bi = mempty
& haskell .~ Set.fromList [ resolveInHackage (toNixName x) | (Dependency x _) <- Cabal.setupDepends bi ]
& haskell .~ Set.fromList [ resolveInHackage (toNixName x) | (Dependency x _ _) <- Cabal.setupDepends bi ]

bindNull :: Identifier -> Binding
bindNull i = binding # (i, path # ["null"])
2 changes: 1 addition & 1 deletion src/Distribution/Nixpkgs/Haskell/FromCabal/PostProcess.hs
Expand Up @@ -21,7 +21,7 @@ import Language.Nix

postProcess :: Derivation -> Derivation
postProcess deriv =
foldr (.) id [ f | (Dependency n vr, f) <- hooks, packageName deriv == n, packageVersion deriv `withinRange` vr ]
foldr (.) id [ f | (Dependency n vr _, f) <- hooks, packageName deriv == n, packageVersion deriv `withinRange` vr ]
. fixGtkBuilds
. fixBuildDependsForTools
$ deriv
Expand Down
27 changes: 24 additions & 3 deletions src/Distribution/Nixpkgs/Haskell/OrphanInstances.hs
Expand Up @@ -9,9 +9,12 @@ import qualified Data.Text as T
import Data.Yaml
import Distribution.Compiler
import Distribution.Package
import Distribution.Parsec
import Distribution.System
import Distribution.Text
import Distribution.Pretty as Cabal
import qualified Data.Version as Base
import Distribution.Version
import Language.Nix.PrettyPrinting as Nix

instance NFData CompilerInfo
instance NFData AbiTag
Expand Down Expand Up @@ -61,7 +64,25 @@ instance FromJSON CompilerInfo where
parseJSON (String s) = return (unknownCompilerInfo (fromString (T.unpack s)) NoAbiTag)
parseJSON s = fail ("parseJSON: " ++ show s ++ " is not a valid Haskell compiler")

instance Nix.Pretty Version where
pPrint = pretty

instance Nix.Pretty PackageName where
pPrint = pretty

instance Nix.Pretty PackageIdentifier where
pPrint = pretty

instance Nix.Pretty CompilerId where
pPrint = pretty

instance Nix.Pretty Platform where
pPrint = pretty

instance Nix.Pretty Base.Version where
pPrint = text . Base.showVersion

-- parsing tools

text2isString :: Text a => String -> String -> a
text2isString t s = fromMaybe (error ("fromString: " ++ show s ++ " is not a valid " ++ t)) (simpleParse s)
text2isString :: Parsec a => String -> String -> a
text2isString t s = fromMaybe (error ("fromString: " ++ show s ++ " is not a valid " ++ t)) (simpleParsec s)
17 changes: 9 additions & 8 deletions src/Distribution/Nixpkgs/Haskell/PackageSourceSpec.hs
Expand Up @@ -11,16 +11,18 @@ import qualified Data.ByteString.Char8 as BS
import Data.List ( isSuffixOf, isPrefixOf )
import qualified Data.Map as DB
import Data.Maybe
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Data.Time
import Distribution.Nixpkgs.Fetch
import Distribution.Nixpkgs.Hashes
import qualified Distribution.Nixpkgs.Haskell.Hackage as DB
import Distribution.Nixpkgs.Haskell.OrphanInstances ( )
import qualified Distribution.Package as Cabal
import Distribution.PackageDescription
import qualified Distribution.PackageDescription as Cabal
import Distribution.PackageDescription.Parsec as Cabal
import Distribution.Parsec.Common (showPError)
import Distribution.Text ( simpleParse, display )
import Distribution.Parsec
import Distribution.Version
import qualified Hpack.Config as Hpack
import qualified Hpack.Render as Hpack
Expand All @@ -29,8 +31,7 @@ import System.Directory ( doesDirectoryExist, doesFileExist, createDirectoryIfMi
import System.Exit ( exitFailure )
import System.FilePath ( (</>), (<.>) )
import System.IO
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Text.PrettyPrint.HughesPJClass hiding ( first )

data HpackUse
= ForceHpack
Expand Down Expand Up @@ -107,12 +108,12 @@ fromDB hackageDBIO pkg = do
return (ds, setCabalFileHash (DB.cabalFileSha256 vd) (DB.cabalFile vd))
where
pkgId :: Cabal.PackageIdentifier
pkgId = fromMaybe (error ("invalid Haskell package id " ++ show pkg)) (simpleParse pkg)
pkgId = fromMaybe (error ("invalid Haskell package id " ++ show pkg)) (simpleParsec pkg)
name = Cabal.packageName pkgId

unknownPackageError = fail $ "No such package " ++ display pkgId ++ " in the cabal database. Did you run cabal update?"
unknownPackageError = fail $ "No such package " ++ prettyShow pkgId ++ " in the cabal database. Did you run cabal update?"

url = "mirror://hackage/" ++ display pkgId ++ ".tar.gz"
url = "mirror://hackage/" ++ prettyShow pkgId ++ ".tar.gz"

version :: Version
version = Cabal.packageVersion pkgId
Expand Down Expand Up @@ -175,7 +176,7 @@ sourceFromHackage optHash pkgId cabalDir = do
exitFailure

showPackageIdentifier :: Cabal.GenericPackageDescription -> String
showPackageIdentifier pkgDesc = name ++ "-" ++ display version where
showPackageIdentifier pkgDesc = name ++ "-" ++ prettyShow version where
pkgId = Cabal.package . Cabal.packageDescription $ pkgDesc
name = Cabal.unPackageName (Cabal.packageName pkgId)
version = Cabal.packageVersion pkgId
Expand Down

0 comments on commit 5efdfe0

Please sign in to comment.