Copyright | Isaac Jones 2003-2004 Duncan Coutts 2007 |
---|---|
License | BSD3 |
Maintainer | cabal-devel@haskell.org |
Portability | portable |
Safe Haskell | None |
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
- CopyFlags { }
- pattern CopyCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg ('Dir Dist)) -> Flag (SymbolicPath CWD ('Dir Pkg)) -> Flag (SymbolicPath Pkg 'File) -> [String] -> CopyFlags
- 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
- TestFlags { }
- pattern TestCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg ('Dir Dist)) -> Flag (SymbolicPath CWD ('Dir Pkg)) -> Flag (SymbolicPath Pkg 'File) -> [String] -> TestFlags
- 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
Structured CommonSetupFlags Source # | |||||
Defined in Distribution.Simple.Setup.Common Methods structure :: Proxy CommonSetupFlags -> Structure Source # structureHash' :: Tagged CommonSetupFlags MD5 | |||||
Binary CommonSetupFlags Source # | |||||
Defined in Distribution.Simple.Setup.Common Methods put :: CommonSetupFlags -> Put # get :: Get CommonSetupFlags # putList :: [CommonSetupFlags] -> Put # | |||||
Monoid CommonSetupFlags Source # | |||||
Defined in Distribution.Simple.Setup.Common Methods mappend :: CommonSetupFlags -> CommonSetupFlags -> CommonSetupFlags # mconcat :: [CommonSetupFlags] -> CommonSetupFlags # | |||||
Semigroup CommonSetupFlags Source # | |||||
Defined in Distribution.Simple.Setup.Common Methods (<>) :: CommonSetupFlags -> CommonSetupFlags -> CommonSetupFlags # sconcat :: NonEmpty CommonSetupFlags -> CommonSetupFlags # stimes :: Integral b => b -> CommonSetupFlags -> CommonSetupFlags # | |||||
Generic CommonSetupFlags Source # | |||||
Defined in Distribution.Simple.Setup.Common Associated Types
Methods from :: CommonSetupFlags -> Rep CommonSetupFlags x # to :: Rep CommonSetupFlags x -> CommonSetupFlags # | |||||
Read CommonSetupFlags Source # | |||||
Defined in Distribution.Simple.Setup.Common Methods readsPrec :: Int -> ReadS CommonSetupFlags # readList :: ReadS [CommonSetupFlags] # | |||||
Show CommonSetupFlags Source # | |||||
Defined in Distribution.Simple.Setup.Common Methods showsPrec :: Int -> CommonSetupFlags -> ShowS # show :: CommonSetupFlags -> String # showList :: [CommonSetupFlags] -> ShowS # | |||||
Eq CommonSetupFlags Source # | |||||
Defined in Distribution.Simple.Setup.Common Methods (==) :: CommonSetupFlags -> CommonSetupFlags -> Bool # (/=) :: CommonSetupFlags -> CommonSetupFlags -> Bool # | |||||
type Rep CommonSetupFlags Source # | |||||
Defined in Distribution.Simple.Setup.Common type Rep CommonSetupFlags = D1 ('MetaData "CommonSetupFlags" "Distribution.Simple.Setup.Common" "Cabal-3.14.1.0-be50" 'False) (C1 ('MetaCons "CommonSetupFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "setupVerbosity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Flag Verbosity)) :*: S1 ('MetaSel ('Just "setupWorkingDir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Flag (SymbolicPath CWD ('Dir Pkg))))) :*: (S1 ('MetaSel ('Just "setupDistPref") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Flag (SymbolicPath Pkg ('Dir Dist)))) :*: (S1 ('MetaSel ('Just "setupCabalFilePath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Flag (SymbolicPath Pkg 'File))) :*: S1 ('MetaSel ('Just "setupTargets") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))))) |
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
Structured ConfigFlags Source # | |||||
Defined in Distribution.Simple.Setup.Config | |||||
Binary ConfigFlags Source # | |||||
Defined in Distribution.Simple.Setup.Config | |||||
Monoid ConfigFlags Source # | |||||
Defined in Distribution.Simple.Setup.Config Methods mempty :: ConfigFlags # mappend :: ConfigFlags -> ConfigFlags -> ConfigFlags # mconcat :: [ConfigFlags] -> ConfigFlags # | |||||
Semigroup ConfigFlags Source # | |||||
Defined in Distribution.Simple.Setup.Config Methods (<>) :: ConfigFlags -> ConfigFlags -> ConfigFlags # sconcat :: NonEmpty ConfigFlags -> ConfigFlags # stimes :: Integral b => b -> ConfigFlags -> ConfigFlags # | |||||
Generic ConfigFlags Source # | |||||
Defined in Distribution.Simple.Setup.Config Associated Types
| |||||
Read ConfigFlags Source # | |||||
Defined in Distribution.Simple.Setup.Config Methods readsPrec :: Int -> ReadS ConfigFlags # readList :: ReadS [ConfigFlags] # readPrec :: ReadPrec ConfigFlags # readListPrec :: ReadPrec [ConfigFlags] # | |||||
Show ConfigFlags Source # | |||||
Defined in Distribution.Simple.Setup.Config Methods showsPrec :: Int -> ConfigFlags -> ShowS # show :: ConfigFlags -> String # showList :: [ConfigFlags] -> ShowS # | |||||
Eq ConfigFlags Source # | |||||
Defined in Distribution.Simple.Setup.Config | |||||
type Rep ConfigFlags Source # | |||||
Defined in Distribution.Simple.Setup.Config type Rep ConfigFlags = D1 ('MetaData "ConfigFlags" "Distribution.Simple.Setup.Config" "Cabal-3.14.1.0-be50" 'False) (C1 ('MetaCons "ConfigFlags" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "configCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: (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 "configProfShared") '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 [SymbolicPath Pkg ('Dir Lib)])) :*: (S1 ('MetaSel ('Just "configExtraLibDirsStatic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg ('Dir Lib)]) :*: S1 ('MetaSel ('Just "configExtraFrameworkDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg ('Dir Framework)])))))) :*: ((((S1 ('MetaSel ('Just "configExtraIncludeDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg ('Dir Include)]) :*: (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 "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 "configPromisedDependencies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PromisedComponent]))))) :*: (((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))) :*: (S1 ('MetaSel ('Just "configCoverageFor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [UnitId])) :*: S1 ('MetaSel ('Just "configIgnoreBuildTools") '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)
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 | |||||
Binary CopyFlags Source # | |||||
Monoid CopyFlags Source # | |||||
Semigroup CopyFlags Source # | |||||
Generic CopyFlags Source # | |||||
Defined in Distribution.Simple.Setup.Copy Associated Types
| |||||
Show 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.1.0-be50" '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
Monoid InstallFlags Source # | |||||
Defined in Distribution.Simple.Setup.Install Methods mempty :: InstallFlags # mappend :: InstallFlags -> InstallFlags -> InstallFlags # mconcat :: [InstallFlags] -> InstallFlags # | |||||
Semigroup InstallFlags Source # | |||||
Defined in Distribution.Simple.Setup.Install Methods (<>) :: InstallFlags -> InstallFlags -> InstallFlags # sconcat :: NonEmpty InstallFlags -> InstallFlags # stimes :: Integral b => b -> InstallFlags -> InstallFlags # | |||||
Generic InstallFlags Source # | |||||
Defined in Distribution.Simple.Setup.Install Associated Types
| |||||
Show InstallFlags Source # | |||||
Defined in Distribution.Simple.Setup.Install Methods showsPrec :: Int -> InstallFlags -> ShowS # show :: InstallFlags -> String # showList :: [InstallFlags] -> ShowS # | |||||
type Rep InstallFlags Source # | |||||
Defined in Distribution.Simple.Setup.Install type Rep InstallFlags = D1 ('MetaData "InstallFlags" "Distribution.Simple.Setup.Install" "Cabal-3.14.1.0-be50" 'False) (C1 ('MetaCons "InstallFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "installCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: S1 ('MetaSel ('Just "installPackageDB") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PackageDB))) :*: (S1 ('MetaSel ('Just "installDest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag CopyDest)) :*: (S1 ('MetaSel ('Just "installUseWrapper") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "installInPlace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))))) |
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 Source # | |||||
Pretty HaddockTarget Source # | |||||
Defined in Distribution.Simple.Setup.Haddock Methods pretty :: HaddockTarget -> Doc Source # prettyVersioned :: CabalSpecVersion -> HaddockTarget -> Doc Source # | |||||
Structured HaddockTarget Source # | |||||
Defined in Distribution.Simple.Setup.Haddock Methods structure :: Proxy HaddockTarget -> Structure Source # structureHash' :: Tagged HaddockTarget MD5 | |||||
Binary HaddockTarget Source # | |||||
Defined in Distribution.Simple.Setup.Haddock | |||||
Generic HaddockTarget Source # | |||||
Defined in Distribution.Simple.Setup.Haddock Associated Types
| |||||
Show HaddockTarget Source # | |||||
Defined in Distribution.Simple.Setup.Haddock Methods showsPrec :: Int -> HaddockTarget -> ShowS # show :: HaddockTarget -> String # showList :: [HaddockTarget] -> ShowS # | |||||
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
HaddockFlags | |
Fields
|
Bundled Patterns
pattern HaddockCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg ('Dir Dist)) -> Flag (SymbolicPath CWD ('Dir Pkg)) -> Flag (SymbolicPath Pkg 'File) -> [String] -> HaddockFlags |
Instances
Structured HaddockFlags Source # | |||||
Defined in Distribution.Simple.Setup.Haddock Methods structure :: Proxy HaddockFlags -> Structure Source # structureHash' :: Tagged HaddockFlags MD5 | |||||
Binary HaddockFlags Source # | |||||
Defined in Distribution.Simple.Setup.Haddock | |||||
Monoid HaddockFlags Source # | |||||
Defined in Distribution.Simple.Setup.Haddock Methods mempty :: HaddockFlags # mappend :: HaddockFlags -> HaddockFlags -> HaddockFlags # mconcat :: [HaddockFlags] -> HaddockFlags # | |||||
Semigroup HaddockFlags Source # | |||||
Defined in Distribution.Simple.Setup.Haddock Methods (<>) :: HaddockFlags -> HaddockFlags -> HaddockFlags # sconcat :: NonEmpty HaddockFlags -> HaddockFlags # stimes :: Integral b => b -> HaddockFlags -> HaddockFlags # | |||||
Generic HaddockFlags Source # | |||||
Defined in Distribution.Simple.Setup.Haddock Associated Types
| |||||
Show HaddockFlags Source # | |||||
Defined in Distribution.Simple.Setup.Haddock Methods showsPrec :: Int -> HaddockFlags -> ShowS # show :: HaddockFlags -> String # showList :: [HaddockFlags] -> ShowS # | |||||
type Rep HaddockFlags Source # | |||||
Defined in Distribution.Simple.Setup.Haddock type Rep HaddockFlags = D1 ('MetaData "HaddockFlags" "Distribution.Simple.Setup.Haddock" "Cabal-3.14.1.0-be50" 'False) (C1 ('MetaCons "HaddockFlags" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "haddockCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: 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 "haddockKeepTempFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "haddockBaseUrl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)))) :*: (S1 ('MetaSel ('Just "haddockResourcesDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: (S1 ('MetaSel ('Just "haddockOutputDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "haddockUseUnicode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))))))) |
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
HaddockProjectFlags | |
Fields
|
Instances
Monoid HaddockProjectFlags Source # | |||||
Defined in Distribution.Simple.Setup.Haddock Methods mempty :: HaddockProjectFlags # mappend :: HaddockProjectFlags -> HaddockProjectFlags -> HaddockProjectFlags # | |||||
Semigroup HaddockProjectFlags Source # | |||||
Defined in Distribution.Simple.Setup.Haddock Methods (<>) :: HaddockProjectFlags -> HaddockProjectFlags -> HaddockProjectFlags # sconcat :: NonEmpty HaddockProjectFlags -> HaddockProjectFlags # stimes :: Integral b => b -> HaddockProjectFlags -> HaddockProjectFlags # | |||||
Generic HaddockProjectFlags Source # | |||||
Defined in Distribution.Simple.Setup.Haddock Associated Types
Methods from :: HaddockProjectFlags -> Rep HaddockProjectFlags x # to :: Rep HaddockProjectFlags x -> HaddockProjectFlags # | |||||
Show HaddockProjectFlags Source # | |||||
Defined in Distribution.Simple.Setup.Haddock Methods showsPrec :: Int -> HaddockProjectFlags -> ShowS # show :: HaddockProjectFlags -> String # showList :: [HaddockProjectFlags] -> ShowS # | |||||
type Rep HaddockProjectFlags Source # | |||||
Defined in Distribution.Simple.Setup.Haddock type Rep HaddockProjectFlags = D1 ('MetaData "HaddockProjectFlags" "Distribution.Simple.Setup.Haddock" "Cabal-3.14.1.0-be50" 'False) (C1 ('MetaCons "HaddockProjectFlags" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "haddockProjectHackage") '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 "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 "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 "haddockProjectResourcesDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: S1 ('MetaSel ('Just "haddockProjectUseUnicode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))))))) |
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
Structured HscolourFlags Source # | |||||
Defined in Distribution.Simple.Setup.Hscolour Methods structure :: Proxy HscolourFlags -> Structure Source # structureHash' :: Tagged HscolourFlags MD5 | |||||
Binary HscolourFlags Source # | |||||
Defined in Distribution.Simple.Setup.Hscolour | |||||
Monoid HscolourFlags Source # | |||||
Defined in Distribution.Simple.Setup.Hscolour Methods mempty :: HscolourFlags # mappend :: HscolourFlags -> HscolourFlags -> HscolourFlags # mconcat :: [HscolourFlags] -> HscolourFlags # | |||||
Semigroup HscolourFlags Source # | |||||
Defined in Distribution.Simple.Setup.Hscolour Methods (<>) :: HscolourFlags -> HscolourFlags -> HscolourFlags # sconcat :: NonEmpty HscolourFlags -> HscolourFlags # stimes :: Integral b => b -> HscolourFlags -> HscolourFlags # | |||||
Generic HscolourFlags Source # | |||||
Defined in Distribution.Simple.Setup.Hscolour Associated Types
| |||||
Show HscolourFlags Source # | |||||
Defined in Distribution.Simple.Setup.Hscolour Methods showsPrec :: Int -> HscolourFlags -> ShowS # show :: HscolourFlags -> String # showList :: [HscolourFlags] -> ShowS # | |||||
type Rep HscolourFlags Source # | |||||
Defined in Distribution.Simple.Setup.Hscolour type Rep HscolourFlags = D1 ('MetaData "HscolourFlags" "Distribution.Simple.Setup.Hscolour" "Cabal-3.14.1.0-be50" 'False) (C1 ('MetaCons "HscolourFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "hscolourCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: (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)))))) |
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
Structured BuildFlags Source # | |||||
Defined in Distribution.Simple.Setup.Build | |||||
Binary BuildFlags Source # | |||||
Defined in Distribution.Simple.Setup.Build | |||||
Monoid BuildFlags Source # | |||||
Defined in Distribution.Simple.Setup.Build Methods mempty :: BuildFlags # mappend :: BuildFlags -> BuildFlags -> BuildFlags # mconcat :: [BuildFlags] -> BuildFlags # | |||||
Semigroup BuildFlags Source # | |||||
Defined in Distribution.Simple.Setup.Build Methods (<>) :: BuildFlags -> BuildFlags -> BuildFlags # sconcat :: NonEmpty BuildFlags -> BuildFlags # stimes :: Integral b => b -> BuildFlags -> BuildFlags # | |||||
Generic BuildFlags Source # | |||||
Defined in Distribution.Simple.Setup.Build Associated Types
| |||||
Read BuildFlags Source # | |||||
Defined in Distribution.Simple.Setup.Build Methods readsPrec :: Int -> ReadS BuildFlags # readList :: ReadS [BuildFlags] # readPrec :: ReadPrec BuildFlags # readListPrec :: ReadPrec [BuildFlags] # | |||||
Show BuildFlags Source # | |||||
Defined in Distribution.Simple.Setup.Build Methods showsPrec :: Int -> BuildFlags -> ShowS # show :: BuildFlags -> String # showList :: [BuildFlags] -> ShowS # | |||||
type Rep BuildFlags Source # | |||||
Defined in Distribution.Simple.Setup.Build type Rep BuildFlags = D1 ('MetaData "BuildFlags" "Distribution.Simple.Setup.Build" "Cabal-3.14.1.0-be50" 'False) (C1 ('MetaCons "BuildFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "buildCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: S1 ('MetaSel ('Just "buildProgramPaths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, FilePath)])) :*: (S1 ('MetaSel ('Just "buildProgramArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, [String])]) :*: (S1 ('MetaSel ('Just "buildNumJobs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag (Maybe Int))) :*: S1 ('MetaSel ('Just "buildUseSemaphore") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)))))) |
data DumpBuildInfo Source #
Constructors
NoDumpBuildInfo | |
DumpBuildInfo |
Instances
Structured DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo Methods structure :: Proxy DumpBuildInfo -> Structure Source # structureHash' :: Tagged DumpBuildInfo MD5 | |||||
Binary DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo | |||||
Bounded DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo | |||||
Enum DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo Methods succ :: DumpBuildInfo -> DumpBuildInfo # pred :: DumpBuildInfo -> DumpBuildInfo # toEnum :: Int -> DumpBuildInfo # fromEnum :: DumpBuildInfo -> Int # enumFrom :: DumpBuildInfo -> [DumpBuildInfo] # enumFromThen :: DumpBuildInfo -> DumpBuildInfo -> [DumpBuildInfo] # enumFromTo :: DumpBuildInfo -> DumpBuildInfo -> [DumpBuildInfo] # enumFromThenTo :: DumpBuildInfo -> DumpBuildInfo -> DumpBuildInfo -> [DumpBuildInfo] # | |||||
Generic DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo Associated Types
| |||||
Read DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo Methods readsPrec :: Int -> ReadS DumpBuildInfo # readList :: ReadS [DumpBuildInfo] # | |||||
Show DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo Methods showsPrec :: Int -> DumpBuildInfo -> ShowS # show :: DumpBuildInfo -> String # showList :: [DumpBuildInfo] -> ShowS # | |||||
Eq DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo Methods (==) :: DumpBuildInfo -> DumpBuildInfo -> Bool # (/=) :: DumpBuildInfo -> DumpBuildInfo -> Bool # | |||||
Ord DumpBuildInfo Source # | |||||
Defined in Distribution.Types.DumpBuildInfo Methods 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 |
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
Structured ReplFlags Source # | |||||
Defined in Distribution.Simple.Setup.Repl | |||||
Binary ReplFlags Source # | |||||
Monoid ReplFlags Source # | |||||
Semigroup ReplFlags Source # | |||||
Generic ReplFlags Source # | |||||
Defined in Distribution.Simple.Setup.Repl Associated Types
| |||||
Show ReplFlags Source # | |||||
type Rep ReplFlags Source # | |||||
Defined in Distribution.Simple.Setup.Repl type Rep ReplFlags = D1 ('MetaData "ReplFlags" "Distribution.Simple.Setup.Repl" "Cabal-3.14.1.0-be50" 'False) (C1 ('MetaCons "ReplFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "replCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: S1 ('MetaSel ('Just "replProgramPaths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, FilePath)])) :*: (S1 ('MetaSel ('Just "replProgramArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, [String])]) :*: (S1 ('MetaSel ('Just "replReload") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "replReplOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ReplOptions))))) |
data ReplOptions Source #
Constructors
ReplOptions | |
Fields |
Instances
Structured ReplOptions Source # | |||||
Defined in Distribution.Simple.Setup.Repl | |||||
Binary ReplOptions Source # | |||||
Defined in Distribution.Simple.Setup.Repl | |||||
Monoid ReplOptions Source # | |||||
Defined in Distribution.Simple.Setup.Repl Methods mempty :: ReplOptions # mappend :: ReplOptions -> ReplOptions -> ReplOptions # mconcat :: [ReplOptions] -> ReplOptions # | |||||
Semigroup ReplOptions Source # | |||||
Defined in Distribution.Simple.Setup.Repl Methods (<>) :: ReplOptions -> ReplOptions -> ReplOptions # sconcat :: NonEmpty ReplOptions -> ReplOptions # stimes :: Integral b => b -> ReplOptions -> ReplOptions # | |||||
Generic ReplOptions Source # | |||||
Defined in Distribution.Simple.Setup.Repl Associated Types
| |||||
Show ReplOptions Source # | |||||
Defined in Distribution.Simple.Setup.Repl Methods showsPrec :: Int -> ReplOptions -> ShowS # show :: ReplOptions -> String # showList :: [ReplOptions] -> ShowS # | |||||
type Rep ReplOptions Source # | |||||
Defined in Distribution.Simple.Setup.Repl type Rep ReplOptions = D1 ('MetaData "ReplOptions" "Distribution.Simple.Setup.Repl" "Cabal-3.14.1.0-be50" '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)) :*: S1 ('MetaSel ('Just "replOptionsFlagOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath))))) |
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
Structured CleanFlags Source # | |||||
Defined in Distribution.Simple.Setup.Clean | |||||
Binary CleanFlags Source # | |||||
Defined in Distribution.Simple.Setup.Clean | |||||
Monoid CleanFlags Source # | |||||
Defined in Distribution.Simple.Setup.Clean Methods mempty :: CleanFlags # mappend :: CleanFlags -> CleanFlags -> CleanFlags # mconcat :: [CleanFlags] -> CleanFlags # | |||||
Semigroup CleanFlags Source # | |||||
Defined in Distribution.Simple.Setup.Clean Methods (<>) :: CleanFlags -> CleanFlags -> CleanFlags # sconcat :: NonEmpty CleanFlags -> CleanFlags # stimes :: Integral b => b -> CleanFlags -> CleanFlags # | |||||
Generic CleanFlags Source # | |||||
Defined in Distribution.Simple.Setup.Clean Associated Types
| |||||
Show CleanFlags Source # | |||||
Defined in Distribution.Simple.Setup.Clean Methods showsPrec :: Int -> CleanFlags -> ShowS # show :: CleanFlags -> String # showList :: [CleanFlags] -> ShowS # | |||||
type Rep CleanFlags Source # | |||||
Defined in Distribution.Simple.Setup.Clean type Rep CleanFlags = D1 ('MetaData "CleanFlags" "Distribution.Simple.Setup.Clean" "Cabal-3.14.1.0-be50" 'False) (C1 ('MetaCons "CleanFlags" 'PrefixI 'True) (S1 ('MetaSel ('Just "cleanCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: S1 ('MetaSel ('Just "cleanSaveConf") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) |
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
Monoid RegisterFlags Source # | |||||
Defined in Distribution.Simple.Setup.Register Methods mempty :: RegisterFlags # mappend :: RegisterFlags -> RegisterFlags -> RegisterFlags # mconcat :: [RegisterFlags] -> RegisterFlags # | |||||
Semigroup RegisterFlags Source # | |||||
Defined in Distribution.Simple.Setup.Register Methods (<>) :: RegisterFlags -> RegisterFlags -> RegisterFlags # sconcat :: NonEmpty RegisterFlags -> RegisterFlags # stimes :: Integral b => b -> RegisterFlags -> RegisterFlags # | |||||
Generic RegisterFlags Source # | |||||
Defined in Distribution.Simple.Setup.Register Associated Types
| |||||
Show RegisterFlags Source # | |||||
Defined in Distribution.Simple.Setup.Register Methods showsPrec :: Int -> RegisterFlags -> ShowS # show :: RegisterFlags -> String # showList :: [RegisterFlags] -> ShowS # | |||||
type Rep RegisterFlags Source # | |||||
Defined in Distribution.Simple.Setup.Register type Rep RegisterFlags = D1 ('MetaData "RegisterFlags" "Distribution.Simple.Setup.Register" "Cabal-3.14.1.0-be50" 'False) (C1 ('MetaCons "RegisterFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "registerCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: (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 (SymbolicPath Pkg ('Dir PkgConf))))) :*: (S1 ('MetaSel ('Just "regInPlace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "regPrintId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))))) |
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
Monoid SDistFlags Source # | |||||
Defined in Distribution.Simple.Setup.SDist Methods mempty :: SDistFlags # mappend :: SDistFlags -> SDistFlags -> SDistFlags # mconcat :: [SDistFlags] -> SDistFlags # | |||||
Semigroup SDistFlags Source # | |||||
Defined in Distribution.Simple.Setup.SDist Methods (<>) :: SDistFlags -> SDistFlags -> SDistFlags # sconcat :: NonEmpty SDistFlags -> SDistFlags # stimes :: Integral b => b -> SDistFlags -> SDistFlags # | |||||
Generic SDistFlags Source # | |||||
Defined in Distribution.Simple.Setup.SDist Associated Types
| |||||
Show SDistFlags Source # | |||||
Defined in Distribution.Simple.Setup.SDist Methods showsPrec :: Int -> SDistFlags -> ShowS # show :: SDistFlags -> String # showList :: [SDistFlags] -> ShowS # | |||||
type Rep SDistFlags Source # | |||||
Defined in Distribution.Simple.Setup.SDist type Rep SDistFlags = D1 ('MetaData "SDistFlags" "Distribution.Simple.Setup.SDist" "Cabal-3.14.1.0-be50" 'False) (C1 ('MetaCons "SDistFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "sDistCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: S1 ('MetaSel ('Just "sDistSnapshot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "sDistDirectory") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "sDistListSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath))))) |
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
Structured TestFlags Source # | |||||
Defined in Distribution.Simple.Setup.Test | |||||
Binary TestFlags Source # | |||||
Monoid TestFlags Source # | |||||
Semigroup TestFlags Source # | |||||
Generic TestFlags Source # | |||||
Defined in Distribution.Simple.Setup.Test Associated Types
| |||||
Show TestFlags Source # | |||||
type Rep TestFlags Source # | |||||
Defined in Distribution.Simple.Setup.Test type Rep TestFlags = D1 ('MetaData "TestFlags" "Distribution.Simple.Setup.Test" "Cabal-3.14.1.0-be50" 'False) (C1 ('MetaCons "TestFlags" 'PrefixI 'True) (((S1 ('MetaSel ('Just "testCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: 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.Test Methods parsec :: CabalParsing m => m TestShowDetails Source # | |||||
Pretty TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup.Test Methods pretty :: TestShowDetails -> Doc Source # prettyVersioned :: CabalSpecVersion -> TestShowDetails -> Doc Source # | |||||
Structured TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup.Test Methods structure :: Proxy TestShowDetails -> Structure Source # structureHash' :: Tagged TestShowDetails MD5 | |||||
Binary TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup.Test Methods put :: TestShowDetails -> Put # get :: Get TestShowDetails # putList :: [TestShowDetails] -> Put # | |||||
Monoid TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup.Test Methods mappend :: TestShowDetails -> TestShowDetails -> TestShowDetails # mconcat :: [TestShowDetails] -> TestShowDetails # | |||||
Semigroup TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup.Test Methods (<>) :: TestShowDetails -> TestShowDetails -> TestShowDetails # sconcat :: NonEmpty TestShowDetails -> TestShowDetails # stimes :: Integral b => b -> TestShowDetails -> TestShowDetails # | |||||
Bounded TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup.Test | |||||
Enum TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup.Test Methods succ :: TestShowDetails -> TestShowDetails # pred :: TestShowDetails -> TestShowDetails # toEnum :: Int -> TestShowDetails # fromEnum :: TestShowDetails -> Int # enumFrom :: TestShowDetails -> [TestShowDetails] # enumFromThen :: TestShowDetails -> TestShowDetails -> [TestShowDetails] # enumFromTo :: TestShowDetails -> TestShowDetails -> [TestShowDetails] # enumFromThenTo :: TestShowDetails -> TestShowDetails -> TestShowDetails -> [TestShowDetails] # | |||||
Generic TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup.Test Associated Types
Methods from :: TestShowDetails -> Rep TestShowDetails x # to :: Rep TestShowDetails x -> TestShowDetails # | |||||
Show TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup.Test Methods showsPrec :: Int -> TestShowDetails -> ShowS # show :: TestShowDetails -> String # showList :: [TestShowDetails] -> ShowS # | |||||
Eq TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup.Test Methods (==) :: TestShowDetails -> TestShowDetails -> Bool # (/=) :: TestShowDetails -> TestShowDetails -> Bool # | |||||
Ord TestShowDetails Source # | |||||
Defined in Distribution.Simple.Setup.Test Methods 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.Test type Rep TestShowDetails = D1 ('MetaData "TestShowDetails" "Distribution.Simple.Setup.Test" "Cabal-3.14.1.0-be50" '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 #
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
Structured BenchmarkFlags Source # | |||||
Defined in Distribution.Simple.Setup.Benchmark Methods structure :: Proxy BenchmarkFlags -> Structure Source # structureHash' :: Tagged BenchmarkFlags MD5 | |||||
Binary BenchmarkFlags Source # | |||||
Defined in Distribution.Simple.Setup.Benchmark Methods put :: BenchmarkFlags -> Put # get :: Get BenchmarkFlags # putList :: [BenchmarkFlags] -> Put # | |||||
Monoid BenchmarkFlags Source # | |||||
Defined in Distribution.Simple.Setup.Benchmark Methods mappend :: BenchmarkFlags -> BenchmarkFlags -> BenchmarkFlags # mconcat :: [BenchmarkFlags] -> BenchmarkFlags # | |||||
Semigroup BenchmarkFlags Source # | |||||
Defined in Distribution.Simple.Setup.Benchmark Methods (<>) :: BenchmarkFlags -> BenchmarkFlags -> BenchmarkFlags # sconcat :: NonEmpty BenchmarkFlags -> BenchmarkFlags # stimes :: Integral b => b -> BenchmarkFlags -> BenchmarkFlags # | |||||
Generic BenchmarkFlags Source # | |||||
Defined in Distribution.Simple.Setup.Benchmark Associated Types
Methods from :: BenchmarkFlags -> Rep BenchmarkFlags x # to :: Rep BenchmarkFlags x -> BenchmarkFlags # | |||||
Show BenchmarkFlags Source # | |||||
Defined in Distribution.Simple.Setup.Benchmark Methods showsPrec :: Int -> BenchmarkFlags -> ShowS # show :: BenchmarkFlags -> String # showList :: [BenchmarkFlags] -> ShowS # | |||||
type Rep BenchmarkFlags Source # | |||||
Defined in Distribution.Simple.Setup.Benchmark type Rep BenchmarkFlags = D1 ('MetaData "BenchmarkFlags" "Distribution.Simple.Setup.Benchmark" "Cabal-3.14.1.0-be50" 'False) (C1 ('MetaCons "BenchmarkFlags" 'PrefixI 'True) (S1 ('MetaSel ('Just "benchmarkCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: S1 ('MetaSel ('Just "benchmarkOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PathTemplate]))) |
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 | |||||
Binary CopyDest Source # | |||||
Generic CopyDest Source # | |||||
Defined in Distribution.Simple.InstallDirs Associated Types
| |||||
Show 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.1.0-be50" '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
Applicative Flag Source # | |||||
Functor Flag Source # | |||||
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 # | |||||
Structured a => Structured (Flag a) Source # | |||||
Defined in Distribution.Simple.Flag | |||||
Binary a => Binary (Flag a) Source # | |||||
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 # | |||||
Defined in Distribution.Simple.Flag Associated Types
| |||||
Read a => Read (Flag a) Source # | |||||
Show a => Show (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.1.0-be50" '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
Structured BuildingWhat Source # | |||||
Defined in Distribution.Simple.Setup Methods structure :: Proxy BuildingWhat -> Structure Source # structureHash' :: Tagged BuildingWhat MD5 | |||||
Binary BuildingWhat Source # | |||||
Defined in Distribution.Simple.Setup | |||||
Generic BuildingWhat Source # | |||||
Defined in Distribution.Simple.Setup Associated Types
| |||||
Show BuildingWhat Source # | |||||
Defined in Distribution.Simple.Setup Methods showsPrec :: Int -> BuildingWhat -> ShowS # show :: BuildingWhat -> String # showList :: [BuildingWhat] -> ShowS # | |||||
type Rep BuildingWhat Source # | |||||
Defined in Distribution.Simple.Setup type Rep BuildingWhat = D1 ('MetaData "BuildingWhat" "Distribution.Simple.Setup" "Cabal-3.14.1.0-be50" 'False) ((C1 ('MetaCons "BuildNormal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildFlags)) :+: C1 ('MetaCons "BuildRepl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ReplFlags))) :+: (C1 ('MetaCons "BuildHaddock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HaddockFlags)) :+: C1 ('MetaCons "BuildHscolour" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HscolourFlags)))) |
buildingWhatWorkingDir :: BuildingWhat -> Maybe (SymbolicPath CWD ('Dir Pkg)) Source #
buildingWhatDistPref :: BuildingWhat -> SymbolicPath Pkg ('Dir Dist) Source #