Cabal-3.4.0.0: A framework for packaging Haskell software
Safe HaskellNone
LanguageHaskell2010

Distribution.Types.Dependency

Synopsis

Documentation

data Dependency Source #

Describes a dependency on a source package (API)

Invariant: package name does not appear as LSubLibName in set of library names.

Constructors

Dependency PackageName VersionRange (NonEmptySet LibraryName)

The set of libraries required from the package. Only the selected libraries will be built. It does not affect the cabal-install solver yet.

Instances

Instances details
Eq Dependency Source # 
Instance details

Defined in Distribution.Types.Dependency

Data Dependency Source # 
Instance details

Defined in Distribution.Types.Dependency

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dependency -> c Dependency #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dependency #

toConstr :: Dependency -> Constr #

dataTypeOf :: Dependency -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Dependency) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dependency) #

gmapT :: (forall b. Data b => b -> b) -> Dependency -> Dependency #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dependency -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dependency -> r #

gmapQ :: (forall d. Data d => d -> u) -> Dependency -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Dependency -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dependency -> m Dependency #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dependency -> m Dependency #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dependency -> m Dependency #

Read Dependency Source # 
Instance details

Defined in Distribution.Types.Dependency

Show Dependency Source # 
Instance details

Defined in Distribution.Types.Dependency

Generic Dependency Source # 
Instance details

Defined in Distribution.Types.Dependency

Associated Types

type Rep Dependency :: Type -> Type #

Binary Dependency Source # 
Instance details

Defined in Distribution.Types.Dependency

NFData Dependency Source # 
Instance details

Defined in Distribution.Types.Dependency

Methods

rnf :: Dependency -> () #

Structured Dependency Source # 
Instance details

Defined in Distribution.Types.Dependency

Pretty Dependency Source #
>>> prettyShow $ Dependency "pkg" anyVersion mainLibSet
"pkg"
>>> prettyShow $ Dependency "pkg" anyVersion $ NES.insert (LSubLibName "sublib") mainLibSet
"pkg:{pkg, sublib}"
>>> prettyShow $ Dependency "pkg" anyVersion $ NES.singleton (LSubLibName "sublib")
"pkg:sublib"
>>> prettyShow $ Dependency "pkg" anyVersion $ NES.insert (LSubLibName "sublib-b") $ NES.singleton (LSubLibName "sublib-a")
"pkg:{sublib-a, sublib-b}"
Instance details

Defined in Distribution.Types.Dependency

Parsec Dependency Source #
>>> simpleParsec "mylib:sub" :: Maybe Dependency
Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LSubLibName (UnqualComponentName "sub") :| [])))
>>> simpleParsec "mylib:{sub1,sub2}" :: Maybe Dependency
Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LSubLibName (UnqualComponentName "sub1") :| [LSubLibName (UnqualComponentName "sub2")])))
>>> simpleParsec "mylib:{ sub1 , sub2 }" :: Maybe Dependency
Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LSubLibName (UnqualComponentName "sub1") :| [LSubLibName (UnqualComponentName "sub2")])))
>>> simpleParsec "mylib:{ sub1 , sub2 } ^>= 42" :: Maybe Dependency
Just (Dependency (PackageName "mylib") (MajorBoundVersion (mkVersion [42])) (fromNonEmpty (LSubLibName (UnqualComponentName "sub1") :| [LSubLibName (UnqualComponentName "sub2")])))
>>> simpleParsec "mylib:{ } ^>= 42" :: Maybe Dependency
Nothing
>>> traverse_ print (map simpleParsec ["mylib:mylib", "mylib:{mylib}", "mylib:{mylib,sublib}" ] :: [Maybe Dependency])
Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LMainLibName :| [])))
Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LMainLibName :| [])))
Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LMainLibName :| [LSubLibName (UnqualComponentName "sublib")])))

Spaces around colon are not allowed:

>>> map simpleParsec ["mylib: sub", "mylib :sub", "mylib: {sub1,sub2}", "mylib :{sub1,sub2}"] :: [Maybe Dependency]
[Nothing,Nothing,Nothing,Nothing]

Sublibrary syntax is accepted since cabal-version: 3.0

>>> map (`simpleParsec'` "mylib:sub") [CabalSpecV2_4, CabalSpecV3_0] :: [Maybe Dependency]
[Nothing,Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LSubLibName (UnqualComponentName "sub") :| [])))]
Instance details

Defined in Distribution.Types.Dependency

type Rep Dependency Source # 
Instance details

Defined in Distribution.Types.Dependency

mkDependency :: PackageName -> VersionRange -> NonEmptySet LibraryName -> Dependency Source #

Smart constructor of Dependency.

If PackageName is appears as LSubLibName in a set of sublibraries, it is automatically converted to LMainLibName.

Since: 3.4.0.0

mainLibSet :: NonEmptySet LibraryName Source #

Library set with main library.

Since: 3.4.0.0