Cabal-1.23.1.0: A framework for packaging Haskell software

CopyrightIsaac Jones 2003-2004 Duncan Coutts 2007
LicenseBSD3
Maintainercabal-devel@haskell.org
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Distribution.Simple.Setup

Description

This is a big module, but not very complicated. The code is very regular and repetitive. It defines the command line interface for all the Cabal commands. For each command (like configure, build etc) it defines a type that holds all the flags, the default set of flags and a CommandUI that maps command line flags to and from the corresponding flags type.

All the flags types are instances of Monoid, see http://www.haskell.org/pipermail/cabal-devel/2007-December/001509.html for an explanation.

The types defined here get used in the front end and especially in cabal-install which has to do quite a bit of manipulating sets of command line flags.

This is actually relatively nice, it works quite well. The main change it needs is to unify it with the code for managing sets of fields that can be read and written from files. This would allow us to save configure flags in config files.

Synopsis

Documentation

data ConfigFlags Source

Flags to configure command.

IMPORTANT: every time a new flag is added, filterConfigureFlags should be updated.

Constructors

ConfigFlags 

Fields

Instances

Read ConfigFlags 
Show ConfigFlags 
Generic ConfigFlags 

Associated Types

type Rep ConfigFlags :: * -> * Source

Semigroup ConfigFlags 
Monoid ConfigFlags 
Binary ConfigFlags 
type Rep ConfigFlags = D1 (MetaData "ConfigFlags" "Distribution.Simple.Setup" "Cabal-1.23.1.0" False) (C1 (MetaCons "ConfigFlags" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "configPrograms") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProgramConfiguration)) (S1 (MetaSel (Just Symbol "configProgramPaths") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, FilePath)]))) ((:*:) (S1 (MetaSel (Just Symbol "configProgramArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, [String])])) ((:*:) (S1 (MetaSel (Just Symbol "configProgramPathExtra") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NubList FilePath))) (S1 (MetaSel (Just Symbol "configHcFlavor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag CompilerFlavor)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "configHcPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath))) (S1 (MetaSel (Just Symbol "configHcPkg") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath)))) ((:*:) (S1 (MetaSel (Just Symbol "configVanillaLib") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) ((:*:) (S1 (MetaSel (Just Symbol "configProfLib") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) (S1 (MetaSel (Just Symbol "configSharedLib") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "configDynExe") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) (S1 (MetaSel (Just Symbol "configProfExe") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "configProf") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) ((:*:) (S1 (MetaSel (Just Symbol "configProfDetail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag ProfDetailLevel))) (S1 (MetaSel (Just Symbol "configProfLibDetail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag ProfDetailLevel)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "configConfigureArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])) ((:*:) (S1 (MetaSel (Just Symbol "configOptimization") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag OptimisationLevel))) (S1 (MetaSel (Just Symbol "configProgPrefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag PathTemplate))))) ((:*:) (S1 (MetaSel (Just Symbol "configProgSuffix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag PathTemplate))) ((:*:) (S1 (MetaSel (Just Symbol "configInstallDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (InstallDirs (Flag PathTemplate)))) (S1 (MetaSel (Just Symbol "configScratchDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath)))))))) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "configExtraLibDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath])) (S1 (MetaSel (Just Symbol "configExtraIncludeDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]))) ((:*:) (S1 (MetaSel (Just Symbol "configIPID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag String))) ((:*:) (S1 (MetaSel (Just Symbol "configDistPref") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath))) (S1 (MetaSel (Just Symbol "configVerbosity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Verbosity)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "configUserInstall") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) ((:*:) (S1 (MetaSel (Just Symbol "configPackageDBs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Maybe PackageDB])) (S1 (MetaSel (Just Symbol "configGHCiLib") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))))) ((:*:) (S1 (MetaSel (Just Symbol "configSplitObjs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) ((:*:) (S1 (MetaSel (Just Symbol "configStripExes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) (S1 (MetaSel (Just Symbol "configStripLibs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "configConstraints") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Dependency])) (S1 (MetaSel (Just Symbol "configDependencies") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(PackageName, UnitId)]))) ((:*:) (S1 (MetaSel (Just Symbol "configConfigurationsFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FlagAssignment)) ((:*:) (S1 (MetaSel (Just Symbol "configTests") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) (S1 (MetaSel (Just Symbol "configBenchmarks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "configCoverage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) ((:*:) (S1 (MetaSel (Just Symbol "configLibCoverage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) (S1 (MetaSel (Just Symbol "configExactConfiguration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))))) ((:*:) (S1 (MetaSel (Just Symbol "configFlagError") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag String))) ((:*:) (S1 (MetaSel (Just Symbol "configRelocatable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) (S1 (MetaSel (Just Symbol "configDebugInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag DebugInfoLevel)))))))))) 

buildVerbose :: BuildFlags -> Verbosity Source

Deprecated: Use buildVerbosity instead

data TestShowDetails Source

Instances

Bounded TestShowDetails 
Enum TestShowDetails 
Eq TestShowDetails 
Ord TestShowDetails 
Show TestShowDetails 
Semigroup TestShowDetails 
Monoid TestShowDetails 
Text TestShowDetails 

data CopyDest Source

The location prefix for the copy command.

Constructors

NoCopyDest 
CopyTo FilePath 

configureArgs :: Bool -> ConfigFlags -> [String] Source

Arguments to pass to a configure script, e.g. generated by autoconf.

programConfigurationOptions :: ProgramConfiguration -> ShowOrParseArgs -> (flags -> [(String, [String])]) -> ([(String, [String])] -> flags -> flags) -> [OptionField flags] Source

For each known program PROG in progConf, produce a PROG-options OptionField.

programConfigurationPaths' :: (String -> String) -> ProgramConfiguration -> ShowOrParseArgs -> (flags -> [(String, FilePath)]) -> ([(String, FilePath)] -> flags -> flags) -> [OptionField flags] Source

Like programConfigurationPaths, but allows to customise the option name.

splitArgs :: String -> [String] Source

Helper function to split a string into a list of arguments. It's supposed to handle quoted things sensibly, eg:

splitArgs "--foo=\"C:\Program Files\Bar\" --baz"
  = ["--foo=C:\Program Files\Bar", "--baz"]

optionDistPref :: (flags -> Flag FilePath) -> (Flag FilePath -> flags -> flags) -> ShowOrParseArgs -> OptionField flags Source

data Flag a Source

All flags are monoids, they come in two flavours:

  1. list flags eg
--ghc-option=foo --ghc-option=bar

gives us all the values ["foo", "bar"]

  1. singular value flags, eg:
--enable-foo --disable-foo

gives us Just False So this Flag type is for the latter singular kind of flag. Its monoid instance gives us the behaviour where it starts out as NoFlag and later flags override earlier ones.

Constructors

Flag a 
NoFlag 

Instances

Functor Flag 

Methods

fmap :: (a -> b) -> Flag a -> Flag b Source

(<$) :: a -> Flag b -> Flag a Source

Bounded a => Bounded (Flag a) 
Enum a => Enum (Flag a) 

Methods

succ :: Flag a -> Flag a Source

pred :: Flag a -> Flag a Source

toEnum :: Int -> Flag a Source

fromEnum :: Flag a -> Int Source

enumFrom :: Flag a -> [Flag a] Source

enumFromThen :: Flag a -> Flag a -> [Flag a] Source

enumFromTo :: Flag a -> Flag a -> [Flag a] Source

enumFromThenTo :: Flag a -> Flag a -> Flag a -> [Flag a] Source

Eq a => Eq (Flag a) 

Methods

(==) :: Flag a -> Flag a -> Bool

(/=) :: Flag a -> Flag a -> Bool

Read a => Read (Flag a) 
Show a => Show (Flag a) 
Generic (Flag a) 

Associated Types

type Rep (Flag a) :: * -> * Source

Methods

from :: Flag a -> Rep (Flag a) x Source

to :: Rep (Flag a) x -> Flag a Source

Semigroup (Flag a) 

Methods

(<>) :: Flag a -> Flag a -> Flag a Source

sconcat :: NonEmpty (Flag a) -> Flag a Source

stimes :: Integral b => b -> Flag a -> Flag a Source

Monoid (Flag a) 

Methods

mempty :: Flag a Source

mappend :: Flag a -> Flag a -> Flag a Source

mconcat :: [Flag a] -> Flag a Source

Binary a => Binary (Flag a) 

Methods

put :: Flag a -> Put Source

get :: Get (Flag a) Source

type Rep (Flag a) = D1 (MetaData "Flag" "Distribution.Simple.Setup" "Cabal-1.23.1.0" False) ((:+:) (C1 (MetaCons "Flag" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))) (C1 (MetaCons "NoFlag" PrefixI False) U1)) 

toFlag :: a -> Flag a Source

fromFlag :: Flag a -> a Source

flagToList :: Flag a -> [a] Source

boolOpt :: SFlags -> SFlags -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a Source

boolOpt' :: OptFlags -> OptFlags -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a Source

trueArg :: MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a Source

falseArg :: MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a Source

optionVerbosity :: (flags -> Flag Verbosity) -> (Flag Verbosity -> flags -> flags) -> OptionField flags Source

optionNumJobs :: (flags -> Flag (Maybe Int)) -> (Flag (Maybe Int) -> flags -> flags) -> OptionField flags Source