| Copyright | Isaac Jones 2003-2004 Duncan Coutts 2007 | 
|---|---|
| License | BSD3 | 
| Maintainer | [email protected] | 
| Portability | portable | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Distribution.Simple.Setup
Description
This module 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
- data GlobalFlags = GlobalFlags {- globalVersion :: Flag Bool
- globalNumericVersion :: Flag Bool
- globalWorkingDir :: Flag (SymbolicPath CWD (Dir Pkg))
 
- emptyGlobalFlags :: GlobalFlags
- defaultGlobalFlags :: GlobalFlags
- globalCommand :: [Command action] -> CommandUI GlobalFlags
- data CommonSetupFlags = CommonSetupFlags {- setupVerbosity :: !(Flag Verbosity)
- setupWorkingDir :: !(Flag (SymbolicPath CWD (Dir Pkg)))
- setupDistPref :: !(Flag (SymbolicPath Pkg (Dir Dist)))
- setupCabalFilePath :: !(Flag (SymbolicPath Pkg File))
- setupTargets :: [String]
 
- defaultCommonSetupFlags :: CommonSetupFlags
- data ConfigFlags where- ConfigFlags { - configCommonFlags :: !CommonSetupFlags
- configPrograms_ :: Option' (Last' ProgramDb)
- configProgramPaths :: [(String, FilePath)]
- configProgramArgs :: [(String, [String])]
- configProgramPathExtra :: NubList FilePath
- configHcFlavor :: Flag CompilerFlavor
- configHcPath :: Flag FilePath
- configHcPkg :: Flag FilePath
- configVanillaLib :: Flag Bool
- configProfLib :: Flag Bool
- configSharedLib :: Flag Bool
- configStaticLib :: Flag Bool
- configDynExe :: Flag Bool
- configFullyStaticExe :: Flag Bool
- configProfExe :: Flag Bool
- configProf :: Flag Bool
- configProfShared :: Flag Bool
- configProfDetail :: Flag ProfDetailLevel
- configProfLibDetail :: Flag ProfDetailLevel
- configConfigureArgs :: [String]
- configOptimization :: Flag OptimisationLevel
- configProgPrefix :: Flag PathTemplate
- configProgSuffix :: Flag PathTemplate
- configInstallDirs :: InstallDirs (Flag PathTemplate)
- configScratchDir :: Flag FilePath
- configExtraLibDirs :: [SymbolicPath Pkg (Dir Lib)]
- configExtraLibDirsStatic :: [SymbolicPath Pkg (Dir Lib)]
- configExtraFrameworkDirs :: [SymbolicPath Pkg (Dir Framework)]
- configExtraIncludeDirs :: [SymbolicPath Pkg (Dir Include)]
- configIPID :: Flag String
- configCID :: Flag ComponentId
- configDeterministic :: Flag Bool
- configUserInstall :: Flag Bool
- configPackageDBs :: [Maybe PackageDB]
- configGHCiLib :: Flag Bool
- configSplitSections :: Flag Bool
- configSplitObjs :: Flag Bool
- configStripExes :: Flag Bool
- configStripLibs :: Flag Bool
- configConstraints :: [PackageVersionConstraint]
- configDependencies :: [GivenComponent]
- configPromisedDependencies :: [PromisedComponent]
- configInstantiateWith :: [(ModuleName, Module)]
- configConfigurationsFlags :: FlagAssignment
- configTests :: Flag Bool
- configBenchmarks :: Flag Bool
- configCoverage :: Flag Bool
- configLibCoverage :: Flag Bool
- configExactConfiguration :: Flag Bool
- configFlagError :: Flag String
- configRelocatable :: Flag Bool
- configDebugInfo :: Flag DebugInfoLevel
- configDumpBuildInfo :: Flag DumpBuildInfo
- configUseResponseFiles :: Flag Bool
- configAllowDependingOnPrivateLibs :: Flag Bool
- configCoverageFor :: Flag [UnitId]
- configIgnoreBuildTools :: Flag Bool
 
- pattern ConfigCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> ConfigFlags
 
- ConfigFlags { 
- emptyConfigFlags :: ConfigFlags
- defaultConfigFlags :: ProgramDb -> ConfigFlags
- configureCommand :: ProgramDb -> CommandUI ConfigFlags
- configPrograms :: WithCallStack (ConfigFlags -> ProgramDb)
- readPackageDb :: String -> Maybe PackageDB
- readPackageDbList :: String -> [Maybe PackageDB]
- showPackageDb :: Maybe PackageDB -> String
- showPackageDbList :: [Maybe PackageDB] -> [String]
- data CopyFlags where
- emptyCopyFlags :: CopyFlags
- defaultCopyFlags :: CopyFlags
- copyCommand :: CommandUI CopyFlags
- data InstallFlags where- InstallFlags { }
- pattern InstallCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> InstallFlags
 
- emptyInstallFlags :: InstallFlags
- defaultInstallFlags :: InstallFlags
- installCommand :: CommandUI InstallFlags
- data HaddockTarget
- data HaddockFlags where- HaddockFlags { - haddockCommonFlags :: !CommonSetupFlags
- haddockProgramPaths :: [(String, FilePath)]
- haddockProgramArgs :: [(String, [String])]
- haddockHoogle :: Flag Bool
- haddockHtml :: Flag Bool
- haddockHtmlLocation :: Flag String
- haddockForHackage :: Flag HaddockTarget
- haddockExecutables :: Flag Bool
- haddockTestSuites :: Flag Bool
- haddockBenchmarks :: Flag Bool
- haddockForeignLibs :: Flag Bool
- haddockInternal :: Flag Bool
- haddockCss :: Flag FilePath
- haddockLinkedSource :: Flag Bool
- haddockQuickJump :: Flag Bool
- haddockHscolourCss :: Flag FilePath
- haddockContents :: Flag PathTemplate
- haddockIndex :: Flag PathTemplate
- haddockKeepTempFiles :: Flag Bool
- haddockBaseUrl :: Flag String
- haddockResourcesDir :: Flag String
- haddockOutputDir :: Flag FilePath
- haddockUseUnicode :: Flag Bool
 
- pattern HaddockCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> HaddockFlags
 
- HaddockFlags { 
- emptyHaddockFlags :: HaddockFlags
- defaultHaddockFlags :: HaddockFlags
- haddockCommand :: CommandUI HaddockFlags
- data Visibility
- data HaddockProjectFlags = HaddockProjectFlags {- haddockProjectHackage :: Flag Bool
- haddockProjectDir :: Flag String
- haddockProjectPrologue :: Flag String
- haddockProjectInterfaces :: Flag [(FilePath, Maybe FilePath, Maybe FilePath, Visibility)]
- haddockProjectProgramPaths :: [(String, FilePath)]
- haddockProjectProgramArgs :: [(String, [String])]
- haddockProjectHoogle :: Flag Bool
- haddockProjectHtmlLocation :: Flag String
- haddockProjectExecutables :: Flag Bool
- haddockProjectTestSuites :: Flag Bool
- haddockProjectBenchmarks :: Flag Bool
- haddockProjectForeignLibs :: Flag Bool
- haddockProjectInternal :: Flag Bool
- haddockProjectCss :: Flag FilePath
- haddockProjectHscolourCss :: Flag FilePath
- haddockProjectKeepTempFiles :: Flag Bool
- haddockProjectVerbosity :: Flag Verbosity
- haddockProjectResourcesDir :: Flag String
- haddockProjectUseUnicode :: Flag Bool
 
- emptyHaddockProjectFlags :: HaddockProjectFlags
- defaultHaddockProjectFlags :: HaddockProjectFlags
- haddockProjectCommand :: CommandUI HaddockProjectFlags
- data HscolourFlags where- HscolourFlags { }
- pattern HscolourCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> HscolourFlags
 
- emptyHscolourFlags :: HscolourFlags
- defaultHscolourFlags :: HscolourFlags
- hscolourCommand :: CommandUI HscolourFlags
- data BuildFlags where- BuildFlags { - buildCommonFlags :: !CommonSetupFlags
- buildProgramPaths :: [(String, FilePath)]
- buildProgramArgs :: [(String, [String])]
- buildNumJobs :: Flag (Maybe Int)
- buildUseSemaphore :: Flag String
 
- pattern BuildCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> BuildFlags
 
- BuildFlags { 
- emptyBuildFlags :: BuildFlags
- defaultBuildFlags :: BuildFlags
- buildCommand :: ProgramDb -> CommandUI BuildFlags
- data DumpBuildInfo
- data ReplFlags where- ReplFlags { - replCommonFlags :: !CommonSetupFlags
- replProgramPaths :: [(String, FilePath)]
- replProgramArgs :: [(String, [String])]
- replReload :: Flag Bool
- replReplOptions :: ReplOptions
 
- pattern ReplCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> ReplFlags
 
- ReplFlags { 
- defaultReplFlags :: ReplFlags
- replCommand :: ProgramDb -> CommandUI ReplFlags
- data ReplOptions = ReplOptions {}
- data CleanFlags where- CleanFlags { }
- pattern CleanCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> CleanFlags
 
- emptyCleanFlags :: CleanFlags
- defaultCleanFlags :: CleanFlags
- cleanCommand :: CommandUI CleanFlags
- data RegisterFlags where- RegisterFlags { - registerCommonFlags :: !CommonSetupFlags
- regPackageDB :: Flag PackageDB
- regGenScript :: Flag Bool
- regGenPkgConf :: Flag (Maybe (SymbolicPath Pkg (Dir PkgConf)))
- regInPlace :: Flag Bool
- regPrintId :: Flag Bool
 
- pattern RegisterCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> RegisterFlags
 
- RegisterFlags { 
- emptyRegisterFlags :: RegisterFlags
- defaultRegisterFlags :: RegisterFlags
- registerCommand :: CommandUI RegisterFlags
- unregisterCommand :: CommandUI RegisterFlags
- data SDistFlags where- SDistFlags { }
- pattern SDistCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> SDistFlags
 
- emptySDistFlags :: SDistFlags
- defaultSDistFlags :: SDistFlags
- sdistCommand :: CommandUI SDistFlags
- data TestFlags where
- emptyTestFlags :: TestFlags
- defaultTestFlags :: TestFlags
- testCommand :: CommandUI TestFlags
- data TestShowDetails
- data BenchmarkFlags where- BenchmarkFlags { }
- pattern BenchmarkCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> BenchmarkFlags
 
- emptyBenchmarkFlags :: BenchmarkFlags
- defaultBenchmarkFlags :: BenchmarkFlags
- benchmarkCommand :: CommandUI BenchmarkFlags
- data CopyDest
- configureArgs :: Bool -> ConfigFlags -> [String]
- configureOptions :: ShowOrParseArgs -> [OptionField ConfigFlags]
- configureCCompiler :: Verbosity -> ProgramDb -> IO (FilePath, [String])
- configureLinker :: Verbosity -> ProgramDb -> IO (FilePath, [String])
- buildOptions :: ProgramDb -> ShowOrParseArgs -> [OptionField BuildFlags]
- haddockOptions :: ShowOrParseArgs -> [OptionField HaddockFlags]
- haddockProjectOptions :: ShowOrParseArgs -> [OptionField HaddockProjectFlags]
- installDirsOptions :: [OptionField (InstallDirs (Flag PathTemplate))]
- testOptions' :: ShowOrParseArgs -> [OptionField TestFlags]
- benchmarkOptions' :: ShowOrParseArgs -> [OptionField BenchmarkFlags]
- programDbOptions :: ProgramDb -> ShowOrParseArgs -> (flags -> [(String, [String])]) -> ([(String, [String])] -> flags -> flags) -> [OptionField flags]
- programDbPaths' :: (String -> String) -> ProgramDb -> ShowOrParseArgs -> (flags -> [(String, FilePath)]) -> ([(String, FilePath)] -> flags -> flags) -> [OptionField flags]
- programFlagsDescription :: ProgramDb -> String
- replOptions :: ShowOrParseArgs -> [OptionField ReplOptions]
- splitArgs :: String -> [String]
- defaultDistPref :: SymbolicPath Pkg (Dir Dist)
- optionDistPref :: (flags -> Flag (SymbolicPath Pkg (Dir Dist))) -> (Flag (SymbolicPath Pkg (Dir Dist)) -> flags -> flags) -> ShowOrParseArgs -> OptionField flags
- data Flag a
- toFlag :: a -> Flag a
- fromFlag :: WithCallStack (Flag a -> a)
- fromFlagOrDefault :: a -> Flag a -> a
- flagToMaybe :: Flag a -> Maybe a
- flagToList :: Flag a -> [a]
- maybeToFlag :: Maybe a -> Flag a
- class BooleanFlag a where
- 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
- data BuildingWhat
- buildingWhatCommonFlags :: BuildingWhat -> CommonSetupFlags
- buildingWhatVerbosity :: BuildingWhat -> Verbosity
- buildingWhatWorkingDir :: BuildingWhat -> Maybe (SymbolicPath CWD (Dir Pkg))
- buildingWhatDistPref :: BuildingWhat -> SymbolicPath Pkg (Dir Dist)
Documentation
data GlobalFlags Source #
Flags that apply at the top level, not to any sub-command.
Constructors
| GlobalFlags | |
| Fields 
 | |
Instances
globalCommand :: [Command action] -> CommandUI GlobalFlags Source #
data CommonSetupFlags Source #
A datatype that stores common flags for different invocations
 of a Setup executable, e.g. configure, build, install.
Constructors
| CommonSetupFlags | |
| Fields 
 | |
Instances
data ConfigFlags Source #
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 
 | |
Bundled Patterns
| pattern ConfigCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> ConfigFlags | 
Instances
configPrograms :: WithCallStack (ConfigFlags -> ProgramDb) Source #
More convenient version of configPrograms. Results in an
 error if internal invariant is violated.
Flags to copy: (destdir, copy-prefix (backwards compat), verbosity)
Constructors
| CopyFlags | |
| Fields | |
Bundled Patterns
| pattern CopyCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> CopyFlags | 
Instances
| Structured CopyFlags Source # | |
| Defined in Distribution.Simple.Setup.Copy | |
| Monoid CopyFlags Source # | |
| Semigroup CopyFlags Source # | |
| Generic CopyFlags Source # | |
| Show CopyFlags Source # | |
| Binary CopyFlags Source # | |
| type Rep CopyFlags Source # | |
| Defined in Distribution.Simple.Setup.Copy type Rep CopyFlags = D1 ('MetaData "CopyFlags" "Distribution.Simple.Setup.Copy" "Cabal-3.14.0.0-inplace" 'False) (C1 ('MetaCons "CopyFlags" 'PrefixI 'True) (S1 ('MetaSel ('Just "copyCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: S1 ('MetaSel ('Just "copyDest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag CopyDest)))) | |
data InstallFlags Source #
Flags to install: (package db, verbosity)
Constructors
| InstallFlags | |
| Fields | |
Bundled Patterns
| pattern InstallCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> InstallFlags | 
Instances
data HaddockTarget Source #
When we build haddock documentation, there are two cases:
- 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.
- 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
| Parsec HaddockTarget Source # | |
| Defined in Distribution.Simple.Setup.Haddock Methods parsec :: CabalParsing m => m HaddockTarget | |
| Pretty HaddockTarget Source # | |
| Defined in Distribution.Simple.Setup.Haddock | |
| Structured HaddockTarget Source # | |
| Defined in Distribution.Simple.Setup.Haddock | |
| Generic HaddockTarget Source # | |
| Defined in Distribution.Simple.Setup.Haddock Associated Types type Rep HaddockTarget :: Type -> Type # | |
| Show HaddockTarget Source # | |
| Defined in Distribution.Simple.Setup.Haddock Methods showsPrec :: Int -> HaddockTarget -> ShowS # show :: HaddockTarget -> String # showList :: [HaddockTarget] -> ShowS # | |
| Binary HaddockTarget Source # | |
| Defined in Distribution.Simple.Setup.Haddock | |
| Eq HaddockTarget Source # | |
| Defined in Distribution.Simple.Setup.Haddock Methods (==) :: HaddockTarget -> HaddockTarget -> Bool # (/=) :: HaddockTarget -> HaddockTarget -> Bool # | |
| type Rep HaddockTarget Source # | |
| Defined in Distribution.Simple.Setup.Haddock | |
data HaddockFlags Source #
Constructors
Bundled Patterns
| pattern HaddockCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> HaddockFlags | 
Instances
data Visibility Source #
Governs whether modules from a given interface should be visible or
 hidden in the Haddock generated content page.  We don't expose this
 functionality to the user, but simply use Visible for only local packages.
 Visibility of modules is available since haddock-2.26.1.
Instances
| Show Visibility Source # | |
| Defined in Distribution.Simple.Setup.Haddock Methods showsPrec :: Int -> Visibility -> ShowS # show :: Visibility -> String # showList :: [Visibility] -> ShowS # | |
| Eq Visibility Source # | |
| Defined in Distribution.Simple.Setup.Haddock | |
data HaddockProjectFlags Source #
Constructors
Instances
data HscolourFlags Source #
Constructors
| HscolourFlags | |
| Fields | |
Bundled Patterns
| pattern HscolourCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> HscolourFlags | 
Instances
data BuildFlags Source #
Constructors
| BuildFlags | |
| Fields 
 | |
Bundled Patterns
| pattern BuildCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> BuildFlags | 
Instances
data DumpBuildInfo Source #
Constructors
| NoDumpBuildInfo | |
| DumpBuildInfo | 
Instances
Constructors
| ReplFlags | |
| Fields 
 | |
Bundled Patterns
| pattern ReplCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> ReplFlags | 
Instances
data ReplOptions Source #
Constructors
| ReplOptions | |
| Fields | |
Instances
data CleanFlags Source #
Constructors
| CleanFlags | |
| Fields | |
Bundled Patterns
| pattern CleanCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> CleanFlags | 
Instances
data RegisterFlags Source #
Flags to register and unregister: (user package, gen-script,
 in-place, verbosity)
Constructors
| RegisterFlags | |
| Fields 
 | |
Bundled Patterns
| pattern RegisterCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> RegisterFlags | 
Instances
data SDistFlags Source #
Flags to sdist: (snapshot, verbosity)
Constructors
| SDistFlags | |
| Fields | |
Bundled Patterns
| pattern SDistCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> SDistFlags | 
Instances
Constructors
| TestFlags | |
Bundled Patterns
| pattern TestCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> TestFlags | 
Instances
data TestShowDetails Source #
Instances
data BenchmarkFlags Source #
Constructors
| BenchmarkFlags | |
| Fields | |
Bundled Patterns
| pattern BenchmarkCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg (Dir Dist)) -> Flag (SymbolicPath CWD (Dir Pkg)) -> Flag (SymbolicPath Pkg File) -> [String] -> BenchmarkFlags | 
Instances
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
| Structured CopyDest Source # | |
| Defined in Distribution.Simple.InstallDirs | |
| Generic CopyDest Source # | |
| Show CopyDest Source # | |
| Binary CopyDest Source # | |
| Eq CopyDest Source # | |
| type Rep CopyDest Source # | |
| Defined in Distribution.Simple.InstallDirs type Rep CopyDest = D1 ('MetaData "CopyDest" "Distribution.Simple.InstallDirs" "Cabal-3.14.0.0-inplace" 'False) (C1 ('MetaCons "NoCopyDest" 'PrefixI 'False) (U1 :: Type -> Type) :+: (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] Source #
Arguments to pass to a configure script, e.g. generated by
 autoconf.
buildOptions :: ProgramDb -> ShowOrParseArgs -> [OptionField BuildFlags] Source #
programDbOptions :: ProgramDb -> ShowOrParseArgs -> (flags -> [(String, [String])]) -> ([(String, [String])] -> flags -> flags) -> [OptionField flags] Source #
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] Source #
Like programDbPaths, 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"]
splitArgs "\"-DMSGSTR=\\\"foo bar\\\"\" --baz" = ["-DMSGSTR=\"foo bar\"","--baz"]
defaultDistPref :: SymbolicPath Pkg (Dir Dist) Source #
optionDistPref :: (flags -> Flag (SymbolicPath Pkg (Dir Dist))) -> (Flag (SymbolicPath Pkg (Dir Dist)) -> flags -> flags) -> ShowOrParseArgs -> OptionField flags Source #
All flags are monoids, they come in two flavours:
- list flags eg
--ghc-option=foo --ghc-option=bar
gives us all the values ["foo", "bar"]
- 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.
Isomorphic to Maybe a.
Instances
| Foldable Flag Source # | |
| Defined in Distribution.Simple.Flag Methods fold :: Monoid m => Flag m -> m # foldMap :: Monoid m => (a -> m) -> Flag a -> m # foldMap' :: Monoid m => (a -> m) -> Flag a -> m # foldr :: (a -> b -> b) -> b -> Flag a -> b # foldr' :: (a -> b -> b) -> b -> Flag a -> b # foldl :: (b -> a -> b) -> b -> Flag a -> b # foldl' :: (b -> a -> b) -> b -> Flag a -> b # foldr1 :: (a -> a -> a) -> Flag a -> a # foldl1 :: (a -> a -> a) -> Flag a -> a # elem :: Eq a => a -> Flag a -> Bool # maximum :: Ord a => Flag a -> a # | |
| Traversable Flag Source # | |
| Applicative Flag Source # | |
| Functor Flag Source # | |
| Structured a => Structured (Flag a) Source # | |
| Defined in Distribution.Simple.Flag | |
| Monoid (Flag a) Source # | |
| Semigroup (Flag a) Source # | |
| Bounded a => Bounded (Flag a) Source # | |
| Enum a => Enum (Flag a) Source # | |
| Defined in Distribution.Simple.Flag | |
| Generic (Flag a) Source # | |
| Read a => Read (Flag a) Source # | |
| Show a => Show (Flag a) Source # | |
| Binary a => Binary (Flag a) Source # | |
| Eq a => Eq (Flag a) Source # | |
| type Rep (Flag a) Source # | |
| Defined in Distribution.Simple.Flag type Rep (Flag a) = D1 ('MetaData "Flag" "Distribution.Simple.Flag" "Cabal-3.14.0.0-inplace" 'False) (C1 ('MetaCons "Flag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "NoFlag" 'PrefixI 'False) (U1 :: Type -> Type)) | |
fromFlag :: WithCallStack (Flag a -> a) Source #
fromFlagOrDefault :: a -> Flag a -> a Source #
flagToList :: Flag a -> [a] Source #
Converts a Flag value to a list.
class BooleanFlag a where Source #
Types that represent boolean flags.
Instances
optionVerbosity :: (flags -> Flag Verbosity) -> (Flag Verbosity -> flags -> flags) -> OptionField flags Source #
data BuildingWhat Source #
What kind of build phase are we doing/hooking into?
Is this a normal build, or is it perhaps for running an interactive session or Haddock?
Constructors
| BuildNormal BuildFlags | A normal build. | 
| BuildRepl ReplFlags | Build steps for an interactive session. | 
| BuildHaddock HaddockFlags | Build steps for generating documentation. | 
| BuildHscolour HscolourFlags | Build steps for Hscolour. | 
Instances
buildingWhatWorkingDir :: BuildingWhat -> Maybe (SymbolicPath CWD (Dir Pkg)) Source #
buildingWhatDistPref :: BuildingWhat -> SymbolicPath Pkg (Dir Dist) Source #