cabal-install-3.10.2.1: The command-line interface for Cabal and Hackage.
Copyright(c) David Himmelstrup 2005
LicenseBSD-like
Maintainerlemmih@gmail.com
Stabilityprovisional
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Distribution.Client.Setup

Description

 
Synopsis

Documentation

data GlobalFlags Source #

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

Constructors

GlobalFlags 

Instances

Instances details
Monoid GlobalFlags Source # 
Instance details

Defined in Distribution.Client.GlobalFlags

Semigroup GlobalFlags Source # 
Instance details

Defined in Distribution.Client.GlobalFlags

Generic GlobalFlags Source # 
Instance details

Defined in Distribution.Client.GlobalFlags

Associated Types

type Rep GlobalFlags :: Type -> Type #

Show GlobalFlags Source # 
Instance details

Defined in Distribution.Client.GlobalFlags

type Rep GlobalFlags Source # 
Instance details

Defined in Distribution.Client.GlobalFlags

type Rep GlobalFlags = D1 ('MetaData "GlobalFlags" "Distribution.Client.GlobalFlags" "cabal-install-3.10.2.1-65TuIanu7V1TeNXBEsQf0" 'False) (C1 ('MetaCons "GlobalFlags" 'PrefixI 'True) (((S1 ('MetaSel ('Just "globalVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 ('MetaSel ('Just "globalNumericVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "globalConfigFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)))) :*: ((S1 ('MetaSel ('Just "globalConstraintsFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "globalRemoteRepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NubList RemoteRepo))) :*: (S1 ('MetaSel ('Just "globalCacheDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "globalLocalNoIndexRepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NubList LocalRepo))))) :*: ((S1 ('MetaSel ('Just "globalActiveRepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag ActiveRepos)) :*: (S1 ('MetaSel ('Just "globalLogsDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "globalIgnoreExpiry") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "globalHttpTransport") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: S1 ('MetaSel ('Just "globalNix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "globalStoreDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "globalProgPathExtra") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NubList FilePath)))))))

data RepoContext Source #

Access to repositories

Constructors

RepoContext 

Fields

  • repoContextRepos :: [Repo]

    All user-specified repositories

  • repoContextGetTransport :: IO HttpTransport

    Get the HTTP transport

    The transport will be initialized on the first call to this function.

    NOTE: It is important that we don't eagerly initialize the transport. Initializing the transport is not free, and especially in contexts where we don't know a priori whether or not we need the transport (for instance when using cabal in "nix mode") incurring the overhead of transport initialization on _every_ invocation (eg cabal build) is undesirable.

  • repoContextWithSecureRepo :: forall a. Repo -> (forall down. Repository down -> IO a) -> IO a

    Get the (initialized) secure repo

    (the Repo type itself is stateless and must remain so, because it must be serializable)

  • repoContextIgnoreExpiry :: Bool

    Should we ignore expiry times (when checking security)?

data ConfigFlags #

Flags to configure command.

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

Constructors

ConfigFlags 

Fields

Instances

Instances details
Structured ConfigFlags 
Instance details

Defined in Distribution.Simple.Setup

Monoid ConfigFlags 
Instance details

Defined in Distribution.Simple.Setup

Semigroup ConfigFlags 
Instance details

Defined in Distribution.Simple.Setup

Generic ConfigFlags 
Instance details

Defined in Distribution.Simple.Setup

Associated Types

type Rep ConfigFlags :: Type -> Type #

Read ConfigFlags 
Instance details

Defined in Distribution.Simple.Setup

Show ConfigFlags 
Instance details

Defined in Distribution.Simple.Setup

Binary ConfigFlags 
Instance details

Defined in Distribution.Simple.Setup

Eq ConfigFlags 
Instance details

Defined in Distribution.Simple.Setup

type Rep ConfigFlags 
Instance details

Defined in Distribution.Simple.Setup

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

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.

data ConfigExFlags Source #

cabal configure takes some extra flags beyond runghc Setup configure

Instances

Instances details
Monoid ConfigExFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Semigroup ConfigExFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Generic ConfigExFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Associated Types

type Rep ConfigExFlags :: Type -> Type #

Show ConfigExFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Eq ConfigExFlags Source # 
Instance details

Defined in Distribution.Client.Setup

type Rep ConfigExFlags Source # 
Instance details

Defined in Distribution.Client.Setup

data BuildFlags #

Instances

Instances details
Monoid BuildFlags 
Instance details

Defined in Distribution.Simple.Setup

Semigroup BuildFlags 
Instance details

Defined in Distribution.Simple.Setup

Generic BuildFlags 
Instance details

Defined in Distribution.Simple.Setup

Associated Types

type Rep BuildFlags :: Type -> Type #

Read BuildFlags 
Instance details

Defined in Distribution.Simple.Setup

Show BuildFlags 
Instance details

Defined in Distribution.Simple.Setup

type Rep BuildFlags 
Instance details

Defined in Distribution.Simple.Setup

type Rep BuildFlags = D1 ('MetaData "BuildFlags" "Distribution.Simple.Setup" "Cabal-3.10.2.1-GyzoJJgKHqN4rPN6ewqdAH" 'False) (C1 ('MetaCons "BuildFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "buildProgramPaths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, FilePath)]) :*: (S1 ('MetaSel ('Just "buildProgramArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, [String])]) :*: S1 ('MetaSel ('Just "buildDistPref") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)))) :*: ((S1 ('MetaSel ('Just "buildVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)) :*: S1 ('MetaSel ('Just "buildNumJobs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag (Maybe Int)))) :*: (S1 ('MetaSel ('Just "buildArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "buildCabalFilePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath))))))

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.

data InstallFlags Source #

Install takes the same flags as configure along with a few extras.

Instances

Instances details
Monoid InstallFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Semigroup InstallFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Generic InstallFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Associated Types

type Rep InstallFlags :: Type -> Type #

Show InstallFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Binary InstallFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Eq InstallFlags Source # 
Instance details

Defined in Distribution.Client.Setup

type Rep InstallFlags Source # 
Instance details

Defined in Distribution.Client.Setup

type Rep InstallFlags = D1 ('MetaData "InstallFlags" "Distribution.Client.Setup" "cabal-install-3.10.2.1-65TuIanu7V1TeNXBEsQf0" 'False) (C1 ('MetaCons "InstallFlags" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "installDocumentation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "installHaddockIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PathTemplate))) :*: (S1 ('MetaSel ('Just "installDest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag CopyDest)) :*: S1 ('MetaSel ('Just "installDryRun") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "installOnlyDownload") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "installMaxBackjumps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Int))) :*: (S1 ('MetaSel ('Just "installReorderGoals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag ReorderGoals)) :*: S1 ('MetaSel ('Just "installCountConflicts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag CountConflicts))))) :*: (((S1 ('MetaSel ('Just "installFineGrainedConflicts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FineGrainedConflicts)) :*: S1 ('MetaSel ('Just "installMinimizeConflictSet") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag MinimizeConflictSet))) :*: (S1 ('MetaSel ('Just "installIndependentGoals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag IndependentGoals)) :*: S1 ('MetaSel ('Just "installPreferOldest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PreferOldest)))) :*: ((S1 ('MetaSel ('Just "installShadowPkgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag ShadowPkgs)) :*: S1 ('MetaSel ('Just "installStrongFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag StrongFlags))) :*: (S1 ('MetaSel ('Just "installAllowBootLibInstalls") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag AllowBootLibInstalls)) :*: (S1 ('MetaSel ('Just "installOnlyConstrained") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag OnlyConstrained)) :*: S1 ('MetaSel ('Just "installReinstall") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))))))) :*: ((((S1 ('MetaSel ('Just "installAvoidReinstalls") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag AvoidReinstalls)) :*: S1 ('MetaSel ('Just "installOverrideReinstall") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "installUpgradeDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "installOnly") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "installOnlyDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "installIndexState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag TotalIndexState))) :*: (S1 ('MetaSel ('Just "installRootCmd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: S1 ('MetaSel ('Just "installSummaryFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NubList PathTemplate))))) :*: (((S1 ('MetaSel ('Just "installLogFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PathTemplate)) :*: S1 ('MetaSel ('Just "installBuildReports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag ReportLevel))) :*: (S1 ('MetaSel ('Just "installReportPlanningFailure") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "installSymlinkBinDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)))) :*: ((S1 ('MetaSel ('Just "installPerComponent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "installNumJobs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag (Maybe Int)))) :*: (S1 ('MetaSel ('Just "installKeepGoing") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 ('MetaSel ('Just "installRunTests") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "installOfflineMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))))))))

data ListFlags Source #

Instances

Instances details
Monoid ListFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Semigroup ListFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Generic ListFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Associated Types

type Rep ListFlags :: Type -> Type #

type Rep ListFlags Source # 
Instance details

Defined in Distribution.Client.Setup

type Rep ListFlags = D1 ('MetaData "ListFlags" "Distribution.Client.Setup" "cabal-install-3.10.2.1-65TuIanu7V1TeNXBEsQf0" 'False) (C1 ('MetaCons "ListFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "listInstalled") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: (S1 ('MetaSel ('Just "listSimpleOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "listCaseInsensitive") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: (S1 ('MetaSel ('Just "listVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)) :*: (S1 ('MetaSel ('Just "listPackageDBs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Maybe PackageDB]) :*: S1 ('MetaSel ('Just "listHcPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath))))))

data UpdateFlags Source #

Instances

Instances details
Generic UpdateFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Associated Types

type Rep UpdateFlags :: Type -> Type #

type Rep UpdateFlags Source # 
Instance details

Defined in Distribution.Client.Setup

type Rep UpdateFlags = D1 ('MetaData "UpdateFlags" "Distribution.Client.Setup" "cabal-install-3.10.2.1-65TuIanu7V1TeNXBEsQf0" '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))))

data InfoFlags Source #

Instances

Instances details
Monoid InfoFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Semigroup InfoFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Generic InfoFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Associated Types

type Rep InfoFlags :: Type -> Type #

type Rep InfoFlags Source # 
Instance details

Defined in Distribution.Client.Setup

type Rep InfoFlags = D1 ('MetaData "InfoFlags" "Distribution.Client.Setup" "cabal-install-3.10.2.1-65TuIanu7V1TeNXBEsQf0" '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])))

data GetFlags Source #

Instances

Instances details
Monoid GetFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Semigroup GetFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Generic GetFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Associated Types

type Rep GetFlags :: Type -> Type #

Methods

from :: GetFlags -> Rep GetFlags x #

to :: Rep GetFlags x -> GetFlags #

type Rep GetFlags Source # 
Instance details

Defined in Distribution.Client.Setup

type Rep GetFlags = D1 ('MetaData "GetFlags" "Distribution.Client.Setup" "cabal-install-3.10.2.1-65TuIanu7V1TeNXBEsQf0" 'False) (C1 ('MetaCons "GetFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "getDestDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: (S1 ('MetaSel ('Just "getOnlyPkgDescr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "getPristine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "getIndexState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag TotalIndexState)) :*: S1 ('MetaSel ('Just "getActiveRepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag ActiveRepos))) :*: (S1 ('MetaSel ('Just "getSourceRepository") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag (Maybe RepoKind))) :*: S1 ('MetaSel ('Just "getVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity))))))

data UploadFlags Source #

Instances

Instances details
Monoid UploadFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Semigroup UploadFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Generic UploadFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Associated Types

type Rep UploadFlags :: Type -> Type #

type Rep UploadFlags Source # 
Instance details

Defined in Distribution.Client.Setup

type Rep UploadFlags = D1 ('MetaData "UploadFlags" "Distribution.Client.Setup" "cabal-install-3.10.2.1-65TuIanu7V1TeNXBEsQf0" 'False) (C1 ('MetaCons "UploadFlags" 'PrefixI 'True) ((S1 ('MetaSel ('Just "uploadCandidate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag IsCandidate)) :*: (S1 ('MetaSel ('Just "uploadDoc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "uploadUsername") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Username)))) :*: (S1 ('MetaSel ('Just "uploadPassword") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Password)) :*: (S1 ('MetaSel ('Just "uploadPasswordCmd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [String])) :*: S1 ('MetaSel ('Just "uploadVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity))))))

data IsCandidate Source #

Is this a candidate package or a package to be published?

Constructors

IsCandidate 
IsPublished 

Instances

Instances details
Eq IsCandidate Source # 
Instance details

Defined in Distribution.Client.Setup

data ReportFlags Source #

Instances

Instances details
Monoid ReportFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Semigroup ReportFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Generic ReportFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Associated Types

type Rep ReportFlags :: Type -> Type #

type Rep ReportFlags Source # 
Instance details

Defined in Distribution.Client.Setup

type Rep ReportFlags = D1 ('MetaData "ReportFlags" "Distribution.Client.Setup" "cabal-install-3.10.2.1-65TuIanu7V1TeNXBEsQf0" 'False) (C1 ('MetaCons "ReportFlags" 'PrefixI 'True) (S1 ('MetaSel ('Just "reportUsername") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Username)) :*: (S1 ('MetaSel ('Just "reportPassword") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Password)) :*: S1 ('MetaSel ('Just "reportVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)))))

data InitFlags Source #

InitFlags is a subset of flags available in the .cabal file that represent options that are relevant to the init command process.

Instances

Instances details
Monoid InitFlags Source # 
Instance details

Defined in Distribution.Client.Init.Types

Semigroup InitFlags Source # 
Instance details

Defined in Distribution.Client.Init.Types

Generic InitFlags Source # 
Instance details

Defined in Distribution.Client.Init.Types

Associated Types

type Rep InitFlags :: Type -> Type #

Show InitFlags Source # 
Instance details

Defined in Distribution.Client.Init.Types

Eq InitFlags Source # 
Instance details

Defined in Distribution.Client.Init.Types

type Rep InitFlags Source # 
Instance details

Defined in Distribution.Client.Init.Types

type Rep InitFlags = D1 ('MetaData "InitFlags" "Distribution.Client.Init.Types" "cabal-install-3.10.2.1-65TuIanu7V1TeNXBEsQf0" 'False) (C1 ('MetaCons "InitFlags" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "interactive") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "quiet") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "packageDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "noComments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "minimal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "simpleProject") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))) :*: (S1 ('MetaSel ('Just "packageName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PackageName)) :*: S1 ('MetaSel ('Just "version") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Version))))) :*: (((S1 ('MetaSel ('Just "cabalVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag CabalSpecVersion)) :*: S1 ('MetaSel ('Just "license") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag SpecLicense))) :*: (S1 ('MetaSel ('Just "author") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: S1 ('MetaSel ('Just "email") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)))) :*: ((S1 ('MetaSel ('Just "homepage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: S1 ('MetaSel ('Just "synopsis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String))) :*: (S1 ('MetaSel ('Just "category") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag String)) :*: S1 ('MetaSel ('Just "extraSrc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [String])))))) :*: ((((S1 ('MetaSel ('Just "extraDoc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [String])) :*: S1 ('MetaSel ('Just "packageType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag PackageType))) :*: (S1 ('MetaSel ('Just "mainIs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath)) :*: S1 ('MetaSel ('Just "language") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Language)))) :*: ((S1 ('MetaSel ('Just "exposedModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [ModuleName])) :*: S1 ('MetaSel ('Just "otherModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [ModuleName]))) :*: (S1 ('MetaSel ('Just "otherExts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [Extension])) :*: S1 ('MetaSel ('Just "dependencies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [Dependency]))))) :*: (((S1 ('MetaSel ('Just "applicationDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [String])) :*: S1 ('MetaSel ('Just "sourceDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [String]))) :*: (S1 ('MetaSel ('Just "buildTools") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [String])) :*: S1 ('MetaSel ('Just "initializeTestSuite") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)))) :*: ((S1 ('MetaSel ('Just "testDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [String])) :*: S1 ('MetaSel ('Just "initHcPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag FilePath))) :*: (S1 ('MetaSel ('Just "initVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)) :*: S1 ('MetaSel ('Just "overwrite") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool))))))))

data ActAsSetupFlags Source #

Instances

Instances details
Monoid ActAsSetupFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Semigroup ActAsSetupFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Generic ActAsSetupFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Associated Types

type Rep ActAsSetupFlags :: Type -> Type #

type Rep ActAsSetupFlags Source # 
Instance details

Defined in Distribution.Client.Setup

type Rep ActAsSetupFlags = D1 ('MetaData "ActAsSetupFlags" "Distribution.Client.Setup" "cabal-install-3.10.2.1-65TuIanu7V1TeNXBEsQf0" 'False) (C1 ('MetaCons "ActAsSetupFlags" 'PrefixI 'True) (S1 ('MetaSel ('Just "actAsSetupBuildType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag BuildType))))

data UserConfigFlags Source #

Instances

Instances details
Monoid UserConfigFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Semigroup UserConfigFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Generic UserConfigFlags Source # 
Instance details

Defined in Distribution.Client.Setup

Associated Types

type Rep UserConfigFlags :: Type -> Type #

type Rep UserConfigFlags Source # 
Instance details

Defined in Distribution.Client.Setup

type Rep UserConfigFlags = D1 ('MetaData "UserConfigFlags" "Distribution.Client.Setup" "cabal-install-3.10.2.1-65TuIanu7V1TeNXBEsQf0" 'False) (C1 ('MetaCons "UserConfigFlags" 'PrefixI 'True) (S1 ('MetaSel ('Just "userConfigVerbosity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Verbosity)) :*: (S1 ('MetaSel ('Just "userConfigForce") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag Bool)) :*: S1 ('MetaSel ('Just "userConfigAppendLines") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag [String])))))

liftOptions :: (b -> a) -> (a -> b -> b) -> [OptionField a] -> [OptionField b] Source #