| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
SimpleCabal
Synopsis
- findCabalFile :: IO FilePath
- readFinalPackageDescription :: [(FlagName, Bool)] -> FilePath -> IO PackageDescription
- finalPackageDescription :: [(FlagName, Bool)] -> FilePath -> IO PackageDescription
- parseFinalPackageDescription :: [(FlagName, Bool)] -> ByteString -> IO (Maybe PackageDescription)
- makeFinalPackageDescription :: [(FlagName, Bool)] -> GenericPackageDescription -> IO PackageDescription
- getPackageId :: IO PackageIdentifier
- buildDepends :: PackageDescription -> [Dependency]
- buildDependencies :: PackageDescription -> [PackageName]
- setupDependencies :: PackageDescription -> [PackageName]
- testsuiteDependencies :: PackageDescription -> [PackageName]
- allBuildInfo :: PackageDescription -> [BuildInfo]
- allLibraries :: PackageDescription -> [Library]
- data BuildInfo = BuildInfo {
- buildable :: Bool
- buildTools :: [LegacyExeDependency]
- buildToolDepends :: [ExeDependency]
- cppOptions :: [String]
- asmOptions :: [String]
- cmmOptions :: [String]
- ccOptions :: [String]
- cxxOptions :: [String]
- ldOptions :: [String]
- hsc2hsOptions :: [String]
- pkgconfigDepends :: [PkgconfigDependency]
- frameworks :: [String]
- extraFrameworkDirs :: [String]
- asmSources :: [FilePath]
- cmmSources :: [FilePath]
- cSources :: [FilePath]
- cxxSources :: [FilePath]
- jsSources :: [FilePath]
- hsSourceDirs :: [SymbolicPath PackageDir SourceDir]
- otherModules :: [ModuleName]
- virtualModules :: [ModuleName]
- autogenModules :: [ModuleName]
- defaultLanguage :: Maybe Language
- otherLanguages :: [Language]
- defaultExtensions :: [Extension]
- otherExtensions :: [Extension]
- oldExtensions :: [Extension]
- extraLibs :: [String]
- extraGHCiLibs :: [String]
- extraBundledLibs :: [String]
- extraLibFlavours :: [String]
- extraDynLibFlavours :: [String]
- extraLibDirs :: [String]
- includeDirs :: [FilePath]
- includes :: [FilePath]
- autogenIncludes :: [FilePath]
- installIncludes :: [FilePath]
- options :: PerCompilerFlavor [String]
- profOptions :: PerCompilerFlavor [String]
- sharedOptions :: PerCompilerFlavor [String]
- staticOptions :: PerCompilerFlavor [String]
- customFieldsBI :: [(String, String)]
- targetBuildDepends :: [Dependency]
- mixins :: [Mixin]
- data Library = Library {}
- depPkgName :: Dependency -> PackageName
- exeDepName :: LegacyExeDependency -> String
- pkgcfgDepName :: PkgconfigDependency -> String
- data FlagName
- mkFlagName :: String -> FlagName
- hasExes :: PackageDescription -> Bool
- hasLibs :: PackageDescription -> Bool
- data PackageDescription = PackageDescription {
- specVersion :: CabalSpecVersion
- package :: PackageIdentifier
- licenseRaw :: Either License License
- licenseFiles :: [SymbolicPath PackageDir LicenseFile]
- copyright :: !ShortText
- maintainer :: !ShortText
- author :: !ShortText
- stability :: !ShortText
- testedWith :: [(CompilerFlavor, VersionRange)]
- homepage :: !ShortText
- pkgUrl :: !ShortText
- bugReports :: !ShortText
- sourceRepos :: [SourceRepo]
- synopsis :: !ShortText
- description :: !ShortText
- category :: !ShortText
- customFieldsPD :: [(String, String)]
- buildTypeRaw :: Maybe BuildType
- setupBuildInfo :: Maybe SetupBuildInfo
- library :: Maybe Library
- subLibraries :: [Library]
- executables :: [Executable]
- foreignLibs :: [ForeignLib]
- testSuites :: [TestSuite]
- benchmarks :: [Benchmark]
- dataFiles :: [FilePath]
- dataDir :: FilePath
- extraSrcFiles :: [FilePath]
- extraTmpFiles :: [FilePath]
- extraDocFiles :: [FilePath]
- data PackageIdentifier = PackageIdentifier {}
- data PackageName
- mkPackageName :: String -> PackageName
- unPackageName :: PackageName -> String
- packageName :: Package pkg => pkg -> PackageName
- packageVersion :: PackageIdentifier -> String
- readGenericPackageDescription :: Verbosity -> FilePath -> IO GenericPackageDescription
- showPkgId :: PackageIdentifier -> String
- showVersion :: Version -> String
- simpleParse :: Parsec a => String -> Maybe a
- tryFindPackageDesc :: FilePath -> IO FilePath
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
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.
allLibraries :: PackageDescription -> [Library] #
Constructors
| BuildInfo | |
Fields
| |
Instances
Constructors
| Library | |
Fields
| |
Instances
depPkgName :: Dependency -> PackageName #
exeDepName :: LegacyExeDependency -> String Source #
name of legacy exe dep
pkgcfgDepName :: PkgconfigDependency -> String Source #
pkgconfig dep name
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
| Parsec FlagName | |
Defined in Distribution.Types.Flag Methods parsec :: CabalParsing m => m FlagName # | |
| Pretty FlagName | |
Defined in Distribution.Types.Flag | |
| Structured FlagName | |
Defined in Distribution.Types.Flag | |
| Data FlagName | |
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 | Since: Cabal-2.0.0.2 |
Defined in Distribution.Types.Flag Methods fromString :: String -> FlagName # | |
| Generic FlagName | |
| Read FlagName | |
| Show FlagName | |
| Binary FlagName | |
| NFData FlagName | |
Defined in Distribution.Types.Flag | |
| Eq FlagName | |
| Ord FlagName | |
Defined in Distribution.Types.Flag | |
| type Rep FlagName | |
Defined in Distribution.Types.Flag | |
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
Instances
data PackageIdentifier #
The name and version of a package.
Constructors
| PackageIdentifier | |
Fields
| |
Instances
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
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
unPackageName :: PackageName -> String #
Convert PackageName to String
packageName :: Package pkg => pkg -> PackageName #
packageVersion :: PackageIdentifier -> String Source #
version string from PackageIdentifier
readGenericPackageDescription :: Verbosity -> FilePath -> IO GenericPackageDescription #
Parse the given package file.
showPkgId :: PackageIdentifier -> String Source #
convert PackageIdentifier to a displayable string
showVersion :: Version -> String Source #
render a Version
simpleParse :: Parsec a => String -> Maybe a #