Cabal-3.2.0.0: A framework for packaging Haskell software
CopyrightIsaac Jones 2003-2005
LicenseBSD3
Maintainercabal-devel@haskell.org
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Distribution.Simple

Description

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

Documentation

data AbiTag Source #

Constructors

NoAbiTag 
AbiTag String 

Instances

Instances details
Eq AbiTag Source # 
Instance details

Defined in Distribution.Compiler

Methods

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

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

Read AbiTag Source # 
Instance details

Defined in Distribution.Compiler

Show AbiTag Source # 
Instance details

Defined in Distribution.Compiler

Generic AbiTag Source # 
Instance details

Defined in Distribution.Compiler

Associated Types

type Rep AbiTag :: Type -> Type #

Methods

from :: AbiTag -> Rep AbiTag x #

to :: Rep AbiTag x -> AbiTag #

Binary AbiTag Source # 
Instance details

Defined in Distribution.Compiler

Methods

put :: AbiTag -> Put #

get :: Get AbiTag #

putList :: [AbiTag] -> Put #

Structured AbiTag Source # 
Instance details

Defined in Distribution.Compiler

Pretty AbiTag Source # 
Instance details

Defined in Distribution.Compiler

Parsec AbiTag Source # 
Instance details

Defined in Distribution.Compiler

Methods

parsec :: CabalParsing m => m AbiTag Source #

type Rep AbiTag Source # 
Instance details

Defined in Distribution.Compiler

type Rep AbiTag = D1 ('MetaData "AbiTag" "Distribution.Compiler" "Cabal-3.2.0.0-inplace" '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.

Constructors

CompilerInfo 

Fields

Instances

Instances details
Read CompilerInfo Source # 
Instance details

Defined in Distribution.Compiler

Show CompilerInfo Source # 
Instance details

Defined in Distribution.Compiler

Generic CompilerInfo Source # 
Instance details

Defined in Distribution.Compiler

Associated Types

type Rep CompilerInfo :: Type -> Type #

Binary CompilerInfo Source # 
Instance details

Defined in Distribution.Compiler

type Rep CompilerInfo Source # 
Instance details

Defined in Distribution.Compiler

type Rep CompilerInfo = D1 ('MetaData "CompilerInfo" "Distribution.Compiler" "Cabal-3.2.0.0-inplace" 'False) (C1 ('MetaCons "CompilerInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "compilerInfoId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CompilerId) :*: S1 ('MetaSel ('Just "compilerInfoAbiTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AbiTag)) :*: (S1 ('MetaSel ('Just "compilerInfoCompat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [CompilerId])) :*: (S1 ('MetaSel ('Just "compilerInfoLanguages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Language])) :*: S1 ('MetaSel ('Just "compilerInfoExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Extension]))))))

data CompilerId Source #

Instances

Instances details
Eq CompilerId Source # 
Instance details

Defined in Distribution.Compiler

Ord CompilerId Source # 
Instance details

Defined in Distribution.Compiler

Read CompilerId Source # 
Instance details

Defined in Distribution.Compiler

Show CompilerId Source # 
Instance details

Defined in Distribution.Compiler

Generic CompilerId Source # 
Instance details

Defined in Distribution.Compiler

Associated Types

type Rep CompilerId :: Type -> Type #

Binary CompilerId Source # 
Instance details

Defined in Distribution.Compiler

NFData CompilerId Source # 
Instance details

Defined in Distribution.Compiler

Methods

rnf :: CompilerId -> () #

Structured CompilerId Source # 
Instance details

Defined in Distribution.Compiler

Pretty CompilerId Source # 
Instance details

Defined in Distribution.Compiler

Parsec CompilerId Source # 
Instance details

Defined in Distribution.Compiler

type Rep CompilerId Source # 
Instance details

Defined in Distribution.Compiler

data PerCompilerFlavor v Source #

PerCompilerFlavor carries only info per GHC and GHCJS

Cabal parses only ghc-options and ghcjs-options, others are omitted.

Constructors

PerCompilerFlavor v v 

Instances

Instances details
Eq v => Eq (PerCompilerFlavor v) Source # 
Instance details

Defined in Distribution.Compiler

Data v => Data (PerCompilerFlavor v) Source # 
Instance details

Defined in Distribution.Compiler

Methods

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

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

toConstr :: PerCompilerFlavor v -> Constr #

dataTypeOf :: PerCompilerFlavor v -> DataType #

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

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

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

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

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

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

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

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

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

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

Read v => Read (PerCompilerFlavor v) Source # 
Instance details

Defined in Distribution.Compiler

Show v => Show (PerCompilerFlavor v) Source # 
Instance details

Defined in Distribution.Compiler

Generic (PerCompilerFlavor v) Source # 
Instance details

Defined in Distribution.Compiler

Associated Types

type Rep (PerCompilerFlavor v) :: Type -> Type #

Semigroup a => Semigroup (PerCompilerFlavor a) Source # 
Instance details

Defined in Distribution.Compiler

(Semigroup a, Monoid a) => Monoid (PerCompilerFlavor a) Source # 
Instance details

Defined in Distribution.Compiler

Binary a => Binary (PerCompilerFlavor a) Source # 
Instance details

Defined in Distribution.Compiler

NFData a => NFData (PerCompilerFlavor a) Source # 
Instance details

Defined in Distribution.Compiler

Methods

rnf :: PerCompilerFlavor a -> () #

Structured a => Structured (PerCompilerFlavor a) Source # 
Instance details

Defined in Distribution.Compiler

type Rep (PerCompilerFlavor v) Source # 
Instance details

Defined in Distribution.Compiler

type Rep (PerCompilerFlavor v) = D1 ('MetaData "PerCompilerFlavor" "Distribution.Compiler" "Cabal-3.2.0.0-inplace" 'False) (C1 ('MetaCons "PerCompilerFlavor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 v) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 v)))

data CompilerFlavor Source #

Instances

Instances details
Eq CompilerFlavor Source # 
Instance details

Defined in Distribution.Compiler

Data CompilerFlavor Source # 
Instance details

Defined in Distribution.Compiler

Methods

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

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

toConstr :: CompilerFlavor -> Constr #

dataTypeOf :: CompilerFlavor -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CompilerFlavor Source # 
Instance details

Defined in Distribution.Compiler

Read CompilerFlavor Source # 
Instance details

Defined in Distribution.Compiler

Show CompilerFlavor Source # 
Instance details

Defined in Distribution.Compiler

Generic CompilerFlavor Source # 
Instance details

Defined in Distribution.Compiler

Associated Types

type Rep CompilerFlavor :: Type -> Type #

Binary CompilerFlavor Source # 
Instance details

Defined in Distribution.Compiler

NFData CompilerFlavor Source # 
Instance details

Defined in Distribution.Compiler

Methods

rnf :: CompilerFlavor -> () #

Structured CompilerFlavor Source # 
Instance details

Defined in Distribution.Compiler

Pretty CompilerFlavor Source # 
Instance details

Defined in Distribution.Compiler

Parsec CompilerFlavor Source # 
Instance details

Defined in Distribution.Compiler

Newtype (CompilerFlavor, VersionRange) TestedWith Source # 
Instance details

Defined in Distribution.Parsec.Newtypes

type Rep CompilerFlavor Source # 
Instance details

Defined in Distribution.Compiler

type Rep CompilerFlavor = D1 ('MetaData "CompilerFlavor" "Distribution.Compiler" "Cabal-3.2.0.0-inplace" 'False) (((C1 ('MetaCons "GHC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GHCJS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NHC" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "YHC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Hugs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HBC" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Helium" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "JHC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LHC" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "UHC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Eta" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HaskellSuite" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "OtherCompiler" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))

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.

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.

Instances

Instances details
Eq ProfDetailLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Read ProfDetailLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Show ProfDetailLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Generic ProfDetailLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Associated Types

type Rep ProfDetailLevel :: Type -> Type #

Binary ProfDetailLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Structured ProfDetailLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

type Rep ProfDetailLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

type Rep ProfDetailLevel = D1 ('MetaData "ProfDetailLevel" "Distribution.Simple.Compiler" "Cabal-3.2.0.0-inplace" 'False) ((C1 ('MetaCons "ProfDetailNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ProfDetailDefault" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ProfDetailExportedFunctions" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ProfDetailToplevelFunctions" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ProfDetailAllFunctions" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ProfDetailOther" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))

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

Instances details
Bounded DebugInfoLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Enum DebugInfoLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Eq DebugInfoLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Read DebugInfoLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Show DebugInfoLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Generic DebugInfoLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Associated Types

type Rep DebugInfoLevel :: Type -> Type #

Binary DebugInfoLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Structured DebugInfoLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

type Rep DebugInfoLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

type Rep DebugInfoLevel = D1 ('MetaData "DebugInfoLevel" "Distribution.Simple.Compiler" "Cabal-3.2.0.0-inplace" 'False) ((C1 ('MetaCons "NoDebugInfo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MinimalDebugInfo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NormalDebugInfo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MaximalDebugInfo" 'PrefixI 'False) (U1 :: Type -> Type)))

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

Instances details
Bounded OptimisationLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Enum OptimisationLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Eq OptimisationLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Read OptimisationLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Show OptimisationLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Generic OptimisationLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Associated Types

type Rep OptimisationLevel :: Type -> Type #

Binary OptimisationLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Structured OptimisationLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

type Rep OptimisationLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

type Rep OptimisationLevel = D1 ('MetaData "OptimisationLevel" "Distribution.Simple.Compiler" "Cabal-3.2.0.0-inplace" 'False) (C1 ('MetaCons "NoOptimisation" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NormalOptimisation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MaximumOptimisation" 'PrefixI 'False) (U1 :: Type -> Type)))

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.

data PackageDB Source #

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

Instances details
Eq PackageDB Source # 
Instance details

Defined in Distribution.Simple.Compiler

Ord PackageDB Source # 
Instance details

Defined in Distribution.Simple.Compiler

Read PackageDB Source # 
Instance details

Defined in Distribution.Simple.Compiler

Show PackageDB Source # 
Instance details

Defined in Distribution.Simple.Compiler

Generic PackageDB Source # 
Instance details

Defined in Distribution.Simple.Compiler

Associated Types

type Rep PackageDB :: Type -> Type #

Binary PackageDB Source # 
Instance details

Defined in Distribution.Simple.Compiler

Structured PackageDB Source # 
Instance details

Defined in Distribution.Simple.Compiler

type Rep PackageDB Source # 
Instance details

Defined in Distribution.Simple.Compiler

type Rep PackageDB = D1 ('MetaData "PackageDB" "Distribution.Simple.Compiler" "Cabal-3.2.0.0-inplace" '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))))

data Compiler Source #

Constructors

Compiler 

Fields

Instances

Instances details
Eq Compiler Source # 
Instance details

Defined in Distribution.Simple.Compiler

Read Compiler Source # 
Instance details

Defined in Distribution.Simple.Compiler

Show Compiler Source # 
Instance details

Defined in Distribution.Simple.Compiler

Generic Compiler Source # 
Instance details

Defined in Distribution.Simple.Compiler

Associated Types

type Rep Compiler :: Type -> Type #

Methods

from :: Compiler -> Rep Compiler x #

to :: Rep Compiler x -> Compiler #

Binary Compiler Source # 
Instance details

Defined in Distribution.Simple.Compiler

Methods

put :: Compiler -> Put #

get :: Get Compiler #

putList :: [Compiler] -> Put #

Structured Compiler Source # 
Instance details

Defined in Distribution.Simple.Compiler

type Rep Compiler Source # 
Instance details

Defined in Distribution.Simple.Compiler

type Rep Compiler = D1 ('MetaData "Compiler" "Distribution.Simple.Compiler" "Cabal-3.2.0.0-inplace" 'False) (C1 ('MetaCons "Compiler" 'PrefixI 'True) ((S1 ('MetaSel ('Just "compilerId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CompilerId) :*: (S1 ('MetaSel ('Just "compilerAbiTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AbiTag) :*: S1 ('MetaSel ('Just "compilerCompat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [CompilerId]))) :*: (S1 ('MetaSel ('Just "compilerLanguages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Language, Flag)]) :*: (S1 ('MetaSel ('Just "compilerExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Extension, Maybe Flag)]) :*: S1 ('MetaSel ('Just "compilerProperties") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map String String))))))

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:_)) -> ...
  _                    -> ...

registrationPackageDB :: PackageDBStack -> PackageDB Source #

Return the package that we should register into. This is the package db at the top of the stack.

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?

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

data UserHooks Source #

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.

Constructors

UserHooks 

Fields

type Args = [String] Source #

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.

defaultMainWithHooksNoReadArgs :: UserHooks -> GenericPackageDescription -> [String] -> IO () Source #

A customizable version of defaultMainNoRead that also takes the command line arguments.

Since: 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:

Thus configure can use local system information to generate package.buildinfo and possibly other files.

emptyUserHooks :: UserHooks Source #

Empty UserHooks which do nothing.