Cabal-1.3.4: A framework for packaging Haskell softwareContentsIndex
Distribution.PackageDescription
Portabilityportable
Stabilityalpha
MaintainerIsaac Jones <ijones@syntaxpolice.org>
Contents
Package descriptions
Libraries
Executables
Build information
Supplementary build information
package configuration
Description
Package description and parsing.
Synopsis
data PackageDescription = PackageDescription {
package :: PackageIdentifier
license :: License
licenseFile :: FilePath
copyright :: String
maintainer :: String
author :: String
stability :: String
testedWith :: [(CompilerFlavor, VersionRange)]
homepage :: String
pkgUrl :: String
synopsis :: String
description :: String
category :: String
buildDepends :: [Dependency]
descCabalVersion :: VersionRange
buildType :: (Maybe BuildType)
library :: (Maybe Library)
executables :: [Executable]
dataFiles :: [FilePath]
extraSrcFiles :: [FilePath]
extraTmpFiles :: [FilePath]
}
emptyPackageDescription :: PackageDescription
data BuildType
= Simple
| Configure
| Make
| Custom
data Library = Library {
exposedModules :: [String]
libBuildInfo :: BuildInfo
}
emptyLibrary :: Library
withLib :: PackageDescription -> a -> (Library -> IO a) -> IO a
hasLibs :: PackageDescription -> Bool
libModules :: PackageDescription -> [String]
data Executable = Executable {
exeName :: String
modulePath :: FilePath
buildInfo :: BuildInfo
}
emptyExecutable :: Executable
withExe :: PackageDescription -> (Executable -> IO a) -> IO ()
hasExes :: PackageDescription -> Bool
exeModules :: PackageDescription -> [String]
data BuildInfo = BuildInfo {
buildable :: Bool
buildTools :: [Dependency]
cppOptions :: [String]
ccOptions :: [String]
ldOptions :: [String]
pkgconfigDepends :: [Dependency]
frameworks :: [String]
cSources :: [FilePath]
hsSourceDirs :: [FilePath]
otherModules :: [String]
extensions :: [Extension]
extraLibs :: [String]
extraLibDirs :: [String]
includeDirs :: [FilePath]
includes :: [FilePath]
installIncludes :: [FilePath]
options :: [(CompilerFlavor, [String])]
ghcProfOptions :: [String]
ghcSharedOptions :: [String]
}
emptyBuildInfo :: BuildInfo
allBuildInfo :: PackageDescription -> [BuildInfo]
unionBuildInfo :: BuildInfo -> BuildInfo -> BuildInfo
hcOptions :: CompilerFlavor -> BuildInfo -> [String]
type HookedBuildInfo = (Maybe BuildInfo, [(String, BuildInfo)])
emptyHookedBuildInfo :: HookedBuildInfo
updatePackageDescription :: HookedBuildInfo -> PackageDescription -> PackageDescription
data GenericPackageDescription = GenericPackageDescription {
packageDescription :: PackageDescription
genPackageFlags :: [Flag]
condLibrary :: (Maybe (CondTree ConfVar [Dependency] Library))
condExecutables :: [(String, CondTree ConfVar [Dependency] Executable)]
}
data Flag = MkFlag {
flagName :: String
flagDescription :: String
flagDefault :: Bool
}
data CondTree v c a = CondNode {
condTreeData :: a
condTreeConstraints :: c
condTreeComponents :: [(Condition v, CondTree v c a, Maybe (CondTree v c a))]
}
data ConfVar
= OS String
| Arch String
| Flag ConfFlag
| Impl String VersionRange
data ConfFlag = ConfFlag String
data Condition c
= Var c
| Lit Bool
| CNot (Condition c)
| COr (Condition c) (Condition c)
| CAnd (Condition c) (Condition c)
Package descriptions
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
package :: PackageIdentifier
license :: License
licenseFile :: FilePath
copyright :: String
maintainer :: String
author :: String
stability :: String
testedWith :: [(CompilerFlavor, VersionRange)]
homepage :: String
pkgUrl :: String
synopsis :: StringA one-line summary of this package
description :: StringA more verbose description of this package
category :: String
buildDepends :: [Dependency]
descCabalVersion :: VersionRangeIf this package depends on a specific version of Cabal, give that here.
buildType :: (Maybe BuildType)
library :: (Maybe Library)
executables :: [Executable]
dataFiles :: [FilePath]
extraSrcFiles :: [FilePath]
extraTmpFiles :: [FilePath]
show/hide Instances
emptyPackageDescription :: PackageDescription
data BuildType
The type of build system used by this package.
Constructors
Simplecalls Distribution.Simple.defaultMain
Configurecalls Distribution.Simple.defaultMainWithHooks defaultUserHooks, which invokes configure to generate additional build information used by later phases.
Makecalls Distribution.Make.defaultMain
Customuses user-supplied Setup.hs or Setup.lhs (default)
show/hide Instances
Libraries
data Library
Constructors
Library
exposedModules :: [String]
libBuildInfo :: BuildInfo
show/hide Instances
emptyLibrary :: Library
withLib :: PackageDescription -> a -> (Library -> IO a) -> IO a
If the package description has a library section, call the given function with the library build info as argument.
hasLibs :: PackageDescription -> Bool
does this package have any libraries?
libModules :: PackageDescription -> [String]
Get all the module names from the libraries in this package
Executables
data Executable
Constructors
Executable
exeName :: String
modulePath :: FilePath
buildInfo :: BuildInfo
show/hide Instances
emptyExecutable :: Executable
withExe :: PackageDescription -> (Executable -> IO a) -> IO ()
Perform the action on each buildable Executable in the package description.
hasExes :: PackageDescription -> Bool
does this package have any executables?
exeModules :: PackageDescription -> [String]
Get all the module names from the exes in this package
Build information
data BuildInfo
Constructors
BuildInfo
buildable :: Boolcomponent is buildable here
buildTools :: [Dependency]tools needed to build this bit
cppOptions :: [String]options for pre-processing Haskell code
ccOptions :: [String]options for C compiler
ldOptions :: [String]options for linker
pkgconfigDepends :: [Dependency]pkg-config packages that are used
frameworks :: [String]support frameworks for Mac OS X
cSources :: [FilePath]
hsSourceDirs :: [FilePath]where to look for the haskell module hierarchy
otherModules :: [String]non-exposed or non-main modules
extensions :: [Extension]
extraLibs :: [String]what libraries to link with when compiling a program that uses your package
extraLibDirs :: [String]
includeDirs :: [FilePath]directories to find .h files
includes :: [FilePath]The .h files to be found in includeDirs
installIncludes :: [FilePath].h files to install with the package
options :: [(CompilerFlavor, [String])]
ghcProfOptions :: [String]
ghcSharedOptions :: [String]
show/hide Instances
emptyBuildInfo :: BuildInfo
allBuildInfo :: PackageDescription -> [BuildInfo]
The BuildInfo for the library (if there is one and it's buildable) and all the buildable executables. Useful for gathering dependencies.
unionBuildInfo :: BuildInfo -> BuildInfo -> BuildInfo
hcOptions :: CompilerFlavor -> BuildInfo -> [String]
Select options for a particular Haskell compiler.
Supplementary build information
type HookedBuildInfo = (Maybe BuildInfo, [(String, BuildInfo)])
emptyHookedBuildInfo :: HookedBuildInfo
updatePackageDescription :: HookedBuildInfo -> PackageDescription -> PackageDescription
package configuration
data GenericPackageDescription
Constructors
GenericPackageDescription
packageDescription :: PackageDescription
genPackageFlags :: [Flag]
condLibrary :: (Maybe (CondTree ConfVar [Dependency] Library))
condExecutables :: [(String, CondTree ConfVar [Dependency] Executable)]
show/hide Instances
data Flag
A flag can represent a feature to be included, or a way of linking a target against its dependencies, or in fact whatever you can think of.
Constructors
MkFlag
flagName :: String
flagDescription :: String
flagDefault :: Bool
show/hide Instances
data CondTree v c a
Constructors
CondNode
condTreeData :: a
condTreeConstraints :: c
condTreeComponents :: [(Condition v, CondTree v c a, Maybe (CondTree v c a))]
show/hide Instances
(Show a, Show c, ??? a c v) => Show (CondTree v c a)
data ConfVar
A ConfVar represents the variable type used.
Constructors
OS String
Arch String
Flag ConfFlag
Impl String VersionRange
show/hide Instances
data ConfFlag
A ConfFlag represents an user-defined flag
Constructors
ConfFlag String
show/hide Instances
data Condition c
A boolean expression parameterized over the variable type used.
Constructors
Var c
Lit Bool
CNot (Condition c)
COr (Condition c) (Condition c)
CAnd (Condition c) (Condition c)
show/hide Instances
Produced by Haddock version 0.9