Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module parses the plan.json
Cabal plan files that are created
by cabal-install
.
In the future, we hope to avoid doing this, and directly invoke Cabal's
solver to obtain the build plan, instead of invoking
cabal-install build --dry-run
and parsing the resulting plan.json
file.
Synopsis
- newtype CabalPlan = CabalPlan {}
- mapMaybePlanUnits :: (PlanUnit -> Maybe a) -> CabalPlan -> [a]
- newtype CabalPlanBinary = CabalPlanBinary ByteString
- parsePlanBinary :: CabalPlanBinary -> CabalPlan
- newtype PkgName = PkgName {}
- pkgNameVersion :: PkgName -> Version -> Text
- validPackageName :: Text -> Bool
- mangledPkgName :: PkgName -> String
- newtype AllowNewer = AllowNewer (Set (Text, Text))
- type PkgSpecs = Map PkgName PkgSpec
- data PkgSpec = PkgSpec {
- psConstraints :: !(Maybe Constraints)
- psFlags :: !FlagSpec
- emptyPkgSpec :: PkgSpec
- parsePkgSpec :: Text -> PkgSpec
- unionPkgSpecsOverriding :: PkgSpecs -> PkgSpecs -> PkgSpecs
- newtype Constraints = Constraints Text
- newtype FlagSpec = FlagSpec (Map Text Bool)
- showFlagSpec :: FlagSpec -> Text
- flagSpecIsEmpty :: FlagSpec -> Bool
- data PkgSrc
- newtype UnitId = UnitId {}
- data PlanUnit
- planUnitUnitId :: PlanUnit -> UnitId
- planUnitPkgName :: PlanUnit -> PkgName
- planUnitVersion :: PlanUnit -> Version
- data PreexistingUnit = PreexistingUnit {}
- data ConfiguredUnit = ConfiguredUnit {
- puId :: !UnitId
- puPkgName :: !PkgName
- puVersion :: !Version
- puComponentName :: !ComponentName
- puFlags :: !FlagSpec
- puDepends :: ![UnitId]
- puExeDepends :: ![UnitId]
- puSetupDepends :: ![UnitId]
- puPkgSrc :: !PkgSrc
- configuredUnitMaybe :: PlanUnit -> Maybe ConfiguredUnit
- cuComponentType :: ConfiguredUnit -> ComponentType
- allDepends :: ConfiguredUnit -> [UnitId]
- unitDepends :: ConfiguredUnit -> [UnitId]
- type UnitSpecs = Map PkgName (PkgSrc, PkgSpec, Set ComponentName)
- unionUnitSpecsCombining :: UnitSpecs -> UnitSpecs -> UnitSpecs
- data ComponentName = ComponentName {}
- cabalComponent :: ComponentName -> Text
- parsePkgComponent :: Text -> Maybe (PkgName, ComponentName)
- data ComponentType
- cabalComponentType :: ComponentType -> Text
- parseComponentType :: Text -> Maybe ComponentType
Build plans
Units in a Cabal plan.json
file.
newtype CabalPlanBinary Source #
Binary data underlying a cabal
plan.json
file.
parsePlanBinary :: CabalPlanBinary -> CabalPlan Source #
Decode a CabalPlanBinary
into a CabalPlan
.
Packages
A cabal package name, e.g. lens
, aeson
.
validPackageName :: Text -> Bool Source #
Is the string a valid cabal
package name? That is, does it consist
only of alphanumeric identifiers and hyphens?
mangledPkgName :: PkgName -> String Source #
A Cabal mangled package name, in which -
has been replaced with _
.
Allow-newer
newtype AllowNewer Source #
A collection of allow-newer specifications, e.g. pkg1:pkg2,*:base
.
AllowNewer (Set (Text, Text)) |
Instances
Monoid AllowNewer Source # | |
Defined in BuildEnv.CabalPlan mempty :: AllowNewer # mappend :: AllowNewer -> AllowNewer -> AllowNewer # mconcat :: [AllowNewer] -> AllowNewer # | |
Semigroup AllowNewer Source # | |
Defined in BuildEnv.CabalPlan (<>) :: AllowNewer -> AllowNewer -> AllowNewer # sconcat :: NonEmpty AllowNewer -> AllowNewer # stimes :: Integral b => b -> AllowNewer -> AllowNewer # | |
Show AllowNewer Source # | |
Defined in BuildEnv.CabalPlan showsPrec :: Int -> AllowNewer -> ShowS # show :: AllowNewer -> String # showList :: [AllowNewer] -> ShowS # |
Package specification
type PkgSpecs = Map PkgName PkgSpec Source #
A mapping from a package name to its flags and constraints.
Constraints and flags for a package.
PkgSpec | |
|
emptyPkgSpec :: PkgSpec Source #
No flags or constraints on a package.
parsePkgSpec :: Text -> PkgSpec Source #
Parse flags and constraints (in that order).
unionPkgSpecsOverriding :: PkgSpecs -> PkgSpecs -> PkgSpecs Source #
Left-biased union of two sets of packages, overriding flags and constraints of the second argument with those provided in the first argument.
Package constraints
newtype Constraints Source #
A collection of cabal constraints, e.g. >= 3.2 && < 3.4
,
in raw textual format.
Instances
Semigroup Constraints Source # | Combine two constraints using |
Defined in BuildEnv.CabalPlan (<>) :: Constraints -> Constraints -> Constraints # sconcat :: NonEmpty Constraints -> Constraints # stimes :: Integral b => b -> Constraints -> Constraints # | |
Show Constraints Source # | |
Defined in BuildEnv.CabalPlan showsPrec :: Int -> Constraints -> ShowS # show :: Constraints -> String # showList :: [Constraints] -> ShowS # |
Package flags
Specification of package flags, e.g. +foo -bar
.
+
corresponds to True
and -
to False
.
showFlagSpec :: FlagSpec -> Text Source #
flagSpecIsEmpty :: FlagSpec -> Bool Source #
Package source location
The source location of a package.
Nothing
: it's in the package database (e.g. Hackage).Just fp
: specified by thecabal
file at the given path.
Units
Units
A unique identifier for a unit,
e.g. lens-5.2-1bfd85cb66d2330e59a2f957e87cac993d922401
.
planUnitUnitId :: PlanUnit -> UnitId Source #
planUnitPkgName :: PlanUnit -> PkgName Source #
planUnitVersion :: PlanUnit -> Version Source #
data PreexistingUnit Source #
Information about a built-in pre-existing unit (such as base
).
Instances
Show PreexistingUnit Source # | |
Defined in BuildEnv.CabalPlan showsPrec :: Int -> PreexistingUnit -> ShowS # show :: PreexistingUnit -> String # showList :: [PreexistingUnit] -> ShowS # |
data ConfiguredUnit Source #
Information about a unit: name, version, dependencies, flags.
ConfiguredUnit | |
|
Instances
Show ConfiguredUnit Source # | |
Defined in BuildEnv.CabalPlan showsPrec :: Int -> ConfiguredUnit -> ShowS # show :: ConfiguredUnit -> String # showList :: [ConfiguredUnit] -> ShowS # |
cuComponentType :: ConfiguredUnit -> ComponentType Source #
Get what kind of component this unit is: lib
, exe
, etc.
allDepends :: ConfiguredUnit -> [UnitId] Source #
All the dependencies of a unit: depends
, exe-depends
and setup-depends
.
unitDepends :: ConfiguredUnit -> [UnitId] Source #
The dependencies of a unit, excluding setup-depends
.
Units within a package
type UnitSpecs = Map PkgName (PkgSrc, PkgSpec, Set ComponentName) Source #
A mapping from a package name to its flags, constraints, and components we want to build from it.
unionUnitSpecsCombining :: UnitSpecs -> UnitSpecs -> UnitSpecs Source #
Combine two UnitSpecs
. Combines constraints and flags.
Components
data ComponentName Source #
The name of a cabal component, e.g. lib:comp
.
ComponentName | |
|
Instances
Show ComponentName Source # | |
Defined in BuildEnv.CabalPlan showsPrec :: Int -> ComponentName -> ShowS # show :: ComponentName -> String # showList :: [ComponentName] -> ShowS # | |
Eq ComponentName Source # | |
Defined in BuildEnv.CabalPlan (==) :: ComponentName -> ComponentName -> Bool # (/=) :: ComponentName -> ComponentName -> Bool # | |
Ord ComponentName Source # | |
Defined in BuildEnv.CabalPlan compare :: ComponentName -> ComponentName -> Ordering # (<) :: ComponentName -> ComponentName -> Bool # (<=) :: ComponentName -> ComponentName -> Bool # (>) :: ComponentName -> ComponentName -> Bool # (>=) :: ComponentName -> ComponentName -> Bool # max :: ComponentName -> ComponentName -> ComponentName # min :: ComponentName -> ComponentName -> ComponentName # |
cabalComponent :: ComponentName -> Text Source #
Print a cabal component using colon syntax ty:comp
.
parsePkgComponent :: Text -> Maybe (PkgName, ComponentName) Source #
Parse a cabal package component, using the syntax pkg:ty:comp
,
e.g. attoparsec:lib:attoparsec-internal
.
data ComponentType Source #
The type of a component, e.g. library, executable, test-suite...
Instances
Show ComponentType Source # | |
Defined in BuildEnv.CabalPlan showsPrec :: Int -> ComponentType -> ShowS # show :: ComponentType -> String # showList :: [ComponentType] -> ShowS # | |
Eq ComponentType Source # | |
Defined in BuildEnv.CabalPlan (==) :: ComponentType -> ComponentType -> Bool # (/=) :: ComponentType -> ComponentType -> Bool # | |
Ord ComponentType Source # | |
Defined in BuildEnv.CabalPlan compare :: ComponentType -> ComponentType -> Ordering # (<) :: ComponentType -> ComponentType -> Bool # (<=) :: ComponentType -> ComponentType -> Bool # (>) :: ComponentType -> ComponentType -> Bool # (>=) :: ComponentType -> ComponentType -> Bool # max :: ComponentType -> ComponentType -> ComponentType # min :: ComponentType -> ComponentType -> ComponentType # |
cabalComponentType :: ComponentType -> Text Source #
Print the cabal component type as expected in cabal colon syntax
pkg:ty:comp
.
parseComponentType :: Text -> Maybe ComponentType Source #
Parse the type of a cabal
component, e.g library, executable, etc.