Copyright | (c) David Himmelstrup 2005 |
---|---|
License | BSD-like |
Maintainer | lemmih@gmail.com |
Stability | provisional |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Distribution.Client.Setup
Description
Synopsis
- globalCommand :: [Command action] -> CommandUI GlobalFlags
- data GlobalFlags = GlobalFlags {
- globalVersion :: Flag Bool
- globalNumericVersion :: Flag Bool
- globalConfigFile :: Flag FilePath
- globalConstraintsFile :: Flag FilePath
- globalRemoteRepos :: NubList RemoteRepo
- globalCacheDir :: Flag FilePath
- globalLocalNoIndexRepos :: NubList LocalRepo
- globalActiveRepos :: Flag ActiveRepos
- globalLogsDir :: Flag FilePath
- globalWorldFile :: Flag FilePath
- globalIgnoreExpiry :: Flag Bool
- globalHttpTransport :: Flag String
- globalNix :: Flag Bool
- globalStoreDir :: Flag FilePath
- globalProgPathExtra :: NubList FilePath
- defaultGlobalFlags :: GlobalFlags
- data RepoContext = RepoContext {
- repoContextRepos :: [Repo]
- repoContextGetTransport :: IO HttpTransport
- repoContextWithSecureRepo :: forall a. Repo -> (forall down. Repository down -> IO a) -> IO a
- repoContextIgnoreExpiry :: Bool
- withRepoContext :: Verbosity -> GlobalFlags -> (RepoContext -> IO a) -> IO a
- configureCommand :: CommandUI ConfigFlags
- 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]
- 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
- configUseResponseFiles :: Flag Bool
- configAllowDependingOnPrivateLibs :: Flag Bool
- configureOptions :: ShowOrParseArgs -> [OptionField ConfigFlags]
- filterConfigureFlags :: ConfigFlags -> Version -> ConfigFlags
- configPackageDB' :: ConfigFlags -> PackageDBStack
- configCompilerAux' :: ConfigFlags -> IO (Compiler, Platform, ProgramDb)
- configureExCommand :: CommandUI (ConfigFlags, ConfigExFlags)
- data ConfigExFlags = ConfigExFlags {
- configCabalVersion :: Flag Version
- configExConstraints :: [(UserConstraint, ConstraintSource)]
- configPreferences :: [PackageVersionConstraint]
- configSolver :: Flag PreSolver
- configAllowNewer :: Maybe AllowNewer
- configAllowOlder :: Maybe AllowOlder
- configWriteGhcEnvironmentFilesPolicy :: Flag WriteGhcEnvironmentFilesPolicy
- defaultConfigExFlags :: ConfigExFlags
- buildCommand :: CommandUI BuildFlags
- data BuildFlags = BuildFlags {
- buildProgramPaths :: [(String, FilePath)]
- buildProgramArgs :: [(String, [String])]
- buildDistPref :: Flag FilePath
- buildVerbosity :: Flag Verbosity
- buildNumJobs :: Flag (Maybe Int)
- buildArgs :: [String]
- buildCabalFilePath :: Flag FilePath
- filterTestFlags :: TestFlags -> Version -> TestFlags
- replCommand :: CommandUI ReplFlags
- testCommand :: CommandUI (BuildFlags, TestFlags)
- benchmarkCommand :: CommandUI (BuildFlags, BenchmarkFlags)
- testOptions :: ShowOrParseArgs -> [OptionField TestFlags]
- benchmarkOptions :: ShowOrParseArgs -> [OptionField BenchmarkFlags]
- configureExOptions :: ShowOrParseArgs -> ConstraintSource -> [OptionField ConfigExFlags]
- reconfigureCommand :: CommandUI (ConfigFlags, ConfigExFlags)
- installCommand :: CommandUI (ConfigFlags, ConfigExFlags, InstallFlags, HaddockFlags, TestFlags, BenchmarkFlags)
- data InstallFlags = InstallFlags {
- installDocumentation :: Flag Bool
- installHaddockIndex :: Flag PathTemplate
- installDest :: Flag CopyDest
- installDryRun :: Flag Bool
- installMaxBackjumps :: Flag Int
- installReorderGoals :: Flag ReorderGoals
- installCountConflicts :: Flag CountConflicts
- installFineGrainedConflicts :: Flag FineGrainedConflicts
- installMinimizeConflictSet :: Flag MinimizeConflictSet
- installIndependentGoals :: Flag IndependentGoals
- installShadowPkgs :: Flag ShadowPkgs
- installStrongFlags :: Flag StrongFlags
- installAllowBootLibInstalls :: Flag AllowBootLibInstalls
- installOnlyConstrained :: Flag OnlyConstrained
- installReinstall :: Flag Bool
- installAvoidReinstalls :: Flag AvoidReinstalls
- installOverrideReinstall :: Flag Bool
- installUpgradeDeps :: Flag Bool
- installOnly :: Flag Bool
- installOnlyDeps :: Flag Bool
- installIndexState :: Flag TotalIndexState
- installRootCmd :: Flag String
- installSummaryFile :: NubList PathTemplate
- installLogFile :: Flag PathTemplate
- installBuildReports :: Flag ReportLevel
- installReportPlanningFailure :: Flag Bool
- installSymlinkBinDir :: Flag FilePath
- installPerComponent :: Flag Bool
- installOneShot :: Flag Bool
- installNumJobs :: Flag (Maybe Int)
- installKeepGoing :: Flag Bool
- installRunTests :: Flag Bool
- installOfflineMode :: Flag Bool
- installOptions :: ShowOrParseArgs -> [OptionField InstallFlags]
- defaultInstallFlags :: InstallFlags
- filterHaddockArgs :: [String] -> Version -> [String]
- filterHaddockFlags :: HaddockFlags -> Version -> HaddockFlags
- haddockOptions :: ShowOrParseArgs -> [OptionField HaddockFlags]
- defaultSolver :: PreSolver
- defaultMaxBackjumps :: Int
- listCommand :: CommandUI ListFlags
- data ListFlags = ListFlags {
- listInstalled :: Flag Bool
- listSimpleOutput :: Flag Bool
- listCaseInsensitive :: Flag Bool
- listVerbosity :: Flag Verbosity
- listPackageDBs :: [Maybe PackageDB]
- listHcPath :: Flag FilePath
- listNeedsCompiler :: ListFlags -> Bool
- updateCommand :: CommandUI UpdateFlags
- data UpdateFlags = UpdateFlags {
- updateVerbosity :: Flag Verbosity
- updateIndexState :: Flag TotalIndexState
- defaultUpdateFlags :: UpdateFlags
- infoCommand :: CommandUI InfoFlags
- data InfoFlags = InfoFlags {
- infoVerbosity :: Flag Verbosity
- infoPackageDBs :: [Maybe PackageDB]
- fetchCommand :: CommandUI FetchFlags
- data FetchFlags = FetchFlags {
- fetchDeps :: Flag Bool
- fetchDryRun :: Flag Bool
- fetchSolver :: Flag PreSolver
- fetchMaxBackjumps :: Flag Int
- fetchReorderGoals :: Flag ReorderGoals
- fetchCountConflicts :: Flag CountConflicts
- fetchFineGrainedConflicts :: Flag FineGrainedConflicts
- fetchMinimizeConflictSet :: Flag MinimizeConflictSet
- fetchIndependentGoals :: Flag IndependentGoals
- fetchShadowPkgs :: Flag ShadowPkgs
- fetchStrongFlags :: Flag StrongFlags
- fetchAllowBootLibInstalls :: Flag AllowBootLibInstalls
- fetchOnlyConstrained :: Flag OnlyConstrained
- fetchTests :: Flag Bool
- fetchBenchmarks :: Flag Bool
- fetchVerbosity :: Flag Verbosity
- freezeCommand :: CommandUI FreezeFlags
- data FreezeFlags = FreezeFlags {
- freezeDryRun :: Flag Bool
- freezeTests :: Flag Bool
- freezeBenchmarks :: Flag Bool
- freezeSolver :: Flag PreSolver
- freezeMaxBackjumps :: Flag Int
- freezeReorderGoals :: Flag ReorderGoals
- freezeCountConflicts :: Flag CountConflicts
- freezeFineGrainedConflicts :: Flag FineGrainedConflicts
- freezeMinimizeConflictSet :: Flag MinimizeConflictSet
- freezeIndependentGoals :: Flag IndependentGoals
- freezeShadowPkgs :: Flag ShadowPkgs
- freezeStrongFlags :: Flag StrongFlags
- freezeAllowBootLibInstalls :: Flag AllowBootLibInstalls
- freezeOnlyConstrained :: Flag OnlyConstrained
- freezeVerbosity :: Flag Verbosity
- genBoundsCommand :: CommandUI FreezeFlags
- outdatedCommand :: CommandUI OutdatedFlags
- data OutdatedFlags = OutdatedFlags {
- outdatedVerbosity :: Flag Verbosity
- outdatedFreezeFile :: Flag Bool
- outdatedNewFreezeFile :: Flag Bool
- outdatedProjectFile :: Flag FilePath
- outdatedSimpleOutput :: Flag Bool
- outdatedExitCode :: Flag Bool
- outdatedQuiet :: Flag Bool
- outdatedIgnore :: [PackageName]
- outdatedMinor :: Maybe IgnoreMajorVersionBumps
- data IgnoreMajorVersionBumps
- = IgnoreMajorVersionBumpsNone
- | IgnoreMajorVersionBumpsAll
- | IgnoreMajorVersionBumpsSome [PackageName]
- getCommand :: CommandUI GetFlags
- unpackCommand :: CommandUI GetFlags
- data GetFlags = GetFlags {
- getDestDir :: Flag FilePath
- getPristine :: Flag Bool
- getIndexState :: Flag TotalIndexState
- getActiveRepos :: Flag ActiveRepos
- getSourceRepository :: Flag (Maybe RepoKind)
- getVerbosity :: Flag Verbosity
- checkCommand :: CommandUI (Flag Verbosity)
- formatCommand :: CommandUI (Flag Verbosity)
- uploadCommand :: CommandUI UploadFlags
- data UploadFlags = UploadFlags {
- uploadCandidate :: Flag IsCandidate
- uploadDoc :: Flag Bool
- uploadUsername :: Flag Username
- uploadPassword :: Flag Password
- uploadPasswordCmd :: Flag [String]
- uploadVerbosity :: Flag Verbosity
- data IsCandidate
- reportCommand :: CommandUI ReportFlags
- data ReportFlags = ReportFlags {
- reportUsername :: Flag Username
- reportPassword :: Flag Password
- reportVerbosity :: Flag Verbosity
- runCommand :: CommandUI BuildFlags
- initCommand :: CommandUI InitFlags
- initOptions :: ShowOrParseArgs -> [OptionField InitFlags]
- data InitFlags = InitFlags {
- interactive :: Flag Bool
- quiet :: Flag Bool
- packageDir :: Flag FilePath
- noComments :: Flag Bool
- minimal :: Flag Bool
- simpleProject :: Flag Bool
- packageName :: Flag PackageName
- version :: Flag Version
- cabalVersion :: Flag CabalSpecVersion
- license :: Flag License
- author :: Flag String
- email :: Flag String
- homepage :: Flag String
- synopsis :: Flag String
- category :: Flag (Either String Category)
- extraSrc :: Maybe [String]
- packageType :: Flag PackageType
- mainIs :: Flag FilePath
- language :: Flag Language
- exposedModules :: Maybe [ModuleName]
- otherModules :: Maybe [ModuleName]
- otherExts :: Maybe [Extension]
- dependencies :: Maybe [Dependency]
- applicationDirs :: Maybe [String]
- sourceDirs :: Maybe [String]
- buildTools :: Maybe [String]
- initializeTestSuite :: Flag Bool
- testDirs :: Maybe [String]
- initHcPath :: Flag FilePath
- initVerbosity :: Flag Verbosity
- overwrite :: Flag Bool
- actAsSetupCommand :: CommandUI ActAsSetupFlags
- data ActAsSetupFlags = ActAsSetupFlags {
- actAsSetupBuildType :: Flag BuildType
- execCommand :: CommandUI ExecFlags
- data ExecFlags = ExecFlags {
- execVerbosity :: Flag Verbosity
- execDistPref :: Flag FilePath
- defaultExecFlags :: ExecFlags
- userConfigCommand :: CommandUI UserConfigFlags
- data UserConfigFlags = UserConfigFlags {
- userConfigVerbosity :: Flag Verbosity
- userConfigForce :: Flag Bool
- userConfigAppendLines :: Flag [String]
- manpageCommand :: CommandUI ManpageFlags
- haddockCommand :: CommandUI HaddockFlags
- cleanCommand :: CommandUI CleanFlags
- doctestCommand :: CommandUI DoctestFlags
- copyCommand :: CommandUI CopyFlags
- registerCommand :: CommandUI RegisterFlags
- parsePackageArgs :: [String] -> Either String [PackageVersionConstraint]
- liftOptions :: (b -> a) -> (a -> b -> b) -> [OptionField a] -> [OptionField b]
- yesNoOpt :: ShowOrParseArgs -> MkOptDescr (b -> Flag Bool) (Flag Bool -> b -> b) b
Documentation
globalCommand :: [Command action] -> CommandUI GlobalFlags Source #
data GlobalFlags Source #
Flags that apply at the top level, not to any sub-command.
Constructors
GlobalFlags | |
Fields
|
Instances
data RepoContext Source #
Access to repositories
Constructors
RepoContext | |
Fields
|
withRepoContext :: Verbosity -> GlobalFlags -> (RepoContext -> IO a) -> IO a Source #
configureCommand :: CommandUI ConfigFlags Source #
data ConfigFlags #
Constructors
Instances
configureOptions :: ShowOrParseArgs -> [OptionField ConfigFlags] Source #
filterConfigureFlags :: ConfigFlags -> Version -> ConfigFlags Source #
Given some ConfigFlags
for the version of Cabal that
cabal-install was built with, and a target older Version
of
Cabal that we want to pass these flags to, convert the
flags into a form that will be accepted by the older
Setup script. Generally speaking, this just means filtering
out flags that the old Cabal library doesn't understand, but
in some cases it may also mean "emulating" a feature using
some more legacy flags.
configPackageDB' :: ConfigFlags -> PackageDBStack Source #
Get the package database settings from ConfigFlags
, accounting for
--package-db
and --user
flags.
configCompilerAux' :: ConfigFlags -> IO (Compiler, Platform, ProgramDb) Source #
Configure the compiler, but reduce verbosity during this step.
configureExCommand :: CommandUI (ConfigFlags, ConfigExFlags) Source #
data ConfigExFlags Source #
cabal configure takes some extra flags beyond runghc Setup configure
Constructors
ConfigExFlags | |
Fields
|
Instances
buildCommand :: CommandUI BuildFlags Source #
data BuildFlags #
Constructors
BuildFlags | |
Fields
|
Instances
filterTestFlags :: TestFlags -> Version -> TestFlags Source #
Given some TestFlags
for the version of Cabal that
cabal-install was built with, and a target older Version
of
Cabal that we want to pass these flags to, convert the
flags into a form that will be accepted by the older
Setup script. Generally speaking, this just means filtering
out flags that the old Cabal library doesn't understand, but
in some cases it may also mean "emulating" a feature using
some more legacy flags.
replCommand :: CommandUI ReplFlags Source #
testCommand :: CommandUI (BuildFlags, TestFlags) Source #
benchmarkCommand :: CommandUI (BuildFlags, BenchmarkFlags) Source #
testOptions :: ShowOrParseArgs -> [OptionField TestFlags] Source #
benchmarkOptions :: ShowOrParseArgs -> [OptionField BenchmarkFlags] Source #
configureExOptions :: ShowOrParseArgs -> ConstraintSource -> [OptionField ConfigExFlags] Source #
reconfigureCommand :: CommandUI (ConfigFlags, ConfigExFlags) Source #
installCommand :: CommandUI (ConfigFlags, ConfigExFlags, InstallFlags, HaddockFlags, TestFlags, BenchmarkFlags) Source #
data InstallFlags Source #
Install takes the same flags as configure along with a few extras.
Constructors
Instances
Eq InstallFlags Source # | |
Defined in Distribution.Client.Setup | |
Show InstallFlags Source # | |
Defined in Distribution.Client.Setup Methods showsPrec :: Int -> InstallFlags -> ShowS # show :: InstallFlags -> String # showList :: [InstallFlags] -> ShowS # | |
Generic InstallFlags Source # | |
Defined in Distribution.Client.Setup Associated Types type Rep InstallFlags :: Type -> Type # | |
Semigroup InstallFlags Source # | |
Defined in Distribution.Client.Setup Methods (<>) :: InstallFlags -> InstallFlags -> InstallFlags # sconcat :: NonEmpty InstallFlags -> InstallFlags # stimes :: Integral b => b -> InstallFlags -> InstallFlags # | |
Monoid InstallFlags Source # | |
Defined in Distribution.Client.Setup Methods mempty :: InstallFlags # mappend :: InstallFlags -> InstallFlags -> InstallFlags # mconcat :: [InstallFlags] -> InstallFlags # | |
Binary InstallFlags Source # | |
Defined in Distribution.Client.Setup | |
type Rep InstallFlags Source # | |
Defined in Distribution.Client.Setup |
installOptions :: ShowOrParseArgs -> [OptionField InstallFlags] Source #
filterHaddockArgs :: [String] -> Version -> [String] Source #
filterHaddockFlags :: HaddockFlags -> Version -> HaddockFlags Source #
haddockOptions :: ShowOrParseArgs -> [OptionField HaddockFlags] Source #
defaultSolver :: PreSolver Source #
listCommand :: CommandUI ListFlags Source #
Constructors
ListFlags | |
Fields
|
Instances
listNeedsCompiler :: ListFlags -> Bool Source #
updateCommand :: CommandUI UpdateFlags Source #
data UpdateFlags Source #
Constructors
UpdateFlags | |
Fields
|
Instances
Generic UpdateFlags Source # | |
Defined in Distribution.Client.Setup Associated Types type Rep UpdateFlags :: Type -> Type # | |
type Rep UpdateFlags Source # | |
Defined in Distribution.Client.Setup type Rep UpdateFlags = D1 ('MetaData "UpdateFlags" "Distribution.Client.Setup" "hackport-0.7.2.1-1OygFJYGTmY8Q1y3r3WxcM-hackport-external-libs-cabal-install" 'False) (C1 ('MetaCons "UpdateFlags" 'PrefixI 'True) (S1 ('MetaSel ('Just "updateVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)) :*: S1 ('MetaSel ('Just "updateIndexState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag TotalIndexState)))) |
infoCommand :: CommandUI InfoFlags Source #
Constructors
InfoFlags | |
Fields
|
Instances
Generic InfoFlags Source # | |
Semigroup InfoFlags Source # | |
Monoid InfoFlags Source # | |
type Rep InfoFlags Source # | |
Defined in Distribution.Client.Setup type Rep InfoFlags = D1 ('MetaData "InfoFlags" "Distribution.Client.Setup" "hackport-0.7.2.1-1OygFJYGTmY8Q1y3r3WxcM-hackport-external-libs-cabal-install" 'False) (C1 ('MetaCons "InfoFlags" 'PrefixI 'True) (S1 ('MetaSel ('Just "infoVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)) :*: S1 ('MetaSel ('Just "infoPackageDBs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Maybe PackageDB]))) |
fetchCommand :: CommandUI FetchFlags Source #
data FetchFlags Source #
Constructors
FetchFlags | |
Fields
|
freezeCommand :: CommandUI FreezeFlags Source #
data FreezeFlags Source #
Constructors
FreezeFlags | |
Fields
|
genBoundsCommand :: CommandUI FreezeFlags Source #
outdatedCommand :: CommandUI OutdatedFlags Source #
data OutdatedFlags Source #
Constructors
OutdatedFlags | |
Fields
|
data IgnoreMajorVersionBumps Source #
Constructors
IgnoreMajorVersionBumpsNone | |
IgnoreMajorVersionBumpsAll | |
IgnoreMajorVersionBumpsSome [PackageName] |
Instances
Semigroup IgnoreMajorVersionBumps Source # | |
Defined in Distribution.Client.Setup Methods (<>) :: IgnoreMajorVersionBumps -> IgnoreMajorVersionBumps -> IgnoreMajorVersionBumps # sconcat :: NonEmpty IgnoreMajorVersionBumps -> IgnoreMajorVersionBumps # stimes :: Integral b => b -> IgnoreMajorVersionBumps -> IgnoreMajorVersionBumps # | |
Monoid IgnoreMajorVersionBumps Source # | |
Defined in Distribution.Client.Setup |
getCommand :: CommandUI GetFlags Source #
unpackCommand :: CommandUI GetFlags Source #
Constructors
GetFlags | |
Fields
|
Instances
checkCommand :: CommandUI (Flag Verbosity) Source #
formatCommand :: CommandUI (Flag Verbosity) Source #
uploadCommand :: CommandUI UploadFlags Source #
data UploadFlags Source #
Constructors
UploadFlags | |
Fields
|
Instances
Generic UploadFlags Source # | |
Defined in Distribution.Client.Setup Associated Types type Rep UploadFlags :: Type -> Type # | |
Semigroup UploadFlags Source # | |
Defined in Distribution.Client.Setup Methods (<>) :: UploadFlags -> UploadFlags -> UploadFlags # sconcat :: NonEmpty UploadFlags -> UploadFlags # stimes :: Integral b => b -> UploadFlags -> UploadFlags # | |
Monoid UploadFlags Source # | |
Defined in Distribution.Client.Setup Methods mempty :: UploadFlags # mappend :: UploadFlags -> UploadFlags -> UploadFlags # mconcat :: [UploadFlags] -> UploadFlags # | |
type Rep UploadFlags Source # | |
Defined in Distribution.Client.Setup |
data IsCandidate Source #
Is this a candidate package or a package to be published?
Constructors
IsCandidate | |
IsPublished |
Instances
Eq IsCandidate Source # | |
Defined in Distribution.Client.Setup |
reportCommand :: CommandUI ReportFlags Source #
data ReportFlags Source #
Constructors
ReportFlags | |
Fields
|
Instances
Generic ReportFlags Source # | |
Defined in Distribution.Client.Setup Associated Types type Rep ReportFlags :: Type -> Type # | |
Semigroup ReportFlags Source # | |
Defined in Distribution.Client.Setup Methods (<>) :: ReportFlags -> ReportFlags -> ReportFlags # sconcat :: NonEmpty ReportFlags -> ReportFlags # stimes :: Integral b => b -> ReportFlags -> ReportFlags # | |
Monoid ReportFlags Source # | |
Defined in Distribution.Client.Setup Methods mempty :: ReportFlags # mappend :: ReportFlags -> ReportFlags -> ReportFlags # mconcat :: [ReportFlags] -> ReportFlags # | |
type Rep ReportFlags Source # | |
Defined in Distribution.Client.Setup |
runCommand :: CommandUI BuildFlags Source #
initCommand :: CommandUI InitFlags Source #
initOptions :: ShowOrParseArgs -> [OptionField InitFlags] Source #
InitFlags is really just a simple type to represent certain portions of a .cabal file. Rather than have a flag for EVERY possible field, we just have one for each field that the user is likely to want and/or that we are likely to be able to intelligently guess.
Constructors
InitFlags | |
Fields
|
actAsSetupCommand :: CommandUI ActAsSetupFlags Source #
data ActAsSetupFlags Source #
Constructors
ActAsSetupFlags | |
Fields
|
Instances
execCommand :: CommandUI ExecFlags Source #
Constructors
ExecFlags | |
Fields
|
Instances
Generic ExecFlags Source # | |
Semigroup ExecFlags Source # | |
Monoid ExecFlags Source # | |
type Rep ExecFlags Source # | |
Defined in Distribution.Client.Setup type Rep ExecFlags = D1 ('MetaData "ExecFlags" "Distribution.Client.Setup" "hackport-0.7.2.1-1OygFJYGTmY8Q1y3r3WxcM-hackport-external-libs-cabal-install" 'False) (C1 ('MetaCons "ExecFlags" 'PrefixI 'True) (S1 ('MetaSel ('Just "execVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)) :*: S1 ('MetaSel ('Just "execDistPref") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)))) |
userConfigCommand :: CommandUI UserConfigFlags Source #
data UserConfigFlags Source #
Constructors
UserConfigFlags | |
Fields
|
Instances
manpageCommand :: CommandUI ManpageFlags Source #
haddockCommand :: CommandUI HaddockFlags Source #
cleanCommand :: CommandUI CleanFlags Source #
doctestCommand :: CommandUI DoctestFlags Source #
copyCommand :: CommandUI CopyFlags Source #
registerCommand :: CommandUI RegisterFlags Source #
liftOptions :: (b -> a) -> (a -> b -> b) -> [OptionField a] -> [OptionField b] Source #