Copyright | Isaac Jones 2003-2004 Duncan Coutts 2007 |
---|---|
License | BSD3 |
Maintainer | cabal-devel@haskell.org |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
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
- data GlobalFlags = GlobalFlags {}
- emptyGlobalFlags :: GlobalFlags
- defaultGlobalFlags :: GlobalFlags
- globalCommand :: [Command action] -> CommandUI GlobalFlags
- data ConfigFlags = ConfigFlags {
- configArgs :: [String]
- 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
- 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 :: [FilePath]
- configExtraLibDirsStatic :: [FilePath]
- configExtraFrameworkDirs :: [FilePath]
- configExtraIncludeDirs :: [FilePath]
- configIPID :: Flag String
- configCID :: Flag ComponentId
- configDeterministic :: Flag Bool
- configDistPref :: Flag FilePath
- configCabalFilePath :: Flag FilePath
- configVerbosity :: Flag Verbosity
- 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]
- 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
- emptyConfigFlags :: ConfigFlags
- defaultConfigFlags :: ProgramDb -> ConfigFlags
- configureCommand :: ProgramDb -> CommandUI ConfigFlags
- configPrograms :: WithCallStack (ConfigFlags -> ProgramDb)
- configAbsolutePaths :: ConfigFlags -> IO ConfigFlags
- readPackageDb :: String -> Maybe PackageDB
- readPackageDbList :: String -> [Maybe PackageDB]
- showPackageDb :: Maybe PackageDB -> String
- showPackageDbList :: [Maybe PackageDB] -> [String]
- data CopyFlags = CopyFlags {}
- emptyCopyFlags :: CopyFlags
- defaultCopyFlags :: CopyFlags
- copyCommand :: CommandUI CopyFlags
- data InstallFlags = InstallFlags {}
- emptyInstallFlags :: InstallFlags
- defaultInstallFlags :: InstallFlags
- installCommand :: CommandUI InstallFlags
- data HaddockTarget
- data HaddockFlags = HaddockFlags {
- 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
- haddockDistPref :: Flag FilePath
- haddockKeepTempFiles :: Flag Bool
- haddockVerbosity :: Flag Verbosity
- haddockCabalFilePath :: Flag FilePath
- haddockBaseUrl :: Flag String
- haddockLib :: Flag String
- haddockArgs :: [String]
- emptyHaddockFlags :: HaddockFlags
- defaultHaddockFlags :: HaddockFlags
- haddockCommand :: CommandUI HaddockFlags
- data Visibility
- data HaddockProjectFlags = HaddockProjectFlags {
- haddockProjectHackage :: Flag Bool
- haddockProjectLocal :: Flag Bool
- haddockProjectDir :: Flag String
- haddockProjectPrologue :: Flag String
- haddockProjectGenIndex :: Flag Bool
- haddockProjectGenContents :: Flag Bool
- 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
- haddockProjectLinkedSource :: Flag Bool
- haddockProjectQuickJump :: Flag Bool
- haddockProjectHscolourCss :: Flag FilePath
- haddockProjectKeepTempFiles :: Flag Bool
- haddockProjectVerbosity :: Flag Verbosity
- haddockProjectLib :: Flag String
- emptyHaddockProjectFlags :: HaddockProjectFlags
- defaultHaddockProjectFlags :: HaddockProjectFlags
- haddockProjectCommand :: CommandUI HaddockProjectFlags
- data HscolourFlags = HscolourFlags {}
- emptyHscolourFlags :: HscolourFlags
- defaultHscolourFlags :: HscolourFlags
- hscolourCommand :: CommandUI HscolourFlags
- data BuildFlags = BuildFlags {
- buildProgramPaths :: [(String, FilePath)]
- buildProgramArgs :: [(String, [String])]
- buildDistPref :: Flag FilePath
- buildVerbosity :: Flag Verbosity
- buildNumJobs :: Flag (Maybe Int)
- buildArgs :: [String]
- buildCabalFilePath :: Flag FilePath
- emptyBuildFlags :: BuildFlags
- defaultBuildFlags :: BuildFlags
- buildCommand :: ProgramDb -> CommandUI BuildFlags
- data DumpBuildInfo
- data ReplFlags = ReplFlags {
- replProgramPaths :: [(String, FilePath)]
- replProgramArgs :: [(String, [String])]
- replDistPref :: Flag FilePath
- replVerbosity :: Flag Verbosity
- replReload :: Flag Bool
- replReplOptions :: ReplOptions
- defaultReplFlags :: ReplFlags
- replCommand :: ProgramDb -> CommandUI ReplFlags
- data ReplOptions = ReplOptions {}
- data CleanFlags = CleanFlags {}
- emptyCleanFlags :: CleanFlags
- defaultCleanFlags :: CleanFlags
- cleanCommand :: CommandUI CleanFlags
- data RegisterFlags = RegisterFlags {}
- emptyRegisterFlags :: RegisterFlags
- defaultRegisterFlags :: RegisterFlags
- registerCommand :: CommandUI RegisterFlags
- unregisterCommand :: CommandUI RegisterFlags
- data SDistFlags = SDistFlags {}
- emptySDistFlags :: SDistFlags
- defaultSDistFlags :: SDistFlags
- sdistCommand :: CommandUI SDistFlags
- data TestFlags = TestFlags {}
- emptyTestFlags :: TestFlags
- defaultTestFlags :: TestFlags
- testCommand :: CommandUI TestFlags
- data TestShowDetails
- data BenchmarkFlags = 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 :: FilePath
- optionDistPref :: (flags -> Flag FilePath) -> (Flag FilePath -> 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
- optionNumJobs :: (flags -> Flag (Maybe Int)) -> (Flag (Maybe Int) -> flags -> flags) -> OptionField flags
Documentation
data GlobalFlags Source #
Flags that apply at the top level, not to any sub-command.
Instances
globalCommand :: [Command action] -> CommandUI GlobalFlags Source #
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
ConfigFlags | |
|
Instances
Structured ConfigFlags Source # | |||||
Defined in Distribution.Simple.Setup structure :: Proxy ConfigFlags -> Structure Source # structureHash' :: Tagged ConfigFlags MD5 | |||||
Monoid ConfigFlags Source # | |||||
Defined in Distribution.Simple.Setup mempty :: ConfigFlags Source # mappend :: ConfigFlags -> ConfigFlags -> ConfigFlags Source # mconcat :: [ConfigFlags] -> ConfigFlags Source # | |||||
Semigroup ConfigFlags Source # | |||||
Defined in Distribution.Simple.Setup (<>) :: ConfigFlags -> ConfigFlags -> ConfigFlags Source # sconcat :: NonEmpty ConfigFlags -> ConfigFlags Source # stimes :: Integral b => b -> ConfigFlags -> ConfigFlags Source # | |||||
Generic ConfigFlags Source # | |||||
Defined in Distribution.Simple.Setup
from :: ConfigFlags -> Rep ConfigFlags x Source # to :: Rep ConfigFlags x -> ConfigFlags Source # | |||||
Read ConfigFlags Source # | |||||
Defined in Distribution.Simple.Setup | |||||
Show ConfigFlags Source # | |||||
Defined in Distribution.Simple.Setup | |||||
Binary ConfigFlags Source # | |||||
Defined in Distribution.Simple.Setup | |||||
Eq ConfigFlags Source # | |||||
Defined in Distribution.Simple.Setup (==) :: ConfigFlags -> ConfigFlags -> Bool # (/=) :: ConfigFlags -> ConfigFlags -> Bool # | |||||
type Rep ConfigFlags Source # | |||||
Defined in Distribution.Simple.Setup type Rep ConfigFlags = D1 ('MetaData "ConfigFlags" "Distribution.Simple.Setup" "Cabal-3.10.2.0-0099" 'False) (C1 ('MetaCons "ConfigFlags" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "configArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "configPrograms_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Option' (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 "configFullyStaticExe") '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 "configExtraLibDirsStatic") '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 [PackageVersionConstraint]))))) :*: (((S1 ('MetaSel ('Just "configDependencies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [GivenComponent]) :*: (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 "configDumpBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag DumpBuildInfo))) :*: (S1 ('MetaSel ('Just "configUseResponseFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "configAllowDependingOnPrivateLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))))))))) |
configPrograms :: WithCallStack (ConfigFlags -> ProgramDb) Source #
More convenient version of configPrograms
. Results in an
error
if internal invariant is violated.
readPackageDb :: String -> Maybe PackageDB Source #
Parse a PackageDB stack entry
Since: Cabal-3.7.0.0
Flags to copy
: (destdir, copy-prefix (backwards compat), verbosity)
CopyFlags | |
|
Instances
Monoid CopyFlags Source # | |||||
Semigroup CopyFlags Source # | |||||
Generic CopyFlags Source # | |||||
Defined in Distribution.Simple.Setup
| |||||
Show CopyFlags Source # | |||||
type Rep CopyFlags Source # | |||||
Defined in Distribution.Simple.Setup type Rep CopyFlags = D1 ('MetaData "CopyFlags" "Distribution.Simple.Setup" "Cabal-3.10.2.0-0099" 'False) (C1 ('MetaCons "CopyFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "copyDest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag CopyDest)) :*: S1 ('MetaSel ('Just "copyDistPref") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath))) :*: (S1 ('MetaSel ('Just "copyVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)) :*: (S1 ('MetaSel ('Just "copyArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "copyCabalFilePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)))))) |
data InstallFlags Source #
Flags to install
: (package db, verbosity)
Instances
Monoid InstallFlags Source # | |||||
Defined in Distribution.Simple.Setup mempty :: InstallFlags Source # mappend :: InstallFlags -> InstallFlags -> InstallFlags Source # mconcat :: [InstallFlags] -> InstallFlags Source # | |||||
Semigroup InstallFlags Source # | |||||
Defined in Distribution.Simple.Setup (<>) :: InstallFlags -> InstallFlags -> InstallFlags Source # sconcat :: NonEmpty InstallFlags -> InstallFlags Source # stimes :: Integral b => b -> InstallFlags -> InstallFlags Source # | |||||
Generic InstallFlags Source # | |||||
Defined in Distribution.Simple.Setup
from :: InstallFlags -> Rep InstallFlags x Source # to :: Rep InstallFlags x -> InstallFlags Source # | |||||
Show InstallFlags Source # | |||||
Defined in Distribution.Simple.Setup | |||||
type Rep InstallFlags Source # | |||||
Defined in Distribution.Simple.Setup type Rep InstallFlags = D1 ('MetaData "InstallFlags" "Distribution.Simple.Setup" "Cabal-3.10.2.0-0099" 'False) (C1 ('MetaCons "InstallFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "installPackageDB") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PackageDB)) :*: (S1 ('MetaSel ('Just "installDest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag CopyDest)) :*: S1 ('MetaSel ('Just "installDistPref") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)))) :*: ((S1 ('MetaSel ('Just "installUseWrapper") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "installInPlace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "installVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)) :*: S1 ('MetaSel ('Just "installCabalFilePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)))))) |
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
.
Instances
Parsec HaddockTarget Source # | |||||
Defined in Distribution.Simple.Setup parsec :: CabalParsing m => m HaddockTarget Source # | |||||
Pretty HaddockTarget Source # | |||||
Defined in Distribution.Simple.Setup pretty :: HaddockTarget -> Doc Source # prettyVersioned :: CabalSpecVersion -> HaddockTarget -> Doc Source # | |||||
Structured HaddockTarget Source # | |||||
Defined in Distribution.Simple.Setup structure :: Proxy HaddockTarget -> Structure Source # structureHash' :: Tagged HaddockTarget MD5 | |||||
Generic HaddockTarget Source # | |||||
Defined in Distribution.Simple.Setup
from :: HaddockTarget -> Rep HaddockTarget x Source # to :: Rep HaddockTarget x -> HaddockTarget Source # | |||||
Show HaddockTarget Source # | |||||
Defined in Distribution.Simple.Setup | |||||
Binary HaddockTarget Source # | |||||
Defined in Distribution.Simple.Setup | |||||
Eq HaddockTarget Source # | |||||
Defined in Distribution.Simple.Setup (==) :: HaddockTarget -> HaddockTarget -> Bool # (/=) :: HaddockTarget -> HaddockTarget -> Bool # | |||||
type Rep HaddockTarget Source # | |||||
data HaddockFlags Source #
HaddockFlags | |
|
Instances
Monoid HaddockFlags Source # | |||||
Defined in Distribution.Simple.Setup mempty :: HaddockFlags Source # mappend :: HaddockFlags -> HaddockFlags -> HaddockFlags Source # mconcat :: [HaddockFlags] -> HaddockFlags Source # | |||||
Semigroup HaddockFlags Source # | |||||
Defined in Distribution.Simple.Setup (<>) :: HaddockFlags -> HaddockFlags -> HaddockFlags Source # sconcat :: NonEmpty HaddockFlags -> HaddockFlags Source # stimes :: Integral b => b -> HaddockFlags -> HaddockFlags Source # | |||||
Generic HaddockFlags Source # | |||||
Defined in Distribution.Simple.Setup
from :: HaddockFlags -> Rep HaddockFlags x Source # to :: Rep HaddockFlags x -> HaddockFlags Source # | |||||
Show HaddockFlags Source # | |||||
Defined in Distribution.Simple.Setup | |||||
type Rep HaddockFlags Source # | |||||
Defined in Distribution.Simple.Setup type Rep HaddockFlags = D1 ('MetaData "HaddockFlags" "Distribution.Simple.Setup" "Cabal-3.10.2.0-0099" '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 "haddockQuickJump") '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 "haddockIndex") '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)))) :*: (S1 ('MetaSel ('Just "haddockBaseUrl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: (S1 ('MetaSel ('Just "haddockLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: S1 ('MetaSel ('Just "haddockArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))))))) |
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 | |
Eq Visibility Source # | |
Defined in Distribution.Simple.Setup (==) :: Visibility -> Visibility -> Bool # (/=) :: Visibility -> Visibility -> Bool # |
data HaddockProjectFlags Source #
HaddockProjectFlags | |
|
Instances
Monoid HaddockProjectFlags Source # | |||||
Semigroup HaddockProjectFlags Source # | |||||
Defined in Distribution.Simple.Setup | |||||
Generic HaddockProjectFlags Source # | |||||
Defined in Distribution.Simple.Setup
from :: HaddockProjectFlags -> Rep HaddockProjectFlags x Source # to :: Rep HaddockProjectFlags x -> HaddockProjectFlags Source # | |||||
Show HaddockProjectFlags Source # | |||||
Defined in Distribution.Simple.Setup | |||||
type Rep HaddockProjectFlags Source # | |||||
Defined in Distribution.Simple.Setup type Rep HaddockProjectFlags = D1 ('MetaData "HaddockProjectFlags" "Distribution.Simple.Setup" "Cabal-3.10.2.0-0099" 'False) (C1 ('MetaCons "HaddockProjectFlags" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "haddockProjectHackage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "haddockProjectLocal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "haddockProjectDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: (S1 ('MetaSel ('Just "haddockProjectPrologue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: S1 ('MetaSel ('Just "haddockProjectGenIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))))) :*: ((S1 ('MetaSel ('Just "haddockProjectGenContents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 ('MetaSel ('Just "haddockProjectInterfaces") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [(FilePath, Maybe FilePath, Maybe FilePath, Visibility)])) :*: S1 ('MetaSel ('Just "haddockProjectProgramPaths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, FilePath)]))) :*: (S1 ('MetaSel ('Just "haddockProjectProgramArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, [String])]) :*: (S1 ('MetaSel ('Just "haddockProjectHoogle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "haddockProjectHtmlLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)))))) :*: (((S1 ('MetaSel ('Just "haddockProjectExecutables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 ('MetaSel ('Just "haddockProjectTestSuites") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "haddockProjectBenchmarks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: (S1 ('MetaSel ('Just "haddockProjectForeignLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 ('MetaSel ('Just "haddockProjectInternal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "haddockProjectCss") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath))))) :*: ((S1 ('MetaSel ('Just "haddockProjectLinkedSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 ('MetaSel ('Just "haddockProjectQuickJump") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "haddockProjectHscolourCss") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)))) :*: (S1 ('MetaSel ('Just "haddockProjectKeepTempFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 ('MetaSel ('Just "haddockProjectVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)) :*: S1 ('MetaSel ('Just "haddockProjectLib") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)))))))) |
data HscolourFlags Source #
Instances
Monoid HscolourFlags Source # | |||||
Defined in Distribution.Simple.Setup mempty :: HscolourFlags Source # mappend :: HscolourFlags -> HscolourFlags -> HscolourFlags Source # mconcat :: [HscolourFlags] -> HscolourFlags Source # | |||||
Semigroup HscolourFlags Source # | |||||
Defined in Distribution.Simple.Setup (<>) :: HscolourFlags -> HscolourFlags -> HscolourFlags Source # sconcat :: NonEmpty HscolourFlags -> HscolourFlags Source # stimes :: Integral b => b -> HscolourFlags -> HscolourFlags Source # | |||||
Generic HscolourFlags Source # | |||||
Defined in Distribution.Simple.Setup
from :: HscolourFlags -> Rep HscolourFlags x Source # to :: Rep HscolourFlags x -> HscolourFlags Source # | |||||
Show HscolourFlags Source # | |||||
Defined in Distribution.Simple.Setup | |||||
type Rep HscolourFlags Source # | |||||
Defined in Distribution.Simple.Setup type Rep HscolourFlags = D1 ('MetaData "HscolourFlags" "Distribution.Simple.Setup" "Cabal-3.10.2.0-0099" 'False) (C1 ('MetaCons "HscolourFlags" 'PrefixI 'True) (((S1 ('MetaSel ('Just "hscolourCSS") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "hscolourExecutables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "hscolourTestSuites") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "hscolourBenchmarks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "hscolourForeignLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "hscolourDistPref") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath))) :*: (S1 ('MetaSel ('Just "hscolourVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)) :*: S1 ('MetaSel ('Just "hscolourCabalFilePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)))))) |
data BuildFlags Source #
BuildFlags | |
|
Instances
Monoid BuildFlags Source # | |||||
Defined in Distribution.Simple.Setup mempty :: BuildFlags Source # mappend :: BuildFlags -> BuildFlags -> BuildFlags Source # mconcat :: [BuildFlags] -> BuildFlags Source # | |||||
Semigroup BuildFlags Source # | |||||
Defined in Distribution.Simple.Setup (<>) :: BuildFlags -> BuildFlags -> BuildFlags Source # sconcat :: NonEmpty BuildFlags -> BuildFlags Source # stimes :: Integral b => b -> BuildFlags -> BuildFlags Source # | |||||
Generic BuildFlags Source # | |||||
Defined in Distribution.Simple.Setup
from :: BuildFlags -> Rep BuildFlags x Source # to :: Rep BuildFlags x -> BuildFlags Source # | |||||
Read BuildFlags Source # | |||||
Defined in Distribution.Simple.Setup | |||||
Show BuildFlags Source # | |||||
Defined in Distribution.Simple.Setup | |||||
type Rep BuildFlags Source # | |||||
Defined in Distribution.Simple.Setup type Rep BuildFlags = D1 ('MetaData "BuildFlags" "Distribution.Simple.Setup" "Cabal-3.10.2.0-0099" 'False) (C1 ('MetaCons "BuildFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "buildProgramPaths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, FilePath)]) :*: (S1 ('MetaSel ('Just "buildProgramArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, [String])]) :*: S1 ('MetaSel ('Just "buildDistPref") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)))) :*: ((S1 ('MetaSel ('Just "buildVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)) :*: S1 ('MetaSel ('Just "buildNumJobs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag (Maybe Int)))) :*: (S1 ('MetaSel ('Just "buildArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "buildCabalFilePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)))))) |
data DumpBuildInfo Source #
Instances
Structured DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo structure :: Proxy DumpBuildInfo -> Structure Source # structureHash' :: Tagged DumpBuildInfo MD5 | |||||
Bounded DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo | |||||
Enum DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo succ :: DumpBuildInfo -> DumpBuildInfo Source # pred :: DumpBuildInfo -> DumpBuildInfo Source # toEnum :: Int -> DumpBuildInfo Source # fromEnum :: DumpBuildInfo -> Int Source # enumFrom :: DumpBuildInfo -> [DumpBuildInfo] Source # enumFromThen :: DumpBuildInfo -> DumpBuildInfo -> [DumpBuildInfo] Source # enumFromTo :: DumpBuildInfo -> DumpBuildInfo -> [DumpBuildInfo] Source # enumFromThenTo :: DumpBuildInfo -> DumpBuildInfo -> DumpBuildInfo -> [DumpBuildInfo] Source # | |||||
Generic DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo
from :: DumpBuildInfo -> Rep DumpBuildInfo x Source # to :: Rep DumpBuildInfo x -> DumpBuildInfo Source # | |||||
Read DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo | |||||
Show DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo | |||||
Binary DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo | |||||
Eq DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo (==) :: DumpBuildInfo -> DumpBuildInfo -> Bool # (/=) :: DumpBuildInfo -> DumpBuildInfo -> Bool # | |||||
Ord DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo compare :: DumpBuildInfo -> DumpBuildInfo -> Ordering # (<) :: DumpBuildInfo -> DumpBuildInfo -> Bool # (<=) :: DumpBuildInfo -> DumpBuildInfo -> Bool # (>) :: DumpBuildInfo -> DumpBuildInfo -> Bool # (>=) :: DumpBuildInfo -> DumpBuildInfo -> Bool # max :: DumpBuildInfo -> DumpBuildInfo -> DumpBuildInfo # min :: DumpBuildInfo -> DumpBuildInfo -> DumpBuildInfo # | |||||
type Rep DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo |
ReplFlags | |
|
Instances
Monoid ReplFlags Source # | |||||
Semigroup ReplFlags Source # | |||||
Generic ReplFlags Source # | |||||
Defined in Distribution.Simple.Setup
| |||||
Show ReplFlags Source # | |||||
type Rep ReplFlags Source # | |||||
Defined in Distribution.Simple.Setup type Rep ReplFlags = D1 ('MetaData "ReplFlags" "Distribution.Simple.Setup" "Cabal-3.10.2.0-0099" 'False) (C1 ('MetaCons "ReplFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "replProgramPaths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, FilePath)]) :*: (S1 ('MetaSel ('Just "replProgramArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, [String])]) :*: S1 ('MetaSel ('Just "replDistPref") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)))) :*: (S1 ('MetaSel ('Just "replVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)) :*: (S1 ('MetaSel ('Just "replReload") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "replReplOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ReplOptions))))) |
data ReplOptions Source #
Instances
Structured ReplOptions Source # | |||||
Defined in Distribution.Simple.Setup structure :: Proxy ReplOptions -> Structure Source # structureHash' :: Tagged ReplOptions MD5 | |||||
Monoid ReplOptions Source # | |||||
Defined in Distribution.Simple.Setup mempty :: ReplOptions Source # mappend :: ReplOptions -> ReplOptions -> ReplOptions Source # mconcat :: [ReplOptions] -> ReplOptions Source # | |||||
Semigroup ReplOptions Source # | |||||
Defined in Distribution.Simple.Setup (<>) :: ReplOptions -> ReplOptions -> ReplOptions Source # sconcat :: NonEmpty ReplOptions -> ReplOptions Source # stimes :: Integral b => b -> ReplOptions -> ReplOptions Source # | |||||
Generic ReplOptions Source # | |||||
Defined in Distribution.Simple.Setup
from :: ReplOptions -> Rep ReplOptions x Source # to :: Rep ReplOptions x -> ReplOptions Source # | |||||
Show ReplOptions Source # | |||||
Defined in Distribution.Simple.Setup | |||||
Binary ReplOptions Source # | |||||
Defined in Distribution.Simple.Setup | |||||
type Rep ReplOptions Source # | |||||
Defined in Distribution.Simple.Setup type Rep ReplOptions = D1 ('MetaData "ReplOptions" "Distribution.Simple.Setup" "Cabal-3.10.2.0-0099" 'False) (C1 ('MetaCons "ReplOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "replOptionsFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "replOptionsNoLoad") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) |
data CleanFlags Source #
Instances
Monoid CleanFlags Source # | |||||
Defined in Distribution.Simple.Setup mempty :: CleanFlags Source # mappend :: CleanFlags -> CleanFlags -> CleanFlags Source # mconcat :: [CleanFlags] -> CleanFlags Source # | |||||
Semigroup CleanFlags Source # | |||||
Defined in Distribution.Simple.Setup (<>) :: CleanFlags -> CleanFlags -> CleanFlags Source # sconcat :: NonEmpty CleanFlags -> CleanFlags Source # stimes :: Integral b => b -> CleanFlags -> CleanFlags Source # | |||||
Generic CleanFlags Source # | |||||
Defined in Distribution.Simple.Setup
from :: CleanFlags -> Rep CleanFlags x Source # to :: Rep CleanFlags x -> CleanFlags Source # | |||||
Show CleanFlags Source # | |||||
Defined in Distribution.Simple.Setup | |||||
type Rep CleanFlags Source # | |||||
Defined in Distribution.Simple.Setup type Rep CleanFlags = D1 ('MetaData "CleanFlags" "Distribution.Simple.Setup" "Cabal-3.10.2.0-0099" '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 Source #
Flags to register
and unregister
: (user package, gen-script,
in-place, verbosity)
RegisterFlags | |
|
Instances
Monoid RegisterFlags Source # | |||||
Defined in Distribution.Simple.Setup mempty :: RegisterFlags Source # mappend :: RegisterFlags -> RegisterFlags -> RegisterFlags Source # mconcat :: [RegisterFlags] -> RegisterFlags Source # | |||||
Semigroup RegisterFlags Source # | |||||
Defined in Distribution.Simple.Setup (<>) :: RegisterFlags -> RegisterFlags -> RegisterFlags Source # sconcat :: NonEmpty RegisterFlags -> RegisterFlags Source # stimes :: Integral b => b -> RegisterFlags -> RegisterFlags Source # | |||||
Generic RegisterFlags Source # | |||||
Defined in Distribution.Simple.Setup
from :: RegisterFlags -> Rep RegisterFlags x Source # to :: Rep RegisterFlags x -> RegisterFlags Source # | |||||
Show RegisterFlags Source # | |||||
Defined in Distribution.Simple.Setup | |||||
type Rep RegisterFlags Source # | |||||
Defined in Distribution.Simple.Setup type Rep RegisterFlags = D1 ('MetaData "RegisterFlags" "Distribution.Simple.Setup" "Cabal-3.10.2.0-0099" 'False) (C1 ('MetaCons "RegisterFlags" 'PrefixI 'True) (((S1 ('MetaSel ('Just "regPackageDB") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PackageDB)) :*: S1 ('MetaSel ('Just "regGenScript") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "regGenPkgConf") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag (Maybe FilePath))) :*: S1 ('MetaSel ('Just "regInPlace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "regDistPref") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "regPrintId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "regVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)) :*: (S1 ('MetaSel ('Just "regArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "regCabalFilePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath))))))) |
data SDistFlags Source #
Flags to sdist
: (snapshot, verbosity)
Instances
Monoid SDistFlags Source # | |||||
Defined in Distribution.Simple.Setup mempty :: SDistFlags Source # mappend :: SDistFlags -> SDistFlags -> SDistFlags Source # mconcat :: [SDistFlags] -> SDistFlags Source # | |||||
Semigroup SDistFlags Source # | |||||
Defined in Distribution.Simple.Setup (<>) :: SDistFlags -> SDistFlags -> SDistFlags Source # sconcat :: NonEmpty SDistFlags -> SDistFlags Source # stimes :: Integral b => b -> SDistFlags -> SDistFlags Source # | |||||
Generic SDistFlags Source # | |||||
Defined in Distribution.Simple.Setup
from :: SDistFlags -> Rep SDistFlags x Source # to :: Rep SDistFlags x -> SDistFlags Source # | |||||
Show SDistFlags Source # | |||||
Defined in Distribution.Simple.Setup | |||||
type Rep SDistFlags Source # | |||||
Defined in Distribution.Simple.Setup type Rep SDistFlags = D1 ('MetaData "SDistFlags" "Distribution.Simple.Setup" "Cabal-3.10.2.0-0099" 'False) (C1 ('MetaCons "SDistFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "sDistSnapshot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "sDistDirectory") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath))) :*: (S1 ('MetaSel ('Just "sDistDistPref") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: (S1 ('MetaSel ('Just "sDistListSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "sDistVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)))))) |
Instances
Monoid TestFlags Source # | |||||
Semigroup TestFlags Source # | |||||
Generic TestFlags Source # | |||||
Defined in Distribution.Simple.Setup
| |||||
Show TestFlags Source # | |||||
type Rep TestFlags Source # | |||||
Defined in Distribution.Simple.Setup type Rep TestFlags = D1 ('MetaData "TestFlags" "Distribution.Simple.Setup" "Cabal-3.10.2.0-0099" 'False) (C1 ('MetaCons "TestFlags" 'PrefixI 'True) (((S1 ('MetaSel ('Just "testDistPref") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "testVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity))) :*: (S1 ('MetaSel ('Just "testHumanLog") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PathTemplate)) :*: S1 ('MetaSel ('Just "testMachineLog") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PathTemplate)))) :*: ((S1 ('MetaSel ('Just "testShowDetails") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag TestShowDetails)) :*: S1 ('MetaSel ('Just "testKeepTix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "testWrapper") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: (S1 ('MetaSel ('Just "testFailWhenNoTestSuites") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "testOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PathTemplate])))))) |
data TestShowDetails Source #
Instances
Parsec TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup parsec :: CabalParsing m => m TestShowDetails Source # | |||||
Pretty TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup pretty :: TestShowDetails -> Doc Source # prettyVersioned :: CabalSpecVersion -> TestShowDetails -> Doc Source # | |||||
Structured TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup structure :: Proxy TestShowDetails -> Structure Source # structureHash' :: Tagged TestShowDetails MD5 | |||||
Monoid TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup | |||||
Semigroup TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup (<>) :: TestShowDetails -> TestShowDetails -> TestShowDetails Source # sconcat :: NonEmpty TestShowDetails -> TestShowDetails Source # stimes :: Integral b => b -> TestShowDetails -> TestShowDetails Source # | |||||
Bounded TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup | |||||
Enum TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup succ :: TestShowDetails -> TestShowDetails Source # pred :: TestShowDetails -> TestShowDetails Source # toEnum :: Int -> TestShowDetails Source # fromEnum :: TestShowDetails -> Int Source # enumFrom :: TestShowDetails -> [TestShowDetails] Source # enumFromThen :: TestShowDetails -> TestShowDetails -> [TestShowDetails] Source # enumFromTo :: TestShowDetails -> TestShowDetails -> [TestShowDetails] Source # enumFromThenTo :: TestShowDetails -> TestShowDetails -> TestShowDetails -> [TestShowDetails] Source # | |||||
Generic TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup
from :: TestShowDetails -> Rep TestShowDetails x Source # to :: Rep TestShowDetails x -> TestShowDetails Source # | |||||
Show TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup | |||||
Binary TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup | |||||
Eq TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup (==) :: TestShowDetails -> TestShowDetails -> Bool # (/=) :: TestShowDetails -> TestShowDetails -> Bool # | |||||
Ord TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup compare :: TestShowDetails -> TestShowDetails -> Ordering # (<) :: TestShowDetails -> TestShowDetails -> Bool # (<=) :: TestShowDetails -> TestShowDetails -> Bool # (>) :: TestShowDetails -> TestShowDetails -> Bool # (>=) :: TestShowDetails -> TestShowDetails -> Bool # max :: TestShowDetails -> TestShowDetails -> TestShowDetails # min :: TestShowDetails -> TestShowDetails -> TestShowDetails # | |||||
type Rep TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup type Rep TestShowDetails = D1 ('MetaData "TestShowDetails" "Distribution.Simple.Setup" "Cabal-3.10.2.0-0099" 'False) ((C1 ('MetaCons "Never" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Failures" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Always" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Streaming" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Direct" 'PrefixI 'False) (U1 :: Type -> Type)))) |
data BenchmarkFlags Source #
Instances
Monoid BenchmarkFlags Source # | |||||
Defined in Distribution.Simple.Setup mempty :: BenchmarkFlags Source # mappend :: BenchmarkFlags -> BenchmarkFlags -> BenchmarkFlags Source # mconcat :: [BenchmarkFlags] -> BenchmarkFlags Source # | |||||
Semigroup BenchmarkFlags Source # | |||||
Defined in Distribution.Simple.Setup (<>) :: BenchmarkFlags -> BenchmarkFlags -> BenchmarkFlags Source # sconcat :: NonEmpty BenchmarkFlags -> BenchmarkFlags Source # stimes :: Integral b => b -> BenchmarkFlags -> BenchmarkFlags Source # | |||||
Generic BenchmarkFlags Source # | |||||
Defined in Distribution.Simple.Setup
from :: BenchmarkFlags -> Rep BenchmarkFlags x Source # to :: Rep BenchmarkFlags x -> BenchmarkFlags Source # | |||||
Show BenchmarkFlags Source # | |||||
Defined in Distribution.Simple.Setup | |||||
type Rep BenchmarkFlags Source # | |||||
Defined in Distribution.Simple.Setup type Rep BenchmarkFlags = D1 ('MetaData "BenchmarkFlags" "Distribution.Simple.Setup" "Cabal-3.10.2.0-0099" 'False) (C1 ('MetaCons "BenchmarkFlags" 'PrefixI 'True) (S1 ('MetaSel ('Just "benchmarkDistPref") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: (S1 ('MetaSel ('Just "benchmarkVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)) :*: S1 ('MetaSel ('Just "benchmarkOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PathTemplate])))) |
The location prefix for the copy command.
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
Generic CopyDest Source # | |||||
Defined in Distribution.Simple.InstallDirs
| |||||
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.10.2.0-0099" '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"]
optionDistPref :: (flags -> Flag FilePath) -> (Flag FilePath -> 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.
Instances
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 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 # | |||||
Generic (Flag a) Source # | |||||
Defined in Distribution.Simple.Flag
| |||||
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.10.2.0-0099" '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 #
flagToMaybe :: Flag a -> Maybe a Source #
flagToList :: Flag a -> [a] Source #
maybeToFlag :: Maybe a -> Flag a Source #
class BooleanFlag a where Source #
Types that represent boolean flags.
Instances
optionVerbosity :: (flags -> Flag Verbosity) -> (Flag Verbosity -> flags -> flags) -> OptionField flags Source #
optionNumJobs :: (flags -> Flag (Maybe Int)) -> (Flag (Maybe Int) -> flags -> flags) -> OptionField flags Source #