Cabal-2.2.0.1: A framework for packaging Haskell software

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

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 GlobalFlags #

Flags that apply at the top level, not to any sub-command.

Instances
Generic GlobalFlags # 
Instance details

Associated Types

type Rep GlobalFlags :: * -> * #

Semigroup GlobalFlags # 
Instance details
Monoid GlobalFlags # 
Instance details
type Rep GlobalFlags # 
Instance details
type Rep GlobalFlags = D1 (MetaData "GlobalFlags" "Distribution.Simple.Setup" "Cabal-2.2.0.1-JS0vobxWxH7sbYKd0omMO" False) (C1 (MetaCons "GlobalFlags" PrefixI True) (S1 (MetaSel (Just "globalVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)) :*: S1 (MetaSel (Just "globalNumericVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))))

data ConfigFlags #

Flags to configure command.

IMPORTANT: every time a new flag is added, filterConfigureFlags should be updated. IMPORTANT: every time a new flag is added, it should be added to the Eq instance

Constructors

ConfigFlags 

Fields

Instances
Eq ConfigFlags # 
Instance details
Read ConfigFlags # 
Instance details
Show ConfigFlags # 
Instance details
Generic ConfigFlags # 
Instance details

Associated Types

type Rep ConfigFlags :: * -> * #

Semigroup ConfigFlags # 
Instance details
Monoid ConfigFlags # 
Instance details
Binary ConfigFlags # 
Instance details
type Rep ConfigFlags # 
Instance details
type Rep ConfigFlags = D1 (MetaData "ConfigFlags" "Distribution.Simple.Setup" "Cabal-2.2.0.1-JS0vobxWxH7sbYKd0omMO" False) (C1 (MetaCons "ConfigFlags" PrefixI True) (((((S1 (MetaSel (Just "configArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]) :*: (S1 (MetaSel (Just "configPrograms_") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last' ProgramDb)) :*: S1 (MetaSel (Just "configProgramPaths") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, FilePath)]))) :*: (S1 (MetaSel (Just "configProgramArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, [String])]) :*: (S1 (MetaSel (Just "configProgramPathExtra") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NubList FilePath)) :*: S1 (MetaSel (Just "configHcFlavor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag CompilerFlavor))))) :*: ((S1 (MetaSel (Just "configHcPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath)) :*: (S1 (MetaSel (Just "configHcPkg") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 (MetaSel (Just "configVanillaLib") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 (MetaSel (Just "configProfLib") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)) :*: S1 (MetaSel (Just "configSharedLib") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 (MetaSel (Just "configStaticLib") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)) :*: S1 (MetaSel (Just "configDynExe") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)))))) :*: (((S1 (MetaSel (Just "configProfExe") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 (MetaSel (Just "configProf") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)) :*: S1 (MetaSel (Just "configProfDetail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag ProfDetailLevel)))) :*: (S1 (MetaSel (Just "configProfLibDetail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag ProfDetailLevel)) :*: (S1 (MetaSel (Just "configConfigureArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]) :*: S1 (MetaSel (Just "configOptimization") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag OptimisationLevel))))) :*: ((S1 (MetaSel (Just "configProgPrefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag PathTemplate)) :*: (S1 (MetaSel (Just "configProgSuffix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag PathTemplate)) :*: S1 (MetaSel (Just "configInstallDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (InstallDirs (Flag PathTemplate))))) :*: ((S1 (MetaSel (Just "configScratchDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 (MetaSel (Just "configExtraLibDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath])) :*: (S1 (MetaSel (Just "configExtraFrameworkDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]) :*: S1 (MetaSel (Just "configExtraIncludeDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath])))))) :*: ((((S1 (MetaSel (Just "configIPID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag String)) :*: (S1 (MetaSel (Just "configCID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag ComponentId)) :*: S1 (MetaSel (Just "configDeterministic") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)))) :*: (S1 (MetaSel (Just "configDistPref") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath)) :*: (S1 (MetaSel (Just "configCabalFilePath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 (MetaSel (Just "configVerbosity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Verbosity))))) :*: ((S1 (MetaSel (Just "configUserInstall") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 (MetaSel (Just "configPackageDBs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Maybe PackageDB]) :*: S1 (MetaSel (Just "configGHCiLib") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 (MetaSel (Just "configSplitSections") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)) :*: S1 (MetaSel (Just "configSplitObjs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 (MetaSel (Just "configStripExes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)) :*: S1 (MetaSel (Just "configStripLibs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)))))) :*: (((S1 (MetaSel (Just "configConstraints") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Dependency]) :*: (S1 (MetaSel (Just "configDependencies") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(PackageName, ComponentId)]) :*: S1 (MetaSel (Just "configInstantiateWith") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(ModuleName, Module)]))) :*: (S1 (MetaSel (Just "configConfigurationsFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FlagAssignment) :*: (S1 (MetaSel (Just "configTests") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)) :*: S1 (MetaSel (Just "configBenchmarks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))))) :*: ((S1 (MetaSel (Just "configCoverage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 (MetaSel (Just "configLibCoverage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)) :*: S1 (MetaSel (Just "configExactConfiguration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 (MetaSel (Just "configFlagError") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag String)) :*: S1 (MetaSel (Just "configRelocatable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 (MetaSel (Just "configDebugInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag DebugInfoLevel)) :*: S1 (MetaSel (Just "configUseResponseFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)))))))))

configPrograms :: WithCallStack (ConfigFlags -> ProgramDb) #

More convenient version of configPrograms. Results in an error if internal invariant is violated.

data CopyFlags #

Flags to copy: (destdir, copy-prefix (backwards compat), verbosity)

Instances
Show CopyFlags # 
Instance details
Generic CopyFlags # 
Instance details

Associated Types

type Rep CopyFlags :: * -> * #

Semigroup CopyFlags # 
Instance details
Monoid CopyFlags # 
Instance details
type Rep CopyFlags # 
Instance details

data InstallFlags #

Flags to install: (package db, verbosity)

Instances
Show InstallFlags # 
Instance details
Generic InstallFlags # 
Instance details

Associated Types

type Rep InstallFlags :: * -> * #

Semigroup InstallFlags # 
Instance details
Monoid InstallFlags # 
Instance details
type Rep InstallFlags # 
Instance details

data DoctestFlags #

Instances
Show DoctestFlags # 
Instance details
Generic DoctestFlags # 
Instance details

Associated Types

type Rep DoctestFlags :: * -> * #

Semigroup DoctestFlags # 
Instance details
Monoid DoctestFlags # 
Instance details
type Rep DoctestFlags # 
Instance details
type Rep DoctestFlags = D1 (MetaData "DoctestFlags" "Distribution.Simple.Setup" "Cabal-2.2.0.1-JS0vobxWxH7sbYKd0omMO" False) (C1 (MetaCons "DoctestFlags" PrefixI True) ((S1 (MetaSel (Just "doctestProgramPaths") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, FilePath)]) :*: S1 (MetaSel (Just "doctestProgramArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, [String])])) :*: (S1 (MetaSel (Just "doctestDistPref") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 (MetaSel (Just "doctestVerbosity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Verbosity)))))

data HaddockTarget #

When we build haddock documentation, there are two cases:

  1. We build haddocks only for the current development version, intended for local use and not for distribution. In this case, we store the generated documentation in distdochtml/name.
  2. We build haddocks for intended for uploading them to hackage. In this case, we need to follow the layout that hackage expects from documentation tarballs, and we might also want to use different flags than for development builds, so in this case we store the generated documentation in distdochtml/id-docs.

Constructors

ForHackage 
ForDevelopment 
Instances
Eq HaddockTarget # 
Instance details
Show HaddockTarget # 
Instance details
Generic HaddockTarget # 
Instance details

Associated Types

type Rep HaddockTarget :: * -> * #

Binary HaddockTarget # 
Instance details
Text HaddockTarget # 
Instance details
type Rep HaddockTarget # 
Instance details
type Rep HaddockTarget = D1 (MetaData "HaddockTarget" "Distribution.Simple.Setup" "Cabal-2.2.0.1-JS0vobxWxH7sbYKd0omMO" False) (C1 (MetaCons "ForHackage" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ForDevelopment" PrefixI False) (U1 :: * -> *))

data HaddockFlags #

Instances
Show HaddockFlags # 
Instance details
Generic HaddockFlags # 
Instance details

Associated Types

type Rep HaddockFlags :: * -> * #

Semigroup HaddockFlags # 
Instance details
Monoid HaddockFlags # 
Instance details
type Rep HaddockFlags # 
Instance details
type Rep HaddockFlags = D1 (MetaData "HaddockFlags" "Distribution.Simple.Setup" "Cabal-2.2.0.1-JS0vobxWxH7sbYKd0omMO" False) (C1 (MetaCons "HaddockFlags" PrefixI True) ((((S1 (MetaSel (Just "haddockProgramPaths") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, FilePath)]) :*: S1 (MetaSel (Just "haddockProgramArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, [String])])) :*: (S1 (MetaSel (Just "haddockHoogle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)) :*: S1 (MetaSel (Just "haddockHtml") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 (MetaSel (Just "haddockHtmlLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag String)) :*: S1 (MetaSel (Just "haddockForHackage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag HaddockTarget))) :*: (S1 (MetaSel (Just "haddockExecutables") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 (MetaSel (Just "haddockTestSuites") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)) :*: S1 (MetaSel (Just "haddockBenchmarks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)))))) :*: (((S1 (MetaSel (Just "haddockForeignLibs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)) :*: S1 (MetaSel (Just "haddockInternal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 (MetaSel (Just "haddockCss") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath)) :*: (S1 (MetaSel (Just "haddockLinkedSource") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)) :*: S1 (MetaSel (Just "haddockHscolourCss") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath))))) :*: ((S1 (MetaSel (Just "haddockContents") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag PathTemplate)) :*: S1 (MetaSel (Just "haddockDistPref") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath))) :*: (S1 (MetaSel (Just "haddockKeepTempFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 (MetaSel (Just "haddockVerbosity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Verbosity)) :*: S1 (MetaSel (Just "haddockCabalFilePath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath))))))))

data HscolourFlags #

Instances
Show HscolourFlags # 
Instance details
Generic HscolourFlags # 
Instance details

Associated Types

type Rep HscolourFlags :: * -> * #

Semigroup HscolourFlags # 
Instance details
Monoid HscolourFlags # 
Instance details
type Rep HscolourFlags # 
Instance details

data BuildFlags #

Instances
Read BuildFlags # 
Instance details
Show BuildFlags # 
Instance details
Generic BuildFlags # 
Instance details

Associated Types

type Rep BuildFlags :: * -> * #

Semigroup BuildFlags # 
Instance details
Monoid BuildFlags # 
Instance details
type Rep BuildFlags # 
Instance details

buildVerbose :: BuildFlags -> Verbosity #

Deprecated: Use buildVerbosity instead

data ReplFlags #

Instances
Show ReplFlags # 
Instance details
Generic ReplFlags # 
Instance details

Associated Types

type Rep ReplFlags :: * -> * #

Semigroup ReplFlags # 
Instance details
Monoid ReplFlags # 
Instance details
type Rep ReplFlags # 
Instance details

data CleanFlags #

Instances
Show CleanFlags # 
Instance details
Generic CleanFlags # 
Instance details

Associated Types

type Rep CleanFlags :: * -> * #

Semigroup CleanFlags # 
Instance details
Monoid CleanFlags # 
Instance details
type Rep CleanFlags # 
Instance details
type Rep CleanFlags = D1 (MetaData "CleanFlags" "Distribution.Simple.Setup" "Cabal-2.2.0.1-JS0vobxWxH7sbYKd0omMO" False) (C1 (MetaCons "CleanFlags" PrefixI True) ((S1 (MetaSel (Just "cleanSaveConf") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)) :*: S1 (MetaSel (Just "cleanDistPref") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath))) :*: (S1 (MetaSel (Just "cleanVerbosity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Verbosity)) :*: S1 (MetaSel (Just "cleanCabalFilePath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath)))))

data RegisterFlags #

Flags to register and unregister: (user package, gen-script, in-place, verbosity)

Instances
Show RegisterFlags # 
Instance details
Generic RegisterFlags # 
Instance details

Associated Types

type Rep RegisterFlags :: * -> * #

Semigroup RegisterFlags # 
Instance details
Monoid RegisterFlags # 
Instance details
type Rep RegisterFlags # 
Instance details

data SDistFlags #

Flags to sdist: (snapshot, verbosity)

Instances
Show SDistFlags # 
Instance details
Generic SDistFlags # 
Instance details

Associated Types

type Rep SDistFlags :: * -> * #

Semigroup SDistFlags # 
Instance details
Monoid SDistFlags # 
Instance details
type Rep SDistFlags # 
Instance details

data TestFlags #

Instances
Generic TestFlags # 
Instance details

Associated Types

type Rep TestFlags :: * -> * #

Semigroup TestFlags # 
Instance details
Monoid TestFlags # 
Instance details
type Rep TestFlags # 
Instance details

data TestShowDetails #

Instances
Bounded TestShowDetails # 
Instance details
Enum TestShowDetails # 
Instance details
Eq TestShowDetails # 
Instance details
Ord TestShowDetails # 
Instance details
Show TestShowDetails # 
Instance details
Semigroup TestShowDetails # 
Instance details
Monoid TestShowDetails # 
Instance details
Pretty TestShowDetails # 
Instance details
Parsec TestShowDetails # 
Instance details
Text TestShowDetails # 
Instance details

data CopyDest #

The location prefix for the copy command.

Constructors

NoCopyDest 
CopyTo FilePath 
CopyToDb FilePath

when using the ${pkgroot} as prefix. The CopyToDb will adjust the paths to be relative to the provided package database when copying / installing.

Instances
Eq CopyDest # 
Instance details
Show CopyDest # 
Instance details
Generic CopyDest # 
Instance details

Associated Types

type Rep CopyDest :: * -> * #

Methods

from :: CopyDest -> Rep CopyDest x #

to :: Rep CopyDest x -> CopyDest #

Binary CopyDest # 
Instance details

Methods

put :: CopyDest -> Put #

get :: Get CopyDest #

putList :: [CopyDest] -> Put #

type Rep CopyDest # 
Instance details
type Rep CopyDest = D1 (MetaData "CopyDest" "Distribution.Simple.InstallDirs" "Cabal-2.2.0.1-JS0vobxWxH7sbYKd0omMO" False) (C1 (MetaCons "NoCopyDest" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "CopyTo" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)) :+: C1 (MetaCons "CopyToDb" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath))))

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

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

programDbOptions :: ProgramDb -> ShowOrParseArgs -> (flags -> [(String, [String])]) -> ([(String, [String])] -> flags -> flags) -> [OptionField flags] #

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

programDbPaths' :: (String -> String) -> ProgramDb -> ShowOrParseArgs -> (flags -> [(String, FilePath)]) -> ([(String, FilePath)] -> flags -> flags) -> [OptionField flags] #

Like programDbPaths, but allows to customise the option name.

programConfigurationOptions :: ProgramDb -> ShowOrParseArgs -> (flags -> [(String, [String])]) -> ([(String, [String])] -> flags -> flags) -> [OptionField flags] #

Deprecated: Use programDbOptions instead

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

programConfigurationPaths' :: (String -> String) -> ProgramDb -> ShowOrParseArgs -> (flags -> [(String, FilePath)]) -> ([(String, FilePath)] -> flags -> flags) -> [OptionField flags] #

Deprecated: Use programDbPaths' instead

Like programDbPaths, but allows to customise the option name.

splitArgs :: String -> [String] #

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"]
splitArgs "\"-DMSGSTR=\\\"foo bar\\\"\" --baz"
  = ["-DMSGSTR=\"foo bar\"","--baz"]

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

data Flag a #

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 # 
Instance details

Methods

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

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

Bounded a => Bounded (Flag a) # 
Instance details

Methods

minBound :: Flag a #

maxBound :: Flag a #

Enum a => Enum (Flag a) # 
Instance details

Methods

succ :: Flag a -> Flag a #

pred :: Flag a -> Flag a #

toEnum :: Int -> Flag a #

fromEnum :: Flag a -> Int #

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

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

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

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

Eq a => Eq (Flag a) # 
Instance details

Methods

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

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

Read a => Read (Flag a) # 
Instance details
Show a => Show (Flag a) # 
Instance details

Methods

showsPrec :: Int -> Flag a -> ShowS #

show :: Flag a -> String #

showList :: [Flag a] -> ShowS #

Generic (Flag a) # 
Instance details

Associated Types

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

Methods

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

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

Semigroup (Flag a) # 
Instance details

Methods

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

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

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

Monoid (Flag a) # 
Instance details

Methods

mempty :: Flag a #

mappend :: Flag a -> Flag a -> Flag a #

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

Binary a => Binary (Flag a) # 
Instance details

Methods

put :: Flag a -> Put #

get :: Get (Flag a) #

putList :: [Flag a] -> Put #

type Rep (Flag a) # 
Instance details
type Rep (Flag a) = D1 (MetaData "Flag" "Distribution.Simple.Setup" "Cabal-2.2.0.1-JS0vobxWxH7sbYKd0omMO" False) (C1 (MetaCons "Flag" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "NoFlag" PrefixI False) (U1 :: * -> *))

toFlag :: a -> Flag a #

fromFlagOrDefault :: a -> Flag a -> a #

flagToList :: Flag a -> [a] #

class BooleanFlag a where #

Types that represent boolean flags.

Minimal complete definition

asBool

Methods

asBool :: a -> Bool #

Instances
BooleanFlag Bool # 
Instance details

Methods

asBool :: Bool -> Bool #

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

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

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

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

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

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