simple-cabal-0.1.3.1: Cabal file wrapper library
Safe HaskellSafe-Inferred
LanguageHaskell2010

SimpleCabal

Synopsis

Documentation

findCabalFile :: IO FilePath Source #

Find the .cabal file in the current directory.

Errors if more than one or no file found.

Since: 0.0.0.1

readFinalPackageDescription :: [(FlagName, Bool)] -> FilePath -> IO PackageDescription Source #

get PackageDescription from a cabal file

deprecates finalPackageDescription

Since: 0.1.2

finalPackageDescription :: [(FlagName, Bool)] -> FilePath -> IO PackageDescription Source #

Generate PackageDescription from the specified .cabal file and flags.

deprecated in favour of readFinalPackageDescription

Since: 0.0.0.1

parseFinalPackageDescription :: [(FlagName, Bool)] -> ByteString -> IO (Maybe PackageDescription) Source #

only available with Cabal-2.2+

Since: 0.1.2

makeFinalPackageDescription :: [(FlagName, Bool)] -> GenericPackageDescription -> IO PackageDescription Source #

convert a GenericPackageDescription to a final PackageDescription

Since: 0.1.2

getPackageId :: IO PackageIdentifier Source #

Get the package name-version from the .cabal file in the current directory.

Since: 0.0.0.1

buildDepends :: PackageDescription -> [Dependency] Source #

List build dependencies

buildDependencies :: PackageDescription -> [PackageName] Source #

Return the list of build dependencies of a package, excluding itself

setupDependencies Source #

Arguments

:: PackageDescription

pkg description

-> [PackageName]

depends

List of setup dependencies

testsuiteDependencies :: PackageDescription -> [PackageName] Source #

Return the list of testsuite dependencies of a package, excluding itself

allBuildInfo :: PackageDescription -> [BuildInfo] #

All BuildInfo in the PackageDescription: libraries, executables, test-suites and benchmarks.

Useful for implementing package checks.

data BuildInfo #

Constructors

BuildInfo 

Fields

Instances

Instances details
FromBuildInfo BuildInfo 
Instance details

Defined in Distribution.PackageDescription.Parsec

Structured BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Data BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Methods

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

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

toConstr :: BuildInfo -> Constr #

dataTypeOf :: BuildInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Semigroup BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Generic BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Associated Types

type Rep BuildInfo :: Type -> Type #

Read BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Show BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Binary BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

NFData BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Methods

rnf :: BuildInfo -> () #

Eq BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

type Rep BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

type Rep BuildInfo = D1 ('MetaData "BuildInfo" "Distribution.Types.BuildInfo" "Cabal-3.6.3.0" 'False) (C1 ('MetaCons "BuildInfo" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "buildable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "buildTools") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [LegacyExeDependency])) :*: (S1 ('MetaSel ('Just "buildToolDepends") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ExeDependency]) :*: (S1 ('MetaSel ('Just "cppOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "asmOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))) :*: ((S1 ('MetaSel ('Just "cmmOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "ccOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "cxxOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :*: (S1 ('MetaSel ('Just "ldOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "hsc2hsOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "pkgconfigDepends") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PkgconfigDependency]))))) :*: (((S1 ('MetaSel ('Just "frameworks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "extraFrameworkDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :*: (S1 ('MetaSel ('Just "asmSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: (S1 ('MetaSel ('Just "cmmSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: S1 ('MetaSel ('Just "cSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath])))) :*: ((S1 ('MetaSel ('Just "cxxSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: (S1 ('MetaSel ('Just "jsSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: S1 ('MetaSel ('Just "hsSourceDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath PackageDir SourceDir]))) :*: (S1 ('MetaSel ('Just "otherModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName]) :*: (S1 ('MetaSel ('Just "virtualModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName]) :*: S1 ('MetaSel ('Just "autogenModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName])))))) :*: ((((S1 ('MetaSel ('Just "defaultLanguage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Language)) :*: S1 ('MetaSel ('Just "otherLanguages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Language])) :*: (S1 ('MetaSel ('Just "defaultExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Extension]) :*: (S1 ('MetaSel ('Just "otherExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Extension]) :*: S1 ('MetaSel ('Just "oldExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Extension])))) :*: ((S1 ('MetaSel ('Just "extraLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "extraGHCiLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "extraBundledLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :*: (S1 ('MetaSel ('Just "extraLibFlavours") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "extraDynLibFlavours") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "extraLibDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))))) :*: (((S1 ('MetaSel ('Just "includeDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: S1 ('MetaSel ('Just "includes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath])) :*: (S1 ('MetaSel ('Just "autogenIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: (S1 ('MetaSel ('Just "installIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: S1 ('MetaSel ('Just "options") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCompilerFlavor [String]))))) :*: ((S1 ('MetaSel ('Just "profOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCompilerFlavor [String])) :*: (S1 ('MetaSel ('Just "sharedOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCompilerFlavor [String])) :*: S1 ('MetaSel ('Just "staticOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCompilerFlavor [String])))) :*: (S1 ('MetaSel ('Just "customFieldsBI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, String)]) :*: (S1 ('MetaSel ('Just "targetBuildDepends") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Dependency]) :*: S1 ('MetaSel ('Just "mixins") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Mixin]))))))))

data Library #

Constructors

Library 

Fields

Instances

Instances details
HasBuildInfo Library 
Instance details

Defined in Distribution.Types.Library

Methods

buildInfo :: Lens' Library BuildInfo #

buildable :: Lens' Library Bool #

buildTools :: Lens' Library [LegacyExeDependency] #

buildToolDepends :: Lens' Library [ExeDependency] #

cppOptions :: Lens' Library [String] #

asmOptions :: Lens' Library [String] #

cmmOptions :: Lens' Library [String] #

ccOptions :: Lens' Library [String] #

cxxOptions :: Lens' Library [String] #

ldOptions :: Lens' Library [String] #

hsc2hsOptions :: Lens' Library [String] #

pkgconfigDepends :: Lens' Library [PkgconfigDependency] #

frameworks :: Lens' Library [String] #

extraFrameworkDirs :: Lens' Library [String] #

asmSources :: Lens' Library [FilePath] #

cmmSources :: Lens' Library [FilePath] #

cSources :: Lens' Library [FilePath] #

cxxSources :: Lens' Library [FilePath] #

jsSources :: Lens' Library [FilePath] #

hsSourceDirs :: Lens' Library [SymbolicPath PackageDir SourceDir] #

otherModules :: Lens' Library [ModuleName] #

virtualModules :: Lens' Library [ModuleName] #

autogenModules :: Lens' Library [ModuleName] #

defaultLanguage :: Lens' Library (Maybe Language) #

otherLanguages :: Lens' Library [Language] #

defaultExtensions :: Lens' Library [Extension] #

otherExtensions :: Lens' Library [Extension] #

oldExtensions :: Lens' Library [Extension] #

extraLibs :: Lens' Library [String] #

extraGHCiLibs :: Lens' Library [String] #

extraBundledLibs :: Lens' Library [String] #

extraLibFlavours :: Lens' Library [String] #

extraDynLibFlavours :: Lens' Library [String] #

extraLibDirs :: Lens' Library [String] #

includeDirs :: Lens' Library [FilePath] #

includes :: Lens' Library [FilePath] #

autogenIncludes :: Lens' Library [FilePath] #

installIncludes :: Lens' Library [FilePath] #

options :: Lens' Library (PerCompilerFlavor [String]) #

profOptions :: Lens' Library (PerCompilerFlavor [String]) #

sharedOptions :: Lens' Library (PerCompilerFlavor [String]) #

staticOptions :: Lens' Library (PerCompilerFlavor [String]) #

customFieldsBI :: Lens' Library [(String, String)] #

targetBuildDepends :: Lens' Library [Dependency] #

mixins :: Lens' Library [Mixin] #

Structured Library 
Instance details

Defined in Distribution.Types.Library

Data Library 
Instance details

Defined in Distribution.Types.Library

Methods

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

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

toConstr :: Library -> Constr #

dataTypeOf :: Library -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid Library

This instance is not good.

We need it for addBuildableCondition. More correct method would be some kind of "create empty clone".

More concretely, addBuildableCondition will make `libVisibility = False` libraries when `buildable: false`. This may cause problems.

Instance details

Defined in Distribution.Types.Library

Semigroup Library 
Instance details

Defined in Distribution.Types.Library

Generic Library 
Instance details

Defined in Distribution.Types.Library

Associated Types

type Rep Library :: Type -> Type #

Methods

from :: Library -> Rep Library x #

to :: Rep Library x -> Library #

Read Library 
Instance details

Defined in Distribution.Types.Library

Show Library 
Instance details

Defined in Distribution.Types.Library

Binary Library 
Instance details

Defined in Distribution.Types.Library

Methods

put :: Library -> Put #

get :: Get Library #

putList :: [Library] -> Put #

NFData Library 
Instance details

Defined in Distribution.Types.Library

Methods

rnf :: Library -> () #

Eq Library 
Instance details

Defined in Distribution.Types.Library

Methods

(==) :: Library -> Library -> Bool #

(/=) :: Library -> Library -> Bool #

type Rep Library 
Instance details

Defined in Distribution.Types.Library

exeDepName :: LegacyExeDependency -> String Source #

name of legacy exe dep

data FlagName #

A FlagName is the name of a user-defined configuration flag

Use mkFlagName and unFlagName to convert from/to a String.

This type is opaque since Cabal-2.0

Since: Cabal-2.0.0.2

Instances

Instances details
Parsec FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

parsec :: CabalParsing m => m FlagName #

Pretty FlagName 
Instance details

Defined in Distribution.Types.Flag

Structured FlagName 
Instance details

Defined in Distribution.Types.Flag

Data FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

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

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

toConstr :: FlagName -> Constr #

dataTypeOf :: FlagName -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString FlagName

mkFlagName

Since: Cabal-2.0.0.2

Instance details

Defined in Distribution.Types.Flag

Generic FlagName 
Instance details

Defined in Distribution.Types.Flag

Associated Types

type Rep FlagName :: Type -> Type #

Methods

from :: FlagName -> Rep FlagName x #

to :: Rep FlagName x -> FlagName #

Read FlagName 
Instance details

Defined in Distribution.Types.Flag

Show FlagName 
Instance details

Defined in Distribution.Types.Flag

Binary FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

put :: FlagName -> Put #

get :: Get FlagName #

putList :: [FlagName] -> Put #

NFData FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

rnf :: FlagName -> () #

Eq FlagName 
Instance details

Defined in Distribution.Types.Flag

Ord FlagName 
Instance details

Defined in Distribution.Types.Flag

type Rep FlagName 
Instance details

Defined in Distribution.Types.Flag

type Rep FlagName = D1 ('MetaData "FlagName" "Distribution.Types.Flag" "Cabal-3.6.3.0" 'True) (C1 ('MetaCons "FlagName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortText)))

mkFlagName :: String -> FlagName #

Construct a FlagName from a String

mkFlagName is the inverse to unFlagName

Note: No validations are performed to ensure that the resulting FlagName is valid

Since: Cabal-2.0.0.2

hasExes :: PackageDescription -> Bool #

does this package have any executables?

hasLibs :: PackageDescription -> Bool #

Does this package have any libraries?

data PackageDescription #

This data type is the internal representation of the file pkg.cabal. It contains two kinds of information about the package: information which is needed for all packages, such as the package name and version, and information which is needed for the simple build system only, such as the compiler options and library name.

Constructors

PackageDescription 

Fields

Instances

Instances details
Package PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

HasBuildInfos PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Structured PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Data PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Methods

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

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

toConstr :: PackageDescription -> Constr #

dataTypeOf :: PackageDescription -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Associated Types

type Rep PackageDescription :: Type -> Type #

Read PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Show PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Binary PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

NFData PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Methods

rnf :: PackageDescription -> () #

Eq PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

type Rep PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

type Rep PackageDescription = D1 ('MetaData "PackageDescription" "Distribution.Types.PackageDescription" "Cabal-3.6.3.0" 'False) (C1 ('MetaCons "PackageDescription" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "specVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CabalSpecVersion) :*: (S1 ('MetaSel ('Just "package") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageIdentifier) :*: S1 ('MetaSel ('Just "licenseRaw") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either License License)))) :*: ((S1 ('MetaSel ('Just "licenseFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath PackageDir LicenseFile]) :*: S1 ('MetaSel ('Just "copyright") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText)) :*: (S1 ('MetaSel ('Just "maintainer") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "author") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText)))) :*: (((S1 ('MetaSel ('Just "stability") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "testedWith") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(CompilerFlavor, VersionRange)])) :*: (S1 ('MetaSel ('Just "homepage") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "pkgUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText))) :*: ((S1 ('MetaSel ('Just "bugReports") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "sourceRepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SourceRepo])) :*: (S1 ('MetaSel ('Just "synopsis") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "description") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText))))) :*: (((S1 ('MetaSel ('Just "category") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText) :*: (S1 ('MetaSel ('Just "customFieldsPD") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, String)]) :*: S1 ('MetaSel ('Just "buildTypeRaw") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe BuildType)))) :*: ((S1 ('MetaSel ('Just "setupBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SetupBuildInfo)) :*: S1 ('MetaSel ('Just "library") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Library))) :*: (S1 ('MetaSel ('Just "subLibraries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Library]) :*: S1 ('MetaSel ('Just "executables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Executable])))) :*: (((S1 ('MetaSel ('Just "foreignLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ForeignLib]) :*: S1 ('MetaSel ('Just "testSuites") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TestSuite])) :*: (S1 ('MetaSel ('Just "benchmarks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Benchmark]) :*: S1 ('MetaSel ('Just "dataFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]))) :*: ((S1 ('MetaSel ('Just "dataDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Just "extraSrcFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath])) :*: (S1 ('MetaSel ('Just "extraTmpFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: S1 ('MetaSel ('Just "extraDocFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath])))))))

data PackageIdentifier #

The name and version of a package.

Constructors

PackageIdentifier 

Fields

Instances

Instances details
Package PackageIdentifier 
Instance details

Defined in Distribution.Package

Parsec PackageIdentifier
>>> simpleParsec "foo-bar-0" :: Maybe PackageIdentifier
Just (PackageIdentifier {pkgName = PackageName "foo-bar", pkgVersion = mkVersion [0]})
>>> simpleParsec "foo-bar" :: Maybe PackageIdentifier
Just (PackageIdentifier {pkgName = PackageName "foo-bar", pkgVersion = mkVersion []})

Note: Stricter than Text instance

>>> simpleParsec "foo-bar-0-0" :: Maybe PackageIdentifier
Nothing
>>> simpleParsec "foo-bar.0" :: Maybe PackageIdentifier
Nothing
>>> simpleParsec "foo-bar.4-2" :: Maybe PackageIdentifier
Nothing
>>> simpleParsec "1.2.3" :: Maybe PackageIdentifier
Nothing
Instance details

Defined in Distribution.Types.PackageId

Pretty PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Structured PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Data PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Methods

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

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

toConstr :: PackageIdentifier -> Constr #

dataTypeOf :: PackageIdentifier -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Associated Types

type Rep PackageIdentifier :: Type -> Type #

Read PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Show PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Binary PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

NFData PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Methods

rnf :: PackageIdentifier -> () #

Eq PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Ord PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

type Rep PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

type Rep PackageIdentifier = D1 ('MetaData "PackageIdentifier" "Distribution.Types.PackageId" "Cabal-3.6.3.0" 'False) (C1 ('MetaCons "PackageIdentifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "pkgName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageName) :*: S1 ('MetaSel ('Just "pkgVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)))

data PackageName #

A package name.

Use mkPackageName and unPackageName to convert from/to a String.

This type is opaque since Cabal-2.0

Since: Cabal-2.0.0.2

Instances

Instances details
Parsec PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

parsec :: CabalParsing m => m PackageName #

Pretty PackageName 
Instance details

Defined in Distribution.Types.PackageName

Structured PackageName 
Instance details

Defined in Distribution.Types.PackageName

Data PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

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

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

toConstr :: PackageName -> Constr #

dataTypeOf :: PackageName -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString PackageName

mkPackageName

Since: Cabal-2.0.0.2

Instance details

Defined in Distribution.Types.PackageName

Generic PackageName 
Instance details

Defined in Distribution.Types.PackageName

Associated Types

type Rep PackageName :: Type -> Type #

Read PackageName 
Instance details

Defined in Distribution.Types.PackageName

Show PackageName 
Instance details

Defined in Distribution.Types.PackageName

Binary PackageName 
Instance details

Defined in Distribution.Types.PackageName

NFData PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

rnf :: PackageName -> () #

Eq PackageName 
Instance details

Defined in Distribution.Types.PackageName

Ord PackageName 
Instance details

Defined in Distribution.Types.PackageName

type Rep PackageName 
Instance details

Defined in Distribution.Types.PackageName

type Rep PackageName = D1 ('MetaData "PackageName" "Distribution.Types.PackageName" "Cabal-3.6.3.0" 'True) (C1 ('MetaCons "PackageName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortText)))

mkPackageName :: String -> PackageName #

Construct a PackageName from a String

mkPackageName is the inverse to unPackageName

Note: No validations are performed to ensure that the resulting PackageName is valid

Since: Cabal-2.0.0.2

packageName :: Package pkg => pkg -> PackageName #

packageVersion :: PackageIdentifier -> String Source #

version string from PackageIdentifier

showPkgId :: PackageIdentifier -> String Source #

convert PackageIdentifier to a displayable string

showVersion :: Version -> String Source #

render a Version