Copyright | Isaac Jones 2003-2005 |
---|---|
License | BSD3 |
Maintainer | cabal-devel@haskell.org |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
This is the command line front end to the Simple build system. When given the parsed command-line args and package information, is able to perform basic commands like configure, build, install, register, etc.
This module exports the main functions that Setup.hs scripts use. It
re-exports the UserHooks
type, the standard entry points like
defaultMain
and defaultMainWithHooks
and the predefined sets of
UserHooks
that custom Setup.hs
scripts can extend to add their own
behaviour.
This module isn't called "Simple" because it's simple. Far from it. It's called "Simple" because it does complicated things to simple software.
The original idea was that there could be different build systems that all presented the same compatible command line interfaces. There is still a Distribution.Make system but in practice no packages use it.
Synopsis
- module Distribution.Package
- module Distribution.Version
- module Distribution.License
- data AbiTag
- data CompilerInfo = CompilerInfo {}
- data CompilerId = CompilerId CompilerFlavor Version
- data PerCompilerFlavor v = PerCompilerFlavor v v
- data CompilerFlavor
- knownCompilerFlavors :: [CompilerFlavor]
- classifyCompilerFlavor :: String -> CompilerFlavor
- buildCompilerFlavor :: CompilerFlavor
- buildCompilerId :: CompilerId
- defaultCompilerFlavor :: Maybe CompilerFlavor
- perCompilerFlavorToList :: PerCompilerFlavor v -> [(CompilerFlavor, v)]
- abiTagString :: AbiTag -> String
- unknownCompilerInfo :: CompilerId -> AbiTag -> CompilerInfo
- data ProfDetailLevel
- data DebugInfoLevel
- data OptimisationLevel
- type PackageDBStack = [PackageDB]
- data PackageDB
- data Compiler = Compiler {
- compilerId :: CompilerId
- compilerAbiTag :: AbiTag
- compilerCompat :: [CompilerId]
- compilerLanguages :: [(Language, Flag)]
- compilerExtensions :: [(Extension, Maybe Flag)]
- compilerProperties :: Map String String
- showCompilerId :: Compiler -> String
- showCompilerIdWithAbi :: Compiler -> String
- compilerFlavor :: Compiler -> CompilerFlavor
- compilerVersion :: Compiler -> Version
- compilerCompatFlavor :: CompilerFlavor -> Compiler -> Bool
- compilerCompatVersion :: CompilerFlavor -> Compiler -> Maybe Version
- compilerInfo :: Compiler -> CompilerInfo
- registrationPackageDB :: PackageDBStack -> PackageDB
- absolutePackageDBPaths :: PackageDBStack -> NoCallStackIO PackageDBStack
- absolutePackageDBPath :: PackageDB -> NoCallStackIO PackageDB
- flagToOptimisationLevel :: Maybe String -> OptimisationLevel
- flagToDebugInfoLevel :: Maybe String -> DebugInfoLevel
- unsupportedLanguages :: Compiler -> [Language] -> [Language]
- languageToFlags :: Compiler -> Maybe Language -> [Flag]
- unsupportedExtensions :: Compiler -> [Extension] -> [Extension]
- extensionsToFlags :: Compiler -> [Extension] -> [Flag]
- parmakeSupported :: Compiler -> Bool
- reexportedModulesSupported :: Compiler -> Bool
- renamingPackageFlagsSupported :: Compiler -> Bool
- unifiedIPIDRequired :: Compiler -> Bool
- packageKeySupported :: Compiler -> Bool
- unitIdSupported :: Compiler -> Bool
- backpackSupported :: Compiler -> Bool
- libraryDynDirSupported :: Compiler -> Bool
- arResponseFilesSupported :: Compiler -> Bool
- coverageSupported :: Compiler -> Bool
- profilingSupported :: Compiler -> Bool
- flagToProfDetailLevel :: String -> ProfDetailLevel
- knownProfDetailLevels :: [(String, [String], ProfDetailLevel)]
- showProfDetailLevel :: ProfDetailLevel -> String
- module Language.Haskell.Extension
- defaultMain :: IO ()
- defaultMainNoRead :: GenericPackageDescription -> IO ()
- defaultMainArgs :: [String] -> IO ()
- data UserHooks = UserHooks {
- readDesc :: IO (Maybe GenericPackageDescription)
- hookedPreProcessors :: [PPSuffixHandler]
- hookedPrograms :: [Program]
- preConf :: Args -> ConfigFlags -> IO HookedBuildInfo
- confHook :: (GenericPackageDescription, HookedBuildInfo) -> ConfigFlags -> IO LocalBuildInfo
- postConf :: Args -> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preBuild :: Args -> BuildFlags -> IO HookedBuildInfo
- buildHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> BuildFlags -> IO ()
- postBuild :: Args -> BuildFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preRepl :: Args -> ReplFlags -> IO HookedBuildInfo
- replHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> ReplFlags -> [String] -> IO ()
- postRepl :: Args -> ReplFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preClean :: Args -> CleanFlags -> IO HookedBuildInfo
- cleanHook :: PackageDescription -> () -> UserHooks -> CleanFlags -> IO ()
- postClean :: Args -> CleanFlags -> PackageDescription -> () -> IO ()
- preCopy :: Args -> CopyFlags -> IO HookedBuildInfo
- copyHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> CopyFlags -> IO ()
- postCopy :: Args -> CopyFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preInst :: Args -> InstallFlags -> IO HookedBuildInfo
- instHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> InstallFlags -> IO ()
- postInst :: Args -> InstallFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preReg :: Args -> RegisterFlags -> IO HookedBuildInfo
- regHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
- postReg :: Args -> RegisterFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preUnreg :: Args -> RegisterFlags -> IO HookedBuildInfo
- unregHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> RegisterFlags -> IO ()
- postUnreg :: Args -> RegisterFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preHscolour :: Args -> HscolourFlags -> IO HookedBuildInfo
- hscolourHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> HscolourFlags -> IO ()
- postHscolour :: Args -> HscolourFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preDoctest :: Args -> DoctestFlags -> IO HookedBuildInfo
- doctestHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> DoctestFlags -> IO ()
- postDoctest :: Args -> DoctestFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preHaddock :: Args -> HaddockFlags -> IO HookedBuildInfo
- haddockHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> HaddockFlags -> IO ()
- postHaddock :: Args -> HaddockFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preTest :: Args -> TestFlags -> IO HookedBuildInfo
- testHook :: Args -> PackageDescription -> LocalBuildInfo -> UserHooks -> TestFlags -> IO ()
- postTest :: Args -> TestFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- preBench :: Args -> BenchmarkFlags -> IO HookedBuildInfo
- benchHook :: Args -> PackageDescription -> LocalBuildInfo -> UserHooks -> BenchmarkFlags -> IO ()
- postBench :: Args -> BenchmarkFlags -> PackageDescription -> LocalBuildInfo -> IO ()
- type Args = [String]
- defaultMainWithHooks :: UserHooks -> IO ()
- defaultMainWithHooksArgs :: UserHooks -> [String] -> IO ()
- defaultMainWithHooksNoRead :: UserHooks -> GenericPackageDescription -> IO ()
- defaultMainWithHooksNoReadArgs :: UserHooks -> GenericPackageDescription -> [String] -> IO ()
- simpleUserHooks :: UserHooks
- autoconfUserHooks :: UserHooks
- emptyUserHooks :: UserHooks
Documentation
module Distribution.Package
module Distribution.Version
module Distribution.License
Instances
Eq AbiTag # | |
Read AbiTag # | |
Show AbiTag # | |
Generic AbiTag # | |
Binary AbiTag # | |
Structured AbiTag # | |
Defined in Distribution.Compiler | |
Pretty AbiTag # | |
Defined in Distribution.Compiler | |
Parsec AbiTag # | |
Defined in Distribution.Compiler parsec :: CabalParsing m => m AbiTag Source # | |
type Rep AbiTag # | |
Defined in Distribution.Compiler type Rep AbiTag = D1 ('MetaData "AbiTag" "Distribution.Compiler" "Cabal-3.2.1.0" 'False) (C1 ('MetaCons "NoAbiTag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AbiTag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) |
data CompilerInfo Source #
Compiler information used for resolving configurations. Some fields can be set to Nothing to indicate that the information is unknown.
CompilerInfo | |
|
Instances
data CompilerId Source #
Instances
data PerCompilerFlavor v Source #
PerCompilerFlavor
carries only info per GHC and GHCJS
Cabal parses only ghc-options
and ghcjs-options
, others are omitted.
Instances
data CompilerFlavor Source #
Instances
defaultCompilerFlavor :: Maybe CompilerFlavor Source #
The default compiler flavour to pick when compiling stuff. This defaults to the compiler used to build the Cabal lib.
However if it's not a recognised compiler then it's Nothing
and the user
will have to specify which compiler they want.
perCompilerFlavorToList :: PerCompilerFlavor v -> [(CompilerFlavor, v)] Source #
abiTagString :: AbiTag -> String Source #
unknownCompilerInfo :: CompilerId -> AbiTag -> CompilerInfo Source #
Make a CompilerInfo of which only the known information is its CompilerId, its AbiTag and that it does not claim to be compatible with other compiler id's.
data ProfDetailLevel Source #
Some compilers (notably GHC) support profiling and can instrument programs so the system can account costs to different functions. There are different levels of detail that can be used for this accounting. For compilers that do not support this notion or the particular detail levels, this is either ignored or just capped to some similar level they do support.
ProfDetailNone | |
ProfDetailDefault | |
ProfDetailExportedFunctions | |
ProfDetailToplevelFunctions | |
ProfDetailAllFunctions | |
ProfDetailOther String |
Instances
data DebugInfoLevel Source #
Some compilers support emitting debug info. Some have different levels. For compilers that do not the level is just capped to the level they do support.
Instances
data OptimisationLevel Source #
Some compilers support optimising. Some have different levels. For compilers that do not the level is just capped to the level they do support.
Instances
type PackageDBStack = [PackageDB] Source #
We typically get packages from several databases, and stack them together. This type lets us be explicit about that stacking. For example typical stacks include:
[GlobalPackageDB] [GlobalPackageDB, UserPackageDB] [GlobalPackageDB, SpecificPackageDB "package.conf.inplace"]
Note that the GlobalPackageDB
is invariably at the bottom since it
contains the rts, base and other special compiler-specific packages.
We are not restricted to using just the above combinations. In particular we can use several custom package dbs and the user package db together.
When it comes to writing, the top most (last) package is used.
Some compilers have a notion of a database of available packages. For some there is just one global db of packages, other compilers support a per-user or an arbitrary db specified at some location in the file system. This can be used to build isloated environments of packages, for example to build a collection of related packages without installing them globally.
Instances
Eq PackageDB # | |
Ord PackageDB # | |
Defined in Distribution.Simple.Compiler | |
Read PackageDB # | |
Show PackageDB # | |
Generic PackageDB # | |
Binary PackageDB # | |
Structured PackageDB # | |
Defined in Distribution.Simple.Compiler | |
type Rep PackageDB # | |
Defined in Distribution.Simple.Compiler type Rep PackageDB = D1 ('MetaData "PackageDB" "Distribution.Simple.Compiler" "Cabal-3.2.1.0" 'False) (C1 ('MetaCons "GlobalPackageDB" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UserPackageDB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SpecificPackageDB" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)))) |
Compiler | |
|
Instances
showCompilerId :: Compiler -> String Source #
compilerVersion :: Compiler -> Version Source #
compilerCompatFlavor :: CompilerFlavor -> Compiler -> Bool Source #
Is this compiler compatible with the compiler flavour we're interested in?
For example this checks if the compiler is actually GHC or is another compiler that claims to be compatible with some version of GHC, e.g. GHCJS.
if compilerCompatFlavor GHC compiler then ... else ...
compilerCompatVersion :: CompilerFlavor -> Compiler -> Maybe Version Source #
Is this compiler compatible with the compiler flavour we're interested in, and if so what version does it claim to be compatible with.
For example this checks if the compiler is actually GHC-7.x or is another compiler that claims to be compatible with some GHC-7.x version.
case compilerCompatVersion GHC compiler of Just (Version (7:_)) -> ... _ -> ...
compilerInfo :: Compiler -> CompilerInfo Source #
registrationPackageDB :: PackageDBStack -> PackageDB Source #
Return the package that we should register into. This is the package db at the top of the stack.
absolutePackageDBPaths :: PackageDBStack -> NoCallStackIO PackageDBStack Source #
Make package paths absolute
unsupportedExtensions :: Compiler -> [Extension] -> [Extension] Source #
For the given compiler, return the extensions it does not support.
extensionsToFlags :: Compiler -> [Extension] -> [Flag] Source #
For the given compiler, return the flags for the supported extensions.
parmakeSupported :: Compiler -> Bool Source #
Does this compiler support parallel --make mode?
reexportedModulesSupported :: Compiler -> Bool Source #
Does this compiler support reexported-modules?
renamingPackageFlagsSupported :: Compiler -> Bool Source #
Does this compiler support thinning/renaming on package flags?
unifiedIPIDRequired :: Compiler -> Bool Source #
Does this compiler have unified IPIDs (so no package keys)
packageKeySupported :: Compiler -> Bool Source #
Does this compiler support package keys?
unitIdSupported :: Compiler -> Bool Source #
Does this compiler support unit IDs?
backpackSupported :: Compiler -> Bool Source #
Does this compiler support Backpack?
libraryDynDirSupported :: Compiler -> Bool Source #
Does this compiler support a package database entry with: "dynamic-library-dirs"?
arResponseFilesSupported :: Compiler -> Bool Source #
Does this compiler's "ar" command supports response file arguments (i.e. @file-style arguments).
coverageSupported :: Compiler -> Bool Source #
Does this compiler support Haskell program coverage?
profilingSupported :: Compiler -> Bool Source #
Does this compiler support profiling?
knownProfDetailLevels :: [(String, [String], ProfDetailLevel)] Source #
module Language.Haskell.Extension
Simple interface
defaultMain :: IO () Source #
A simple implementation of main
for a Cabal setup script.
It reads the package description file using IO, and performs the
action specified on the command line.
defaultMainNoRead :: GenericPackageDescription -> IO () Source #
Like defaultMain
, but accepts the package description as input
rather than using IO to read it.
defaultMainArgs :: [String] -> IO () Source #
A version of defaultMain
that is passed the command line
arguments, rather than getting them from the environment.
Customization
Hooks allow authors to add specific functionality before and after a command is run, and also to specify additional preprocessors.
- WARNING: The hooks interface is under rather constant flux as we try to understand users needs. Setup files that depend on this interface may break in future releases.
UserHooks | |
|
defaultMainWithHooks :: UserHooks -> IO () Source #
A customizable version of defaultMain
.
defaultMainWithHooksArgs :: UserHooks -> [String] -> IO () Source #
A customizable version of defaultMain
that also takes the command
line arguments.
defaultMainWithHooksNoRead :: UserHooks -> GenericPackageDescription -> IO () Source #
A customizable version of defaultMainNoRead
.
defaultMainWithHooksNoReadArgs :: UserHooks -> GenericPackageDescription -> [String] -> IO () Source #
A customizable version of defaultMainNoRead
that also takes the
command line arguments.
Since: Cabal-2.2.0.0
Standard sets of hooks
simpleUserHooks :: UserHooks Source #
Hooks that correspond to a plain instantiation of the "simple" build system
autoconfUserHooks :: UserHooks Source #
Basic autoconf UserHooks
:
postConf
runs./configure
, if present.- the pre-hooks
preBuild
,preClean
,preCopy
,preInst
,preReg
andpreUnreg
read additional build information from package.buildinfo
, if present.
Thus configure
can use local system information to generate
package.buildinfo
and possibly other files.
emptyUserHooks :: UserHooks Source #
Empty UserHooks
which do nothing.