Safe Haskell | None |
---|---|
Language | Haskell2010 |
Distribution.Simple.SetupHooks
Description
This module defines the interface for the Hooks
build-type
.
To write a package that implements build-type: Hooks
, you should define
a module SetupHooks.hs
which exports a value setupHooks ::
.
This is a record that declares actions that should be hooked into the
cabal build process.SetupHooks
See SetupHooks
for more details.
Synopsis
- data SetupHooks = SetupHooks {}
- noSetupHooks :: SetupHooks
- data ConfigureHooks = ConfigureHooks {}
- noConfigureHooks :: ConfigureHooks
- data PreConfPackageInputs = PreConfPackageInputs {}
- data PreConfPackageOutputs = PreConfPackageOutputs {
- buildOptions :: BuildOptions
- extraConfiguredProgs :: ConfiguredProgs
- noPreConfPackageOutputs :: PreConfPackageInputs -> PreConfPackageOutputs
- type PreConfPackageHook = PreConfPackageInputs -> IO PreConfPackageOutputs
- data PostConfPackageInputs = PostConfPackageInputs {}
- type PostConfPackageHook = PostConfPackageInputs -> IO ()
- data PreConfComponentInputs = PreConfComponentInputs {}
- data PreConfComponentOutputs = PreConfComponentOutputs {}
- noPreConfComponentOutputs :: PreConfComponentInputs -> PreConfComponentOutputs
- type PreConfComponentHook = PreConfComponentInputs -> IO PreConfComponentOutputs
- newtype ComponentDiff = ComponentDiff {}
- emptyComponentDiff :: ComponentName -> ComponentDiff
- buildInfoComponentDiff :: ComponentName -> BuildInfo -> ComponentDiff
- type LibraryDiff = Library
- type ForeignLibDiff = ForeignLib
- type ExecutableDiff = Executable
- type TestSuiteDiff = TestSuite
- type BenchmarkDiff = Benchmark
- type BuildInfoDiff = BuildInfo
- data BuildHooks = BuildHooks {}
- noBuildHooks :: BuildHooks
- data BuildingWhat
- buildingWhatVerbosity :: BuildingWhat -> Verbosity
- buildingWhatDistPref :: BuildingWhat -> SymbolicPath Pkg ('Dir Dist)
- data PreBuildComponentInputs = PreBuildComponentInputs {}
- type PreBuildComponentRules = Rules PreBuildComponentInputs
- data PostBuildComponentInputs = PostBuildComponentInputs {}
- type PostBuildComponentHook = PostBuildComponentInputs -> IO ()
- data Rules env
- rules :: StaticPtr label -> (env -> RulesM ()) -> Rules env
- noRules :: RulesM ()
- type Rule = RuleData 'User
- data Dependency
- data RuleOutput = RuleOutput {
- outputOfRule :: !RuleId
- outputIndex :: !Word
- data RuleId
- staticRule :: Typeable arg => Command arg (IO ()) -> [Dependency] -> NonEmpty Location -> Rule
- dynamicRule :: (Typeable depsArg, Typeable depsRes, Typeable arg) => StaticPtr (Dict (Binary depsRes, Show depsRes, Eq depsRes)) -> Command depsArg (IO ([Dependency], depsRes)) -> Command arg (depsRes -> IO ()) -> [Dependency] -> NonEmpty Location -> Rule
- data Location where
- location :: Location -> SymbolicPath Pkg 'File
- autogenComponentModulesDir :: LocalBuildInfo -> ComponentLocalBuildInfo -> SymbolicPath Pkg ('Dir Source)
- componentBuildDir :: LocalBuildInfo -> ComponentLocalBuildInfo -> SymbolicPath Pkg ('Dir Build)
- data RuleCommands (scope :: Scope) (deps :: Scope -> Type -> Type -> Type) (ruleCmd :: Scope -> Type -> Type -> Type) where
- StaticRuleCommand :: forall arg (deps :: Scope -> Type -> Type -> Type) (ruleCmd :: Scope -> Type -> Type -> Type) (scope :: Scope). If (scope == 'System) (arg ~ ByteString) () => {..} -> RuleCommands scope deps ruleCmd
- DynamicRuleCommands :: forall depsArg depsRes arg (deps :: Scope -> Type -> Type -> Type) (ruleCmd :: Scope -> Type -> Type -> Type) (scope :: Scope). If (scope == 'System) (depsArg ~ ByteString, depsRes ~ ByteString, arg ~ ByteString) () => {..} -> RuleCommands scope deps ruleCmd
- type Command = CommandData 'User
- mkCommand :: StaticPtr (Dict (Binary arg, Show arg)) -> StaticPtr (arg -> res) -> arg -> Command arg res
- data Dict c where
- type RulesM a = RulesT IO a
- registerRule :: ShortText -> Rule -> RulesM RuleId
- registerRule_ :: ShortText -> Rule -> RulesT IO ()
- addRuleMonitors :: forall (m :: Type -> Type). Monad m => [MonitorFilePath] -> RulesT m ()
- data Glob
- data MonitorFilePath
- data FilePathRoot
- data MonitorKindFile
- data MonitorKindDir
- data RootedGlob = RootedGlob FilePathRoot Glob
- monitorDirectory :: FilePath -> MonitorFilePath
- monitorDirectoryExistence :: FilePath -> MonitorFilePath
- monitorFile :: FilePath -> MonitorFilePath
- monitorFileExistence :: FilePath -> MonitorFilePath
- monitorFileGlob :: RootedGlob -> MonitorFilePath
- monitorFileGlobExistence :: RootedGlob -> MonitorFilePath
- monitorFileHashed :: FilePath -> MonitorFilePath
- monitorFileHashedSearchPath :: [FilePath] -> FilePath -> [MonitorFilePath]
- monitorFileOrDirectory :: FilePath -> MonitorFilePath
- monitorFileSearchPath :: [FilePath] -> FilePath -> [MonitorFilePath]
- monitorNonExistentDirectory :: FilePath -> MonitorFilePath
- monitorNonExistentFile :: FilePath -> MonitorFilePath
- data InstallHooks = InstallHooks {}
- noInstallHooks :: InstallHooks
- data InstallComponentInputs = InstallComponentInputs {}
- type InstallComponentHook = InstallComponentInputs -> IO ()
- 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 {
- 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 {
- 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 {
- 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
- 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 {
- data HscolourFlags where
- HscolourFlags {
- hscolourCommonFlags :: !CommonSetupFlags
- hscolourCSS :: Flag FilePath
- hscolourExecutables :: Flag Bool
- hscolourTestSuites :: Flag Bool
- hscolourBenchmarks :: Flag Bool
- hscolourForeignLibs :: Flag Bool
- pattern HscolourCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg ('Dir Dist)) -> Flag (SymbolicPath CWD ('Dir Pkg)) -> Flag (SymbolicPath Pkg 'File) -> [String] -> HscolourFlags
- HscolourFlags {
- data CopyFlags where
- CopyFlags {
- copyCommonFlags :: !CommonSetupFlags
- copyDest :: Flag CopyDest
- pattern CopyCommonFlags :: Flag Verbosity -> Flag (SymbolicPath Pkg ('Dir Dist)) -> Flag (SymbolicPath CWD ('Dir Pkg)) -> Flag (SymbolicPath Pkg 'File) -> [String] -> CopyFlags
- CopyFlags {
- installFileGlob :: Verbosity -> CabalSpecVersion -> Maybe (SymbolicPath CWD ('Dir Pkg)) -> (Maybe (SymbolicPath CWD ('Dir DataDir)), SymbolicPath Pkg ('Dir DataDir)) -> RelativePath DataDir 'File -> IO ()
- data Program = Program {
- programName :: String
- programFindLocation :: Verbosity -> ProgramSearchPath -> IO (Maybe (FilePath, [FilePath]))
- programFindVersion :: Verbosity -> FilePath -> IO (Maybe Version)
- programPostConf :: Verbosity -> ConfiguredProgram -> IO ConfiguredProgram
- programNormaliseArgs :: Maybe Version -> PackageDescription -> [String] -> [String]
- data ConfiguredProgram = ConfiguredProgram {
- programId :: String
- programVersion :: Maybe Version
- programDefaultArgs :: [String]
- programOverrideArgs :: [String]
- programOverrideEnv :: [(String, Maybe String)]
- programProperties :: Map String String
- programLocation :: ProgramLocation
- programMonitorFiles :: [FilePath]
- type ProgArg = String
- data ProgramLocation
- = UserSpecified { }
- | FoundOnSystem { }
- data ProgramDb
- addKnownPrograms :: [Program] -> ProgramDb -> ProgramDb
- configureUnconfiguredProgram :: Verbosity -> Program -> ProgramDb -> IO (Maybe ConfiguredProgram)
- simpleProgram :: String -> Program
- data Verbosity
- data Compiler = Compiler {
- compilerId :: CompilerId
- compilerAbiTag :: AbiTag
- compilerCompat :: [CompilerId]
- compilerLanguages :: [(Language, CompilerFlag)]
- compilerExtensions :: [(Extension, Maybe CompilerFlag)]
- compilerProperties :: Map String String
- data Platform = Platform Arch OS
- newtype Suffix = Suffix String
- data LocalBuildConfig
- data LocalBuildInfo
- data PackageBuildDescr
- data PackageDescription = PackageDescription {
- specVersion :: CabalSpecVersion
- package :: PackageIdentifier
- licenseRaw :: Either License License
- licenseFiles :: [RelativePath Pkg 'File]
- copyright :: !ShortText
- maintainer :: !ShortText
- author :: !ShortText
- stability :: !ShortText
- testedWith :: [(CompilerFlavor, VersionRange)]
- homepage :: !ShortText
- pkgUrl :: !ShortText
- bugReports :: !ShortText
- sourceRepos :: [SourceRepo]
- synopsis :: !ShortText
- description :: !ShortText
- category :: !ShortText
- customFieldsPD :: [(String, String)]
- buildTypeRaw :: Maybe BuildType
- setupBuildInfo :: Maybe SetupBuildInfo
- library :: Maybe Library
- subLibraries :: [Library]
- executables :: [Executable]
- foreignLibs :: [ForeignLib]
- testSuites :: [TestSuite]
- benchmarks :: [Benchmark]
- dataFiles :: [RelativePath DataDir 'File]
- dataDir :: SymbolicPath Pkg ('Dir DataDir)
- extraSrcFiles :: [RelativePath Pkg 'File]
- extraTmpFiles :: [RelativePath Pkg 'File]
- extraDocFiles :: [RelativePath Pkg 'File]
- extraFiles :: [RelativePath Pkg 'File]
- data Component
- data ComponentName where
- CLibName LibraryName
- CNotLibName NotLibComponentName
- pattern CBenchName :: UnqualComponentName -> ComponentName
- pattern CExeName :: UnqualComponentName -> ComponentName
- pattern CFLibName :: UnqualComponentName -> ComponentName
- pattern CTestName :: UnqualComponentName -> ComponentName
- componentName :: Component -> ComponentName
- data BuildInfo = BuildInfo {
- buildable :: Bool
- buildTools :: [LegacyExeDependency]
- buildToolDepends :: [ExeDependency]
- cppOptions :: [String]
- asmOptions :: [String]
- cmmOptions :: [String]
- ccOptions :: [String]
- cxxOptions :: [String]
- jsppOptions :: [String]
- ldOptions :: [String]
- hsc2hsOptions :: [String]
- pkgconfigDepends :: [PkgconfigDependency]
- frameworks :: [RelativePath Framework 'File]
- extraFrameworkDirs :: [SymbolicPath Pkg ('Dir Framework)]
- asmSources :: [SymbolicPath Pkg 'File]
- cmmSources :: [SymbolicPath Pkg 'File]
- cSources :: [SymbolicPath Pkg 'File]
- cxxSources :: [SymbolicPath Pkg 'File]
- jsSources :: [SymbolicPath Pkg 'File]
- hsSourceDirs :: [SymbolicPath Pkg ('Dir Source)]
- otherModules :: [ModuleName]
- virtualModules :: [ModuleName]
- autogenModules :: [ModuleName]
- defaultLanguage :: Maybe Language
- otherLanguages :: [Language]
- defaultExtensions :: [Extension]
- otherExtensions :: [Extension]
- oldExtensions :: [Extension]
- extraLibs :: [String]
- extraLibsStatic :: [String]
- extraGHCiLibs :: [String]
- extraBundledLibs :: [String]
- extraLibFlavours :: [String]
- extraDynLibFlavours :: [String]
- extraLibDirs :: [SymbolicPath Pkg ('Dir Lib)]
- extraLibDirsStatic :: [SymbolicPath Pkg ('Dir Lib)]
- includeDirs :: [SymbolicPath Pkg ('Dir Include)]
- includes :: [SymbolicPath Include 'File]
- autogenIncludes :: [RelativePath Include 'File]
- installIncludes :: [RelativePath Include 'File]
- options :: PerCompilerFlavor [String]
- profOptions :: PerCompilerFlavor [String]
- sharedOptions :: PerCompilerFlavor [String]
- profSharedOptions :: PerCompilerFlavor [String]
- staticOptions :: PerCompilerFlavor [String]
- customFieldsBI :: [(String, String)]
- targetBuildDepends :: [Dependency]
- mixins :: [Mixin]
- emptyBuildInfo :: BuildInfo
- data TargetInfo = TargetInfo {}
- data ComponentLocalBuildInfo
- = LibComponentLocalBuildInfo {
- componentLocalName :: ComponentName
- componentComponentId :: ComponentId
- componentUnitId :: UnitId
- componentIsIndefinite_ :: Bool
- componentInstantiatedWith :: [(ModuleName, OpenModule)]
- componentPackageDeps :: [(UnitId, MungedPackageId)]
- componentIncludes :: [(OpenUnitId, ModuleRenaming)]
- componentExeDeps :: [UnitId]
- componentInternalDeps :: [UnitId]
- componentCompatPackageKey :: String
- componentCompatPackageName :: MungedPackageName
- componentExposedModules :: [ExposedModule]
- componentIsPublic :: Bool
- | FLibComponentLocalBuildInfo {
- componentLocalName :: ComponentName
- componentComponentId :: ComponentId
- componentUnitId :: UnitId
- componentPackageDeps :: [(UnitId, MungedPackageId)]
- componentIncludes :: [(OpenUnitId, ModuleRenaming)]
- componentExeDeps :: [UnitId]
- componentInternalDeps :: [UnitId]
- | ExeComponentLocalBuildInfo {
- componentLocalName :: ComponentName
- componentComponentId :: ComponentId
- componentUnitId :: UnitId
- componentPackageDeps :: [(UnitId, MungedPackageId)]
- componentIncludes :: [(OpenUnitId, ModuleRenaming)]
- componentExeDeps :: [UnitId]
- componentInternalDeps :: [UnitId]
- | TestComponentLocalBuildInfo {
- componentLocalName :: ComponentName
- componentComponentId :: ComponentId
- componentUnitId :: UnitId
- componentPackageDeps :: [(UnitId, MungedPackageId)]
- componentIncludes :: [(OpenUnitId, ModuleRenaming)]
- componentExeDeps :: [UnitId]
- componentInternalDeps :: [UnitId]
- | BenchComponentLocalBuildInfo {
- componentLocalName :: ComponentName
- componentComponentId :: ComponentId
- componentUnitId :: UnitId
- componentPackageDeps :: [(UnitId, MungedPackageId)]
- componentIncludes :: [(OpenUnitId, ModuleRenaming)]
- componentExeDeps :: [UnitId]
- componentInternalDeps :: [UnitId]
- = LibComponentLocalBuildInfo {
- data Library = Library {
- libName :: LibraryName
- exposedModules :: [ModuleName]
- reexportedModules :: [ModuleReexport]
- signatures :: [ModuleName]
- libExposed :: Bool
- libVisibility :: LibraryVisibility
- libBuildInfo :: BuildInfo
- data ForeignLib = ForeignLib {
- foreignLibName :: UnqualComponentName
- foreignLibType :: ForeignLibType
- foreignLibOptions :: [ForeignLibOption]
- foreignLibBuildInfo :: BuildInfo
- foreignLibVersionInfo :: Maybe LibVersionInfo
- foreignLibVersionLinux :: Maybe Version
- foreignLibModDefFile :: [RelativePath Source 'File]
- data Executable = Executable {
- exeName :: UnqualComponentName
- modulePath :: RelativePath Source 'File
- exeScope :: ExecutableScope
- buildInfo :: BuildInfo
- data TestSuite = TestSuite {
- testName :: UnqualComponentName
- testInterface :: TestSuiteInterface
- testBuildInfo :: BuildInfo
- testCodeGenerators :: [String]
- data Benchmark = Benchmark {
- benchmarkName :: UnqualComponentName
- benchmarkInterface :: BenchmarkInterface
- benchmarkBuildInfo :: BuildInfo
- data LibraryName
- = LMainLibName
- | LSubLibName UnqualComponentName
- emptyLibrary :: Library
- emptyForeignLib :: ForeignLib
- emptyExecutable :: Executable
- emptyTestSuite :: TestSuite
- emptyBenchmark :: Benchmark
Hooks
A Cabal package with Hooks
build-type
must define the Haskell module
SetupHooks
which defines a value setupHooks ::
.SetupHooks
These *setup hooks* allow package authors to customise the configuration and
building of a package by providing certain hooks that get folded into the
general package configuration and building logic within Cabal
.
This mechanism replaces the Custom
build-type
, providing better
integration with the rest of the Haskell ecosystem.
Usage example:
-- In your .cabal file build-type: Hooks custom-setup setup-depends: base >= 4.18 && < 5, Cabal-hooks >= 3.14 && < 3.15 The declared Cabal version should also be at least 3.14.
-- In SetupHooks.hs, next to your .cabal file module SetupHooks where import Distribution.Simple.SetupHooks ( SetupHooks, noSetupHooks ) setupHooks :: SetupHooks setupHooks = noSetupHooks { configureHooks = myConfigureHooks , buildHooks = myBuildHooks }
Note that SetupHooks
can be monoidally combined, e.g.:
module SetupHooks where import Distribution.Simple.SetupHooks import qualified SomeOtherLibrary ( setupHooks ) setupHooks :: SetupHooks setupHooks = SomeOtherLibrary.setupHooks <> mySetupHooks mySetupHooks :: SetupHooks mySetupHooks = ...
data SetupHooks #
Constructors
SetupHooks | |
Fields |
Instances
Monoid SetupHooks | |
Defined in Distribution.Simple.SetupHooks.Internal Methods mempty :: SetupHooks # mappend :: SetupHooks -> SetupHooks -> SetupHooks # mconcat :: [SetupHooks] -> SetupHooks # | |
Semigroup SetupHooks | |
Defined in Distribution.Simple.SetupHooks.Internal Methods (<>) :: SetupHooks -> SetupHooks -> SetupHooks # sconcat :: NonEmpty SetupHooks -> SetupHooks # stimes :: Integral b => b -> SetupHooks -> SetupHooks # |
Configure hooks
Configure hooks can be used to augment the Cabal configure logic with
package-specific logic. The main principle is that the configure hooks can
feed into updating the PackageDescription
of a cabal
package. From then on,
this package configuration is set in stone, and later hooks (e.g. hooks into
the build phase) can no longer modify this configuration; instead they will
receive this configuration in their inputs, and must honour it.
Configuration happens at two levels:
- global configuration covers the entire package,
- local configuration covers a single component.
Once the global package configuration is done, all hooks work on a per-component level. The configuration hooks thus follow a simple philosophy:
- All modifications to global package options must use
preConfPackageHook
. - All modifications to component configuration options must use
preConfComponentHook
.
For example, to generate modules inside a given component, you should:
- In the per-component configure hook, declare the modules you are going to
generate by adding them to the
autogenModules
field for that component (unless you know them ahead of time, in which case they can be listed textually in the.cabal
file of the project). - In the build hooks, describe the actions that will generate these modules.
data ConfigureHooks #
Constructors
ConfigureHooks | |
Instances
Monoid ConfigureHooks | |
Defined in Distribution.Simple.SetupHooks.Internal Methods mappend :: ConfigureHooks -> ConfigureHooks -> ConfigureHooks # mconcat :: [ConfigureHooks] -> ConfigureHooks # | |
Semigroup ConfigureHooks | |
Defined in Distribution.Simple.SetupHooks.Internal Methods (<>) :: ConfigureHooks -> ConfigureHooks -> ConfigureHooks # sconcat :: NonEmpty ConfigureHooks -> ConfigureHooks # stimes :: Integral b => b -> ConfigureHooks -> ConfigureHooks # |
Per-package configure hooks
data PreConfPackageInputs #
Constructors
PreConfPackageInputs | |
Fields |
Instances
data PreConfPackageOutputs #
Constructors
PreConfPackageOutputs | |
Fields
|
Instances
Structured PreConfPackageOutputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods structure :: Proxy PreConfPackageOutputs -> Structure structureHash' :: Tagged PreConfPackageOutputs MD5 | |||||
Binary PreConfPackageOutputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods put :: PreConfPackageOutputs -> Put # get :: Get PreConfPackageOutputs # putList :: [PreConfPackageOutputs] -> Put # | |||||
Generic PreConfPackageOutputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Associated Types
Methods from :: PreConfPackageOutputs -> Rep PreConfPackageOutputs x # to :: Rep PreConfPackageOutputs x -> PreConfPackageOutputs # | |||||
Show PreConfPackageOutputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods showsPrec :: Int -> PreConfPackageOutputs -> ShowS # show :: PreConfPackageOutputs -> String # showList :: [PreConfPackageOutputs] -> ShowS # | |||||
type Rep PreConfPackageOutputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal type Rep PreConfPackageOutputs = D1 ('MetaData "PreConfPackageOutputs" "Distribution.Simple.SetupHooks.Internal" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "PreConfPackageOutputs" 'PrefixI 'True) (S1 ('MetaSel ('Just "buildOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildOptions) :*: S1 ('MetaSel ('Just "extraConfiguredProgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConfiguredProgs))) |
data PostConfPackageInputs #
Constructors
PostConfPackageInputs | |
Instances
Structured PostConfPackageInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods structure :: Proxy PostConfPackageInputs -> Structure structureHash' :: Tagged PostConfPackageInputs MD5 | |||||
Binary PostConfPackageInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods put :: PostConfPackageInputs -> Put # get :: Get PostConfPackageInputs # putList :: [PostConfPackageInputs] -> Put # | |||||
Generic PostConfPackageInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Associated Types
Methods from :: PostConfPackageInputs -> Rep PostConfPackageInputs x # to :: Rep PostConfPackageInputs x -> PostConfPackageInputs # | |||||
Show PostConfPackageInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods showsPrec :: Int -> PostConfPackageInputs -> ShowS # show :: PostConfPackageInputs -> String # showList :: [PostConfPackageInputs] -> ShowS # | |||||
type Rep PostConfPackageInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal type Rep PostConfPackageInputs = D1 ('MetaData "PostConfPackageInputs" "Distribution.Simple.SetupHooks.Internal" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "PostConfPackageInputs" 'PrefixI 'True) (S1 ('MetaSel ('Just "localBuildConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalBuildConfig) :*: S1 ('MetaSel ('Just "packageBuildDescr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageBuildDescr))) |
type PostConfPackageHook = PostConfPackageInputs -> IO () #
Per-component configure hooks
data PreConfComponentInputs #
Constructors
PreConfComponentInputs | |
Instances
Structured PreConfComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods structure :: Proxy PreConfComponentInputs -> Structure structureHash' :: Tagged PreConfComponentInputs MD5 | |||||
Binary PreConfComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods put :: PreConfComponentInputs -> Put # get :: Get PreConfComponentInputs # putList :: [PreConfComponentInputs] -> Put # | |||||
Generic PreConfComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Associated Types
Methods from :: PreConfComponentInputs -> Rep PreConfComponentInputs x # to :: Rep PreConfComponentInputs x -> PreConfComponentInputs # | |||||
Show PreConfComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods showsPrec :: Int -> PreConfComponentInputs -> ShowS # show :: PreConfComponentInputs -> String # showList :: [PreConfComponentInputs] -> ShowS # | |||||
type Rep PreConfComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal type Rep PreConfComponentInputs = D1 ('MetaData "PreConfComponentInputs" "Distribution.Simple.SetupHooks.Internal" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "PreConfComponentInputs" 'PrefixI 'True) (S1 ('MetaSel ('Just "localBuildConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalBuildConfig) :*: (S1 ('MetaSel ('Just "packageBuildDescr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageBuildDescr) :*: S1 ('MetaSel ('Just "component") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Component)))) |
data PreConfComponentOutputs #
Constructors
PreConfComponentOutputs | |
Fields |
Instances
Structured PreConfComponentOutputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods structure :: Proxy PreConfComponentOutputs -> Structure structureHash' :: Tagged PreConfComponentOutputs MD5 | |||||
Binary PreConfComponentOutputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods put :: PreConfComponentOutputs -> Put # get :: Get PreConfComponentOutputs # putList :: [PreConfComponentOutputs] -> Put # | |||||
Generic PreConfComponentOutputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Associated Types
Methods from :: PreConfComponentOutputs -> Rep PreConfComponentOutputs x # to :: Rep PreConfComponentOutputs x -> PreConfComponentOutputs # | |||||
Show PreConfComponentOutputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods showsPrec :: Int -> PreConfComponentOutputs -> ShowS # show :: PreConfComponentOutputs -> String # showList :: [PreConfComponentOutputs] -> ShowS # | |||||
type Rep PreConfComponentOutputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal type Rep PreConfComponentOutputs = D1 ('MetaData "PreConfComponentOutputs" "Distribution.Simple.SetupHooks.Internal" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "PreConfComponentOutputs" 'PrefixI 'True) (S1 ('MetaSel ('Just "componentDiff") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentDiff))) |
newtype ComponentDiff #
Constructors
ComponentDiff | |
Fields |
Instances
Structured ComponentDiff | |
Defined in Distribution.Simple.SetupHooks.Internal | |
Binary ComponentDiff | |
Defined in Distribution.Simple.SetupHooks.Internal | |
Semigroup ComponentDiff | |
Defined in Distribution.Simple.SetupHooks.Internal Methods (<>) :: ComponentDiff -> ComponentDiff -> ComponentDiff # sconcat :: NonEmpty ComponentDiff -> ComponentDiff # stimes :: Integral b => b -> ComponentDiff -> ComponentDiff # | |
Show ComponentDiff | |
Defined in Distribution.Simple.SetupHooks.Internal Methods showsPrec :: Int -> ComponentDiff -> ShowS # show :: ComponentDiff -> String # showList :: [ComponentDiff] -> ShowS # |
type LibraryDiff = Library #
type ForeignLibDiff = ForeignLib #
type ExecutableDiff = Executable #
type TestSuiteDiff = TestSuite #
type BenchmarkDiff = Benchmark #
type BuildInfoDiff = BuildInfo #
Build hooks
data BuildHooks #
Constructors
BuildHooks | |
Instances
Monoid BuildHooks | |
Defined in Distribution.Simple.SetupHooks.Internal Methods mempty :: BuildHooks # mappend :: BuildHooks -> BuildHooks -> BuildHooks # mconcat :: [BuildHooks] -> BuildHooks # | |
Semigroup BuildHooks | |
Defined in Distribution.Simple.SetupHooks.Internal Methods (<>) :: BuildHooks -> BuildHooks -> BuildHooks # sconcat :: NonEmpty BuildHooks -> BuildHooks # stimes :: Integral b => b -> BuildHooks -> BuildHooks # |
data BuildingWhat #
Constructors
BuildNormal BuildFlags | |
BuildRepl ReplFlags | |
BuildHaddock HaddockFlags | |
BuildHscolour HscolourFlags |
Instances
Structured BuildingWhat | |||||
Defined in Distribution.Simple.Setup | |||||
Binary BuildingWhat | |||||
Defined in Distribution.Simple.Setup | |||||
Generic BuildingWhat | |||||
Defined in Distribution.Simple.Setup Associated Types
| |||||
Show BuildingWhat | |||||
Defined in Distribution.Simple.Setup Methods showsPrec :: Int -> BuildingWhat -> ShowS # show :: BuildingWhat -> String # showList :: [BuildingWhat] -> ShowS # | |||||
type Rep BuildingWhat | |||||
Defined in Distribution.Simple.Setup type Rep BuildingWhat = D1 ('MetaData "BuildingWhat" "Distribution.Simple.Setup" "Cabal-3.16.0.0-inplace" '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)))) |
buildingWhatDistPref :: BuildingWhat -> SymbolicPath Pkg ('Dir Dist) #
Pre-build rules
Pre-build hooks are specified as a collection of pre-build Rules
.
Each Rule
consists of:
- a specification of its static dependencies and outputs,
- the commands that execute the rule.
Rules are constructed using either one of the staticRule
or dynamicRule
smart constructors. Directly constructing a Rule
using the constructors of
that data type is not advised, as this relies on internal implementation details
which are subject to change in between versions of the `Cabal-hooks` library.
Note that:
- To declare the dependency on the output of a rule, one must refer to the
rule directly, and not to the path to the output executing that rule will
eventually produce.
To do so, registering a
Rule
with the API returns a unique identifier for that rule, in the form of aRuleId
. - File dependencies and outputs are not specified directly by
FilePath
, but rather use theLocation
type (which is more convenient when working with preprocessors). - Rules refer to the actions that execute them using static pointers, in order to enable serialisation/deserialisation of rules.
- Rules can additionally monitor files or directories, which determines when to re-compute the entire set of rules.
data PreBuildComponentInputs #
Constructors
PreBuildComponentInputs | |
Fields |
Instances
Structured PreBuildComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods structure :: Proxy PreBuildComponentInputs -> Structure structureHash' :: Tagged PreBuildComponentInputs MD5 | |||||
Binary PreBuildComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods put :: PreBuildComponentInputs -> Put # get :: Get PreBuildComponentInputs # putList :: [PreBuildComponentInputs] -> Put # | |||||
Generic PreBuildComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Associated Types
Methods from :: PreBuildComponentInputs -> Rep PreBuildComponentInputs x # to :: Rep PreBuildComponentInputs x -> PreBuildComponentInputs # | |||||
Show PreBuildComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods showsPrec :: Int -> PreBuildComponentInputs -> ShowS # show :: PreBuildComponentInputs -> String # showList :: [PreBuildComponentInputs] -> ShowS # | |||||
type Rep PreBuildComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal type Rep PreBuildComponentInputs = D1 ('MetaData "PreBuildComponentInputs" "Distribution.Simple.SetupHooks.Internal" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "PreBuildComponentInputs" 'PrefixI 'True) (S1 ('MetaSel ('Just "buildingWhat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildingWhat) :*: (S1 ('MetaSel ('Just "localBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalBuildInfo) :*: S1 ('MetaSel ('Just "targetInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TargetInfo)))) |
Post-build hooks
data PostBuildComponentInputs #
Constructors
PostBuildComponentInputs | |
Fields |
Instances
Structured PostBuildComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods structure :: Proxy PostBuildComponentInputs -> Structure structureHash' :: Tagged PostBuildComponentInputs MD5 | |||||
Binary PostBuildComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods put :: PostBuildComponentInputs -> Put # get :: Get PostBuildComponentInputs # putList :: [PostBuildComponentInputs] -> Put # | |||||
Generic PostBuildComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Associated Types
Methods from :: PostBuildComponentInputs -> Rep PostBuildComponentInputs x # to :: Rep PostBuildComponentInputs x -> PostBuildComponentInputs # | |||||
Show PostBuildComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods showsPrec :: Int -> PostBuildComponentInputs -> ShowS # show :: PostBuildComponentInputs -> String # showList :: [PostBuildComponentInputs] -> ShowS # | |||||
type Rep PostBuildComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal type Rep PostBuildComponentInputs = D1 ('MetaData "PostBuildComponentInputs" "Distribution.Simple.SetupHooks.Internal" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "PostBuildComponentInputs" 'PrefixI 'True) (S1 ('MetaSel ('Just "buildFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildFlags) :*: (S1 ('MetaSel ('Just "localBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalBuildInfo) :*: S1 ('MetaSel ('Just "targetInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TargetInfo)))) |
type PostBuildComponentHook = PostBuildComponentInputs -> IO () #
Rules
data Dependency #
Constructors
RuleDependency !RuleOutput | |
FileDependency !Location |
Instances
Structured Dependency | |||||
Defined in Distribution.Simple.SetupHooks.Rule | |||||
Binary Dependency | |||||
Defined in Distribution.Simple.SetupHooks.Rule | |||||
Generic Dependency | |||||
Defined in Distribution.Simple.SetupHooks.Rule Associated Types
| |||||
Show Dependency | |||||
Defined in Distribution.Simple.SetupHooks.Rule Methods showsPrec :: Int -> Dependency -> ShowS # show :: Dependency -> String # showList :: [Dependency] -> ShowS # | |||||
Eq Dependency | |||||
Defined in Distribution.Simple.SetupHooks.Rule | |||||
Ord Dependency | |||||
Defined in Distribution.Simple.SetupHooks.Rule Methods compare :: Dependency -> Dependency -> Ordering # (<) :: Dependency -> Dependency -> Bool # (<=) :: Dependency -> Dependency -> Bool # (>) :: Dependency -> Dependency -> Bool # (>=) :: Dependency -> Dependency -> Bool # max :: Dependency -> Dependency -> Dependency # min :: Dependency -> Dependency -> Dependency # | |||||
type Rep Dependency | |||||
Defined in Distribution.Simple.SetupHooks.Rule type Rep Dependency = D1 ('MetaData "Dependency" "Distribution.Simple.SetupHooks.Rule" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "RuleDependency" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RuleOutput)) :+: C1 ('MetaCons "FileDependency" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Location))) |
data RuleOutput #
Constructors
RuleOutput | |
Fields
|
Instances
Structured RuleOutput | |||||
Defined in Distribution.Simple.SetupHooks.Rule | |||||
Binary RuleOutput | |||||
Defined in Distribution.Simple.SetupHooks.Rule | |||||
Generic RuleOutput | |||||
Defined in Distribution.Simple.SetupHooks.Rule Associated Types
| |||||
Show RuleOutput | |||||
Defined in Distribution.Simple.SetupHooks.Rule Methods showsPrec :: Int -> RuleOutput -> ShowS # show :: RuleOutput -> String # showList :: [RuleOutput] -> ShowS # | |||||
Eq RuleOutput | |||||
Defined in Distribution.Simple.SetupHooks.Rule | |||||
Ord RuleOutput | |||||
Defined in Distribution.Simple.SetupHooks.Rule Methods compare :: RuleOutput -> RuleOutput -> Ordering # (<) :: RuleOutput -> RuleOutput -> Bool # (<=) :: RuleOutput -> RuleOutput -> Bool # (>) :: RuleOutput -> RuleOutput -> Bool # (>=) :: RuleOutput -> RuleOutput -> Bool # max :: RuleOutput -> RuleOutput -> RuleOutput # min :: RuleOutput -> RuleOutput -> RuleOutput # | |||||
type Rep RuleOutput | |||||
Defined in Distribution.Simple.SetupHooks.Rule type Rep RuleOutput = D1 ('MetaData "RuleOutput" "Distribution.Simple.SetupHooks.Rule" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "RuleOutput" 'PrefixI 'True) (S1 ('MetaSel ('Just "outputOfRule") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RuleId) :*: S1 ('MetaSel ('Just "outputIndex") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word))) |
Instances
Structured RuleId | |||||
Defined in Distribution.Simple.SetupHooks.Rule | |||||
Binary RuleId | |||||
Generic RuleId | |||||
Defined in Distribution.Simple.SetupHooks.Rule Associated Types
| |||||
Show RuleId | |||||
Eq RuleId | |||||
Ord RuleId | |||||
type Rep RuleId | |||||
Defined in Distribution.Simple.SetupHooks.Rule type Rep RuleId = D1 ('MetaData "RuleId" "Distribution.Simple.SetupHooks.Rule" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "RuleId" 'PrefixI 'True) (S1 ('MetaSel ('Just "ruleNameSpace") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RulesNameSpace) :*: S1 ('MetaSel ('Just "ruleName") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText))) |
staticRule :: Typeable arg => Command arg (IO ()) -> [Dependency] -> NonEmpty Location -> Rule #
dynamicRule :: (Typeable depsArg, Typeable depsRes, Typeable arg) => StaticPtr (Dict (Binary depsRes, Show depsRes, Eq depsRes)) -> Command depsArg (IO ([Dependency], depsRes)) -> Command arg (depsRes -> IO ()) -> [Dependency] -> NonEmpty Location -> Rule #
Rule inputs/outputs
Rules can declare various kinds of dependencies:
staticDependencies
: files or other rules that a rule statically depends on,- extra dynamic dependencies, using the
DynamicRuleCommands
constructor, MonitorFilePath
: additional files and directories to monitor.
Rules are considered out-of-date precisely when any of the following conditions apply:
- O1
- there has been a (relevant) change in the files and directories monitored by the rules,
- O2
- the environment passed to the computation of rules has changed.
If the rules are out-of-date, the build system is expected to re-run the computation that computes all rules.
After this re-computation of the set of all rules, we match up new rules
with old rules, by RuleId
. A rule is then considered stale if any of
following conditions apply:
- N
- the rule is new, or
- S
- the rule matches with an old rule, and either:
- S1
- a file dependency of the rule has been modifiedcreateddeleted, or a (transitive) rule dependency of the rule is itself stale, or
- S2
- the rule is different from the old rule, e.g. the argument stored in
the rule command has changed, or the pointer to the action to run the
rule has changed. (This is determined using the
Eq Rule
instance.)
A stale rule becomes no longer stale once we run its associated action. The build system is responsible for re-running the actions associated with each stale rule, in dependency order. This means the build system is expected to behave as follows:
- Any time the rules are out-of-date, query the rules to obtain up-to-date rules.
- Re-run stale rules.
Constructors
Location | |
Fields
|
autogenComponentModulesDir :: LocalBuildInfo -> ComponentLocalBuildInfo -> SymbolicPath Pkg ('Dir Source) #
componentBuildDir :: LocalBuildInfo -> ComponentLocalBuildInfo -> SymbolicPath Pkg ('Dir Build) #
Actions
data RuleCommands (scope :: Scope) (deps :: Scope -> Type -> Type -> Type) (ruleCmd :: Scope -> Type -> Type -> Type) where #
Constructors
StaticRuleCommand | |
Fields
| |
DynamicRuleCommands | |
Fields
|
Instances
(forall res. Binary (ruleCmd 'System ByteString res), Binary (deps 'System ByteString ByteString)) => Binary (RuleCommands 'System deps ruleCmd) | |
Defined in Distribution.Simple.SetupHooks.Rule Methods put :: RuleCommands 'System deps ruleCmd -> Put # get :: Get (RuleCommands 'System deps ruleCmd) # putList :: [RuleCommands 'System deps ruleCmd] -> Put # | |
(forall arg res. Binary (ruleCmd 'User arg res), forall depsArg depsRes. Binary depsRes => Binary (deps 'User depsArg depsRes)) => Binary (RuleCommands 'User deps ruleCmd) | |
Defined in Distribution.Simple.SetupHooks.Rule Methods put :: RuleCommands 'User deps ruleCmd -> Put # get :: Get (RuleCommands 'User deps ruleCmd) # putList :: [RuleCommands 'User deps ruleCmd] -> Put # | |
(forall arg res. Show (ruleCmd 'User arg res), forall depsArg depsRes. Show depsRes => Show (deps 'User depsArg depsRes)) => Show (RuleCommands 'User deps ruleCmd) | |
Defined in Distribution.Simple.SetupHooks.Rule Methods showsPrec :: Int -> RuleCommands 'User deps ruleCmd -> ShowS # show :: RuleCommands 'User deps ruleCmd -> String # showList :: [RuleCommands 'User deps ruleCmd] -> ShowS # | |
(forall res. Eq (ruleCmd 'System ByteString res), Eq (deps 'System ByteString ByteString)) => Eq (RuleCommands 'System deps ruleCmd) | |
Defined in Distribution.Simple.SetupHooks.Rule Methods (==) :: RuleCommands 'System deps ruleCmd -> RuleCommands 'System deps ruleCmd -> Bool # (/=) :: RuleCommands 'System deps ruleCmd -> RuleCommands 'System deps ruleCmd -> Bool # | |
(forall arg res. Eq (ruleCmd 'User arg res), forall depsArg depsRes. Eq depsRes => Eq (deps 'User depsArg depsRes)) => Eq (RuleCommands 'User deps ruleCmd) | |
Defined in Distribution.Simple.SetupHooks.Rule Methods (==) :: RuleCommands 'User deps ruleCmd -> RuleCommands 'User deps ruleCmd -> Bool # (/=) :: RuleCommands 'User deps ruleCmd -> RuleCommands 'User deps ruleCmd -> Bool # |
mkCommand :: StaticPtr (Dict (Binary arg, Show arg)) -> StaticPtr (arg -> res) -> arg -> Command arg res #
Rules API
Defining pre-build rules can be done in the following style:
{-# LANGUAGE BlockArguments, StaticPointers #-} myPreBuildRules :: PreBuildComponentRules myPreBuildRules = rules (static ()) $ \ preBuildEnvironment -> do let cmd1 = mkCommand (static Dict) $ static \ arg -> do { .. } cmd2 = mkCommand (static Dict) $ static \ arg -> do { .. } myData <- liftIO someIOAction addRuleMonitors [ monitorDirectory "someSearchDir" ] registerRule_ "rule_1_1" $ staticRule (cmd1 arg1) deps1 outs1 registerRule_ "rule_1_2" $ staticRule (cmd1 arg2) deps2 outs2 registerRule_ "rule_1_3" $ staticRule (cmd1 arg3) deps3 outs3 registerRule_ "rule_2_4" $ staticRule (cmd2 arg4) deps4 outs4
Here we use the rules
, staticRule
and mkCommand
smart constructors,
rather than directly using the Rules
, Rule
and Command
constructors,
which insulates us from internal changes to the Rules
, Rule
and Command
datatypes, respectively.
We use addRuleMonitors
to declare a monitored directory that the collection
of rules as a whole depends on. In this case, we declare that they depend on the
contents of the "searchDir" directory. This means that the rules will be
computed anew whenever the contents of this directory change.
Arguments
:: ShortText | user-given rule name; these should be unique on a per-package level |
-> Rule | the rule to register |
-> RulesM RuleId |
Register a rule. Returns an identifier for that rule.
Arguments
:: ShortText | user-given rule name; these should be unique on a per-package level |
-> Rule | the rule to register |
-> RulesT IO () |
Register a rule, discarding the produced RuleId
.
Using this function means that you don't expect any other rules to ever
depend on any outputs of this rule. Use registerRule
to retain the
RuleId
instead.
File/directory monitoring
addRuleMonitors :: forall (m :: Type -> Type). Monad m => [MonitorFilePath] -> RulesT m () Source #
Declare additional monitored objects for the collection of all rules.
When these monitored objects change, the rules are re-computed.
Instances
Parsec Glob | |||||
Defined in Distribution.Simple.Glob.Internal | |||||
Pretty Glob | |||||
Defined in Distribution.Simple.Glob.Internal | |||||
Structured Glob | |||||
Defined in Distribution.Simple.Glob.Internal | |||||
Binary Glob | |||||
Generic Glob | |||||
Defined in Distribution.Simple.Glob.Internal Associated Types
| |||||
Show Glob | |||||
Eq Glob | |||||
type Rep Glob | |||||
Defined in Distribution.Simple.Glob.Internal type Rep Glob = D1 ('MetaData "Glob" "Distribution.Simple.Glob.Internal" "Cabal-3.16.0.0-inplace" 'False) ((C1 ('MetaCons "GlobDir" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 GlobPieces) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Glob)) :+: C1 ('MetaCons "GlobDirRecursive" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 GlobPieces))) :+: (C1 ('MetaCons "GlobFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 GlobPieces)) :+: C1 ('MetaCons "GlobDirTrailing" 'PrefixI 'False) (U1 :: Type -> Type))) |
data MonitorFilePath #
Constructors
MonitorFile | |
Fields | |
MonitorFileGlob | |
Fields |
Instances
Structured MonitorFilePath | |||||
Defined in Distribution.Simple.FileMonitor.Types | |||||
Binary MonitorFilePath | |||||
Defined in Distribution.Simple.FileMonitor.Types Methods put :: MonitorFilePath -> Put # get :: Get MonitorFilePath # putList :: [MonitorFilePath] -> Put # | |||||
Generic MonitorFilePath | |||||
Defined in Distribution.Simple.FileMonitor.Types Associated Types
Methods from :: MonitorFilePath -> Rep MonitorFilePath x # to :: Rep MonitorFilePath x -> MonitorFilePath # | |||||
Show MonitorFilePath | |||||
Defined in Distribution.Simple.FileMonitor.Types Methods showsPrec :: Int -> MonitorFilePath -> ShowS # show :: MonitorFilePath -> String # showList :: [MonitorFilePath] -> ShowS # | |||||
Eq MonitorFilePath | |||||
Defined in Distribution.Simple.FileMonitor.Types Methods (==) :: MonitorFilePath -> MonitorFilePath -> Bool # (/=) :: MonitorFilePath -> MonitorFilePath -> Bool # | |||||
type Rep MonitorFilePath | |||||
Defined in Distribution.Simple.FileMonitor.Types type Rep MonitorFilePath = D1 ('MetaData "MonitorFilePath" "Distribution.Simple.FileMonitor.Types" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "MonitorFile" 'PrefixI 'True) (S1 ('MetaSel ('Just "monitorKindFile") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MonitorKindFile) :*: (S1 ('MetaSel ('Just "monitorKindDir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MonitorKindDir) :*: S1 ('MetaSel ('Just "monitorPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FilePath))) :+: C1 ('MetaCons "MonitorFileGlob" 'PrefixI 'True) (S1 ('MetaSel ('Just "monitorKindFile") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MonitorKindFile) :*: (S1 ('MetaSel ('Just "monitorKindDir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MonitorKindDir) :*: S1 ('MetaSel ('Just "monitorPathGlob") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RootedGlob)))) |
data FilePathRoot #
Constructors
FilePathRelative | |
FilePathRoot FilePath | |
FilePathHomeDir |
Instances
Parsec FilePathRoot | |||||
Defined in Distribution.Simple.FileMonitor.Types Methods parsec :: CabalParsing m => m FilePathRoot | |||||
Pretty FilePathRoot | |||||
Defined in Distribution.Simple.FileMonitor.Types | |||||
Structured FilePathRoot | |||||
Defined in Distribution.Simple.FileMonitor.Types | |||||
Binary FilePathRoot | |||||
Defined in Distribution.Simple.FileMonitor.Types | |||||
Generic FilePathRoot | |||||
Defined in Distribution.Simple.FileMonitor.Types Associated Types
| |||||
Show FilePathRoot | |||||
Defined in Distribution.Simple.FileMonitor.Types Methods showsPrec :: Int -> FilePathRoot -> ShowS # show :: FilePathRoot -> String # showList :: [FilePathRoot] -> ShowS # | |||||
Eq FilePathRoot | |||||
Defined in Distribution.Simple.FileMonitor.Types | |||||
type Rep FilePathRoot | |||||
Defined in Distribution.Simple.FileMonitor.Types type Rep FilePathRoot = D1 ('MetaData "FilePathRoot" "Distribution.Simple.FileMonitor.Types" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "FilePathRelative" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FilePathRoot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: C1 ('MetaCons "FilePathHomeDir" 'PrefixI 'False) (U1 :: Type -> Type))) |
data MonitorKindFile #
Constructors
FileExists | |
FileModTime | |
FileHashed | |
FileNotExists |
Instances
Structured MonitorKindFile | |||||
Defined in Distribution.Simple.FileMonitor.Types | |||||
Binary MonitorKindFile | |||||
Defined in Distribution.Simple.FileMonitor.Types Methods put :: MonitorKindFile -> Put # get :: Get MonitorKindFile # putList :: [MonitorKindFile] -> Put # | |||||
Generic MonitorKindFile | |||||
Defined in Distribution.Simple.FileMonitor.Types Associated Types
Methods from :: MonitorKindFile -> Rep MonitorKindFile x # to :: Rep MonitorKindFile x -> MonitorKindFile # | |||||
Show MonitorKindFile | |||||
Defined in Distribution.Simple.FileMonitor.Types Methods showsPrec :: Int -> MonitorKindFile -> ShowS # show :: MonitorKindFile -> String # showList :: [MonitorKindFile] -> ShowS # | |||||
Eq MonitorKindFile | |||||
Defined in Distribution.Simple.FileMonitor.Types Methods (==) :: MonitorKindFile -> MonitorKindFile -> Bool # (/=) :: MonitorKindFile -> MonitorKindFile -> Bool # | |||||
type Rep MonitorKindFile | |||||
Defined in Distribution.Simple.FileMonitor.Types type Rep MonitorKindFile = D1 ('MetaData "MonitorKindFile" "Distribution.Simple.FileMonitor.Types" "Cabal-3.16.0.0-inplace" 'False) ((C1 ('MetaCons "FileExists" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FileModTime" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FileHashed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FileNotExists" 'PrefixI 'False) (U1 :: Type -> Type))) |
data MonitorKindDir #
Constructors
DirExists | |
DirModTime | |
DirNotExists |
Instances
Structured MonitorKindDir | |||||
Defined in Distribution.Simple.FileMonitor.Types | |||||
Binary MonitorKindDir | |||||
Defined in Distribution.Simple.FileMonitor.Types Methods put :: MonitorKindDir -> Put # get :: Get MonitorKindDir # putList :: [MonitorKindDir] -> Put # | |||||
Generic MonitorKindDir | |||||
Defined in Distribution.Simple.FileMonitor.Types Associated Types
Methods from :: MonitorKindDir -> Rep MonitorKindDir x # to :: Rep MonitorKindDir x -> MonitorKindDir # | |||||
Show MonitorKindDir | |||||
Defined in Distribution.Simple.FileMonitor.Types Methods showsPrec :: Int -> MonitorKindDir -> ShowS # show :: MonitorKindDir -> String # showList :: [MonitorKindDir] -> ShowS # | |||||
Eq MonitorKindDir | |||||
Defined in Distribution.Simple.FileMonitor.Types Methods (==) :: MonitorKindDir -> MonitorKindDir -> Bool # (/=) :: MonitorKindDir -> MonitorKindDir -> Bool # | |||||
type Rep MonitorKindDir | |||||
Defined in Distribution.Simple.FileMonitor.Types type Rep MonitorKindDir = D1 ('MetaData "MonitorKindDir" "Distribution.Simple.FileMonitor.Types" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "DirExists" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DirModTime" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DirNotExists" 'PrefixI 'False) (U1 :: Type -> Type))) |
data RootedGlob #
Constructors
RootedGlob FilePathRoot Glob |
Instances
Parsec RootedGlob | |||||
Defined in Distribution.Simple.FileMonitor.Types Methods parsec :: CabalParsing m => m RootedGlob | |||||
Pretty RootedGlob | |||||
Defined in Distribution.Simple.FileMonitor.Types | |||||
Structured RootedGlob | |||||
Defined in Distribution.Simple.FileMonitor.Types | |||||
Binary RootedGlob | |||||
Defined in Distribution.Simple.FileMonitor.Types | |||||
Generic RootedGlob | |||||
Defined in Distribution.Simple.FileMonitor.Types Associated Types
| |||||
Show RootedGlob | |||||
Defined in Distribution.Simple.FileMonitor.Types Methods showsPrec :: Int -> RootedGlob -> ShowS # show :: RootedGlob -> String # showList :: [RootedGlob] -> ShowS # | |||||
Eq RootedGlob | |||||
Defined in Distribution.Simple.FileMonitor.Types | |||||
type Rep RootedGlob | |||||
Defined in Distribution.Simple.FileMonitor.Types type Rep RootedGlob = D1 ('MetaData "RootedGlob" "Distribution.Simple.FileMonitor.Types" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "RootedGlob" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePathRoot) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Glob))) |
monitorFile :: FilePath -> MonitorFilePath #
monitorFileHashedSearchPath :: [FilePath] -> FilePath -> [MonitorFilePath] #
monitorFileSearchPath :: [FilePath] -> FilePath -> [MonitorFilePath] #
Install hooks
data InstallHooks #
Constructors
InstallHooks | |
Instances
Monoid InstallHooks | |
Defined in Distribution.Simple.SetupHooks.Internal Methods mempty :: InstallHooks # mappend :: InstallHooks -> InstallHooks -> InstallHooks # mconcat :: [InstallHooks] -> InstallHooks # | |
Semigroup InstallHooks | |
Defined in Distribution.Simple.SetupHooks.Internal Methods (<>) :: InstallHooks -> InstallHooks -> InstallHooks # sconcat :: NonEmpty InstallHooks -> InstallHooks # stimes :: Integral b => b -> InstallHooks -> InstallHooks # |
data InstallComponentInputs #
Constructors
InstallComponentInputs | |
Fields |
Instances
Structured InstallComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods structure :: Proxy InstallComponentInputs -> Structure structureHash' :: Tagged InstallComponentInputs MD5 | |||||
Binary InstallComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods put :: InstallComponentInputs -> Put # get :: Get InstallComponentInputs # putList :: [InstallComponentInputs] -> Put # | |||||
Generic InstallComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Associated Types
Methods from :: InstallComponentInputs -> Rep InstallComponentInputs x # to :: Rep InstallComponentInputs x -> InstallComponentInputs # | |||||
Show InstallComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal Methods showsPrec :: Int -> InstallComponentInputs -> ShowS # show :: InstallComponentInputs -> String # showList :: [InstallComponentInputs] -> ShowS # | |||||
type Rep InstallComponentInputs | |||||
Defined in Distribution.Simple.SetupHooks.Internal type Rep InstallComponentInputs = D1 ('MetaData "InstallComponentInputs" "Distribution.Simple.SetupHooks.Internal" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "InstallComponentInputs" 'PrefixI 'True) (S1 ('MetaSel ('Just "copyFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CopyFlags) :*: (S1 ('MetaSel ('Just "localBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalBuildInfo) :*: S1 ('MetaSel ('Just "targetInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TargetInfo)))) |
type InstallComponentHook = InstallComponentInputs -> IO () #
Re-exports
Hooks
Configure hooks
data ConfigFlags #
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 | |||||
Defined in Distribution.Simple.Setup.Config | |||||
Binary ConfigFlags | |||||
Defined in Distribution.Simple.Setup.Config | |||||
Monoid ConfigFlags | |||||
Defined in Distribution.Simple.Setup.Config Methods mempty :: ConfigFlags # mappend :: ConfigFlags -> ConfigFlags -> ConfigFlags # mconcat :: [ConfigFlags] -> ConfigFlags # | |||||
Semigroup ConfigFlags | |||||
Defined in Distribution.Simple.Setup.Config Methods (<>) :: ConfigFlags -> ConfigFlags -> ConfigFlags # sconcat :: NonEmpty ConfigFlags -> ConfigFlags # stimes :: Integral b => b -> ConfigFlags -> ConfigFlags # | |||||
Generic ConfigFlags | |||||
Defined in Distribution.Simple.Setup.Config Associated Types
| |||||
Read ConfigFlags | |||||
Defined in Distribution.Simple.Setup.Config Methods readsPrec :: Int -> ReadS ConfigFlags # readList :: ReadS [ConfigFlags] # readPrec :: ReadPrec ConfigFlags # readListPrec :: ReadPrec [ConfigFlags] # | |||||
Show ConfigFlags | |||||
Defined in Distribution.Simple.Setup.Config Methods showsPrec :: Int -> ConfigFlags -> ShowS # show :: ConfigFlags -> String # showList :: [ConfigFlags] -> ShowS # | |||||
Eq ConfigFlags | |||||
Defined in Distribution.Simple.Setup.Config | |||||
type Rep ConfigFlags | |||||
Defined in Distribution.Simple.Setup.Config type Rep ConfigFlags = D1 ('MetaData "ConfigFlags" "Distribution.Simple.Setup.Config" "Cabal-3.16.0.0-inplace" '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))))))))) |
Build hooks
data BuildFlags #
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 | |||||
Defined in Distribution.Simple.Setup.Build | |||||
Binary BuildFlags | |||||
Defined in Distribution.Simple.Setup.Build | |||||
Monoid BuildFlags | |||||
Defined in Distribution.Simple.Setup.Build Methods mempty :: BuildFlags # mappend :: BuildFlags -> BuildFlags -> BuildFlags # mconcat :: [BuildFlags] -> BuildFlags # | |||||
Semigroup BuildFlags | |||||
Defined in Distribution.Simple.Setup.Build Methods (<>) :: BuildFlags -> BuildFlags -> BuildFlags # sconcat :: NonEmpty BuildFlags -> BuildFlags # stimes :: Integral b => b -> BuildFlags -> BuildFlags # | |||||
Generic BuildFlags | |||||
Defined in Distribution.Simple.Setup.Build Associated Types
| |||||
Read BuildFlags | |||||
Defined in Distribution.Simple.Setup.Build Methods readsPrec :: Int -> ReadS BuildFlags # readList :: ReadS [BuildFlags] # readPrec :: ReadPrec BuildFlags # readListPrec :: ReadPrec [BuildFlags] # | |||||
Show BuildFlags | |||||
Defined in Distribution.Simple.Setup.Build Methods showsPrec :: Int -> BuildFlags -> ShowS # show :: BuildFlags -> String # showList :: [BuildFlags] -> ShowS # | |||||
type Rep BuildFlags | |||||
Defined in Distribution.Simple.Setup.Build type Rep BuildFlags = D1 ('MetaData "BuildFlags" "Distribution.Simple.Setup.Build" "Cabal-3.16.0.0-inplace" '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)))))) |
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 | |||||
Defined in Distribution.Simple.Setup.Repl | |||||
Binary ReplFlags | |||||
Monoid ReplFlags | |||||
Semigroup ReplFlags | |||||
Generic ReplFlags | |||||
Defined in Distribution.Simple.Setup.Repl Associated Types
| |||||
Show ReplFlags | |||||
type Rep ReplFlags | |||||
Defined in Distribution.Simple.Setup.Repl type Rep ReplFlags = D1 ('MetaData "ReplFlags" "Distribution.Simple.Setup.Repl" "Cabal-3.16.0.0-inplace" '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 HaddockFlags #
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 | |||||
Defined in Distribution.Simple.Setup.Haddock | |||||
Binary HaddockFlags | |||||
Defined in Distribution.Simple.Setup.Haddock | |||||
Monoid HaddockFlags | |||||
Defined in Distribution.Simple.Setup.Haddock Methods mempty :: HaddockFlags # mappend :: HaddockFlags -> HaddockFlags -> HaddockFlags # mconcat :: [HaddockFlags] -> HaddockFlags # | |||||
Semigroup HaddockFlags | |||||
Defined in Distribution.Simple.Setup.Haddock Methods (<>) :: HaddockFlags -> HaddockFlags -> HaddockFlags # sconcat :: NonEmpty HaddockFlags -> HaddockFlags # stimes :: Integral b => b -> HaddockFlags -> HaddockFlags # | |||||
Generic HaddockFlags | |||||
Defined in Distribution.Simple.Setup.Haddock Associated Types
| |||||
Show HaddockFlags | |||||
Defined in Distribution.Simple.Setup.Haddock Methods showsPrec :: Int -> HaddockFlags -> ShowS # show :: HaddockFlags -> String # showList :: [HaddockFlags] -> ShowS # | |||||
type Rep HaddockFlags | |||||
Defined in Distribution.Simple.Setup.Haddock type Rep HaddockFlags = D1 ('MetaData "HaddockFlags" "Distribution.Simple.Setup.Haddock" "Cabal-3.16.0.0-inplace" '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 "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 HscolourFlags #
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 | |||||
Defined in Distribution.Simple.Setup.Hscolour | |||||
Binary HscolourFlags | |||||
Defined in Distribution.Simple.Setup.Hscolour | |||||
Monoid HscolourFlags | |||||
Defined in Distribution.Simple.Setup.Hscolour Methods mempty :: HscolourFlags # mappend :: HscolourFlags -> HscolourFlags -> HscolourFlags # mconcat :: [HscolourFlags] -> HscolourFlags # | |||||
Semigroup HscolourFlags | |||||
Defined in Distribution.Simple.Setup.Hscolour Methods (<>) :: HscolourFlags -> HscolourFlags -> HscolourFlags # sconcat :: NonEmpty HscolourFlags -> HscolourFlags # stimes :: Integral b => b -> HscolourFlags -> HscolourFlags # | |||||
Generic HscolourFlags | |||||
Defined in Distribution.Simple.Setup.Hscolour Associated Types
| |||||
Show HscolourFlags | |||||
Defined in Distribution.Simple.Setup.Hscolour Methods showsPrec :: Int -> HscolourFlags -> ShowS # show :: HscolourFlags -> String # showList :: [HscolourFlags] -> ShowS # | |||||
type Rep HscolourFlags | |||||
Defined in Distribution.Simple.Setup.Hscolour type Rep HscolourFlags = D1 ('MetaData "HscolourFlags" "Distribution.Simple.Setup.Hscolour" "Cabal-3.16.0.0-inplace" '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)))))) |
Install hooks
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 | |||||
Defined in Distribution.Simple.Setup.Copy | |||||
Binary CopyFlags | |||||
Monoid CopyFlags | |||||
Semigroup CopyFlags | |||||
Generic CopyFlags | |||||
Defined in Distribution.Simple.Setup.Copy Associated Types
| |||||
Show CopyFlags | |||||
type Rep CopyFlags | |||||
Defined in Distribution.Simple.Setup.Copy type Rep CopyFlags = D1 ('MetaData "CopyFlags" "Distribution.Simple.Setup.Copy" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "CopyFlags" 'PrefixI 'True) (S1 ('MetaSel ('Just "copyCommonFlags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonSetupFlags) :*: S1 ('MetaSel ('Just "copyDest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Flag CopyDest)))) |
Hooks
API
These are functions provided as part of the Hooks
API.
It is recommended to import them from this module as opposed to
manually importing them from inside the Cabal module hierarchy.
Copy/install functions
installFileGlob :: Verbosity -> CabalSpecVersion -> Maybe (SymbolicPath CWD ('Dir Pkg)) -> (Maybe (SymbolicPath CWD ('Dir DataDir)), SymbolicPath Pkg ('Dir DataDir)) -> RelativePath DataDir 'File -> IO () #
Interacting with the program database
Constructors
Program | |
Fields
|
data ConfiguredProgram #
Constructors
ConfiguredProgram | |
Fields
|
Instances
Structured ConfiguredProgram | |||||
Defined in Distribution.Simple.Program.Types Methods structure :: Proxy ConfiguredProgram -> Structure structureHash' :: Tagged ConfiguredProgram MD5 | |||||
Binary ConfiguredProgram | |||||
Defined in Distribution.Simple.Program.Types Methods put :: ConfiguredProgram -> Put # get :: Get ConfiguredProgram # putList :: [ConfiguredProgram] -> Put # | |||||
Generic ConfiguredProgram | |||||
Defined in Distribution.Simple.Program.Types Associated Types
Methods from :: ConfiguredProgram -> Rep ConfiguredProgram x # to :: Rep ConfiguredProgram x -> ConfiguredProgram # | |||||
Read ConfiguredProgram | |||||
Defined in Distribution.Simple.Program.Types Methods readsPrec :: Int -> ReadS ConfiguredProgram # readList :: ReadS [ConfiguredProgram] # | |||||
Show ConfiguredProgram | |||||
Defined in Distribution.Simple.Program.Types Methods showsPrec :: Int -> ConfiguredProgram -> ShowS # show :: ConfiguredProgram -> String # showList :: [ConfiguredProgram] -> ShowS # | |||||
Eq ConfiguredProgram | |||||
Defined in Distribution.Simple.Program.Types Methods (==) :: ConfiguredProgram -> ConfiguredProgram -> Bool # (/=) :: ConfiguredProgram -> ConfiguredProgram -> Bool # | |||||
type Rep ConfiguredProgram | |||||
Defined in Distribution.Simple.Program.Types type Rep ConfiguredProgram = D1 ('MetaData "ConfiguredProgram" "Distribution.Simple.Program.Types" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "ConfiguredProgram" 'PrefixI 'True) (((S1 ('MetaSel ('Just "programId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "programVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version))) :*: (S1 ('MetaSel ('Just "programDefaultArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "programOverrideArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :*: ((S1 ('MetaSel ('Just "programOverrideEnv") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, Maybe String)]) :*: S1 ('MetaSel ('Just "programProperties") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map String String))) :*: (S1 ('MetaSel ('Just "programLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProgramLocation) :*: S1 ('MetaSel ('Just "programMonitorFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]))))) |
data ProgramLocation #
Constructors
UserSpecified | |
Fields | |
FoundOnSystem | |
Fields |
Instances
Structured ProgramLocation | |||||
Defined in Distribution.Simple.Program.Types | |||||
Binary ProgramLocation | |||||
Defined in Distribution.Simple.Program.Types Methods put :: ProgramLocation -> Put # get :: Get ProgramLocation # putList :: [ProgramLocation] -> Put # | |||||
Generic ProgramLocation | |||||
Defined in Distribution.Simple.Program.Types Associated Types
Methods from :: ProgramLocation -> Rep ProgramLocation x # to :: Rep ProgramLocation x -> ProgramLocation # | |||||
Read ProgramLocation | |||||
Defined in Distribution.Simple.Program.Types Methods readsPrec :: Int -> ReadS ProgramLocation # readList :: ReadS [ProgramLocation] # | |||||
Show ProgramLocation | |||||
Defined in Distribution.Simple.Program.Types Methods showsPrec :: Int -> ProgramLocation -> ShowS # show :: ProgramLocation -> String # showList :: [ProgramLocation] -> ShowS # | |||||
Eq ProgramLocation | |||||
Defined in Distribution.Simple.Program.Types Methods (==) :: ProgramLocation -> ProgramLocation -> Bool # (/=) :: ProgramLocation -> ProgramLocation -> Bool # | |||||
type Rep ProgramLocation | |||||
Defined in Distribution.Simple.Program.Types type Rep ProgramLocation = D1 ('MetaData "ProgramLocation" "Distribution.Simple.Program.Types" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "UserSpecified" 'PrefixI 'True) (S1 ('MetaSel ('Just "locationPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: C1 ('MetaCons "FoundOnSystem" 'PrefixI 'True) (S1 ('MetaSel ('Just "locationPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath))) |
addKnownPrograms :: [Program] -> ProgramDb -> ProgramDb #
configureUnconfiguredProgram :: Verbosity -> Program -> ProgramDb -> IO (Maybe ConfiguredProgram) #
simpleProgram :: String -> Program #
General Cabal
datatypes
Instances
Parsec Verbosity | |||||
Defined in Distribution.Verbosity | |||||
Pretty Verbosity | |||||
Defined in Distribution.Verbosity | |||||
Structured Verbosity | |||||
Defined in Distribution.Verbosity | |||||
Binary Verbosity | |||||
Bounded Verbosity | |||||
Enum Verbosity | |||||
Defined in Distribution.Verbosity Methods succ :: Verbosity -> Verbosity # pred :: Verbosity -> Verbosity # fromEnum :: Verbosity -> Int # enumFrom :: Verbosity -> [Verbosity] # enumFromThen :: Verbosity -> Verbosity -> [Verbosity] # enumFromTo :: Verbosity -> Verbosity -> [Verbosity] # enumFromThenTo :: Verbosity -> Verbosity -> Verbosity -> [Verbosity] # | |||||
Generic Verbosity | |||||
Defined in Distribution.Verbosity Associated Types
| |||||
Read Verbosity | |||||
Show Verbosity | |||||
Eq Verbosity | |||||
Ord Verbosity | |||||
type Rep Verbosity | |||||
Defined in Distribution.Verbosity type Rep Verbosity = D1 ('MetaData "Verbosity" "Distribution.Verbosity" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "Verbosity" 'PrefixI 'True) (S1 ('MetaSel ('Just "vLevel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VerbosityLevel) :*: (S1 ('MetaSel ('Just "vFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set VerbosityFlag)) :*: S1 ('MetaSel ('Just "vQuiet") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) |
Constructors
Compiler | |
Fields
|
Instances
Structured Compiler | |||||
Defined in Distribution.Simple.Compiler | |||||
Binary Compiler | |||||
Generic Compiler | |||||
Defined in Distribution.Simple.Compiler Associated Types
| |||||
Read Compiler | |||||
Show Compiler | |||||
Eq Compiler | |||||
type Rep Compiler | |||||
Defined in Distribution.Simple.Compiler type Rep Compiler = D1 ('MetaData "Compiler" "Distribution.Simple.Compiler" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "Compiler" 'PrefixI 'True) ((S1 ('MetaSel ('Just "compilerId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CompilerId) :*: (S1 ('MetaSel ('Just "compilerAbiTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AbiTag) :*: S1 ('MetaSel ('Just "compilerCompat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [CompilerId]))) :*: (S1 ('MetaSel ('Just "compilerLanguages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Language, CompilerFlag)]) :*: (S1 ('MetaSel ('Just "compilerExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Extension, Maybe CompilerFlag)]) :*: S1 ('MetaSel ('Just "compilerProperties") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map String String)))))) |
Constructors
Platform Arch OS |
Instances
Parsec Platform | |||||
Defined in Distribution.System | |||||
Pretty Platform | |||||
Defined in Distribution.System | |||||
Structured Platform | |||||
Defined in Distribution.System | |||||
Binary Platform | |||||
NFData Platform | |||||
Defined in Distribution.System | |||||
Data Platform | |||||
Defined in Distribution.System Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Platform -> c Platform # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Platform # toConstr :: Platform -> Constr # dataTypeOf :: Platform -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Platform) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Platform) # gmapT :: (forall b. Data b => b -> b) -> Platform -> Platform # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Platform -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Platform -> r # gmapQ :: (forall d. Data d => d -> u) -> Platform -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Platform -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Platform -> m Platform # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Platform -> m Platform # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Platform -> m Platform # | |||||
Generic Platform | |||||
Defined in Distribution.System Associated Types
| |||||
Read Platform | |||||
Show Platform | |||||
Eq Platform | |||||
Ord Platform | |||||
Defined in Distribution.System | |||||
type Rep Platform | |||||
Defined in Distribution.System type Rep Platform = D1 ('MetaData "Platform" "Distribution.System" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "Platform" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Arch) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OS))) |
Instances
Pretty Suffix | |||||
Defined in Distribution.Simple.PreProcess.Types | |||||
Structured Suffix | |||||
Defined in Distribution.Simple.PreProcess.Types | |||||
Binary Suffix | |||||
IsString Suffix | |||||
Defined in Distribution.Simple.PreProcess.Types Methods fromString :: String -> Suffix # | |||||
Generic Suffix | |||||
Defined in Distribution.Simple.PreProcess.Types Associated Types
| |||||
Show Suffix | |||||
Eq Suffix | |||||
Ord Suffix | |||||
Defined in Distribution.Simple.PreProcess.Types | |||||
type Rep Suffix | |||||
Defined in Distribution.Simple.PreProcess.Types |
Package information
data LocalBuildConfig #
Instances
Structured LocalBuildConfig | |||||
Defined in Distribution.Types.LocalBuildConfig Methods structure :: Proxy LocalBuildConfig -> Structure structureHash' :: Tagged LocalBuildConfig MD5 | |||||
Binary LocalBuildConfig | |||||
Defined in Distribution.Types.LocalBuildConfig Methods put :: LocalBuildConfig -> Put # get :: Get LocalBuildConfig # putList :: [LocalBuildConfig] -> Put # | |||||
Generic LocalBuildConfig | |||||
Defined in Distribution.Types.LocalBuildConfig Associated Types
Methods from :: LocalBuildConfig -> Rep LocalBuildConfig x # to :: Rep LocalBuildConfig x -> LocalBuildConfig # | |||||
Read LocalBuildConfig | |||||
Defined in Distribution.Types.LocalBuildConfig Methods readsPrec :: Int -> ReadS LocalBuildConfig # readList :: ReadS [LocalBuildConfig] # | |||||
Show LocalBuildConfig | |||||
Defined in Distribution.Types.LocalBuildConfig Methods showsPrec :: Int -> LocalBuildConfig -> ShowS # show :: LocalBuildConfig -> String # showList :: [LocalBuildConfig] -> ShowS # | |||||
type Rep LocalBuildConfig | |||||
Defined in Distribution.Types.LocalBuildConfig type Rep LocalBuildConfig = D1 ('MetaData "LocalBuildConfig" "Distribution.Types.LocalBuildConfig" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "LocalBuildConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "extraConfigArgs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "withPrograms") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProgramDb) :*: S1 ('MetaSel ('Just "withBuildOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildOptions)))) |
data LocalBuildInfo #
Instances
Structured LocalBuildInfo | |||||
Defined in Distribution.Types.LocalBuildInfo | |||||
Binary LocalBuildInfo | |||||
Defined in Distribution.Types.LocalBuildInfo Methods put :: LocalBuildInfo -> Put # get :: Get LocalBuildInfo # putList :: [LocalBuildInfo] -> Put # | |||||
Generic LocalBuildInfo | |||||
Defined in Distribution.Types.LocalBuildInfo Associated Types
Methods from :: LocalBuildInfo -> Rep LocalBuildInfo x # to :: Rep LocalBuildInfo x -> LocalBuildInfo # | |||||
Read LocalBuildInfo | |||||
Defined in Distribution.Types.LocalBuildInfo Methods readsPrec :: Int -> ReadS LocalBuildInfo # readList :: ReadS [LocalBuildInfo] # | |||||
Show LocalBuildInfo | |||||
Defined in Distribution.Types.LocalBuildInfo Methods showsPrec :: Int -> LocalBuildInfo -> ShowS # show :: LocalBuildInfo -> String # showList :: [LocalBuildInfo] -> ShowS # | |||||
type Rep LocalBuildInfo | |||||
Defined in Distribution.Types.LocalBuildInfo type Rep LocalBuildInfo = D1 ('MetaData "LocalBuildInfo" "Distribution.Types.LocalBuildInfo" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "NewLocalBuildInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "localBuildDescr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalBuildDescr) :*: S1 ('MetaSel ('Just "localBuildConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalBuildConfig))) |
data PackageBuildDescr #
Instances
Structured PackageBuildDescr | |||||
Defined in Distribution.Types.LocalBuildConfig Methods structure :: Proxy PackageBuildDescr -> Structure structureHash' :: Tagged PackageBuildDescr MD5 | |||||
Binary PackageBuildDescr | |||||
Defined in Distribution.Types.LocalBuildConfig Methods put :: PackageBuildDescr -> Put # get :: Get PackageBuildDescr # putList :: [PackageBuildDescr] -> Put # | |||||
Generic PackageBuildDescr | |||||
Defined in Distribution.Types.LocalBuildConfig Associated Types
Methods from :: PackageBuildDescr -> Rep PackageBuildDescr x # to :: Rep PackageBuildDescr x -> PackageBuildDescr # | |||||
Read PackageBuildDescr | |||||
Defined in Distribution.Types.LocalBuildConfig Methods readsPrec :: Int -> ReadS PackageBuildDescr # readList :: ReadS [PackageBuildDescr] # | |||||
Show PackageBuildDescr | |||||
Defined in Distribution.Types.LocalBuildConfig Methods showsPrec :: Int -> PackageBuildDescr -> ShowS # show :: PackageBuildDescr -> String # showList :: [PackageBuildDescr] -> ShowS # | |||||
type Rep PackageBuildDescr | |||||
Defined in Distribution.Types.LocalBuildConfig type Rep PackageBuildDescr = D1 ('MetaData "PackageBuildDescr" "Distribution.Types.LocalBuildConfig" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "PackageBuildDescr" 'PrefixI 'True) (((S1 ('MetaSel ('Just "configFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConfigFlags) :*: S1 ('MetaSel ('Just "flagAssignment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FlagAssignment)) :*: (S1 ('MetaSel ('Just "componentEnabledSpec") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentRequestedSpec) :*: (S1 ('MetaSel ('Just "compiler") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Compiler) :*: S1 ('MetaSel ('Just "hostPlatform") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Platform)))) :*: ((S1 ('MetaSel ('Just "pkgDescrFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (SymbolicPath Pkg 'File))) :*: S1 ('MetaSel ('Just "localPkgDescr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageDescription)) :*: (S1 ('MetaSel ('Just "installDirTemplates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InstallDirTemplates) :*: (S1 ('MetaSel ('Just "withPackageDB") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageDBStack) :*: S1 ('MetaSel ('Just "extraCoverageFor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId])))))) |
data PackageDescription #
Constructors
PackageDescription | |
Fields
|
Instances
Package PackageDescription | |||||
Defined in Distribution.Types.PackageDescription Methods packageId :: PackageDescription -> PackageIdentifier | |||||
HasBuildInfos PackageDescription | |||||
Defined in Distribution.Types.PackageDescription Methods traverseBuildInfos :: Traversal' PackageDescription BuildInfo | |||||
Structured PackageDescription | |||||
Defined in Distribution.Types.PackageDescription Methods structure :: Proxy PackageDescription -> Structure structureHash' :: Tagged PackageDescription MD5 | |||||
Binary PackageDescription | |||||
Defined in Distribution.Types.PackageDescription Methods put :: PackageDescription -> Put # get :: Get PackageDescription # putList :: [PackageDescription] -> Put # | |||||
NFData PackageDescription | |||||
Defined in Distribution.Types.PackageDescription Methods rnf :: PackageDescription -> () # | |||||
Data PackageDescription | |||||
Defined in Distribution.Types.PackageDescription Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageDescription -> c PackageDescription # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PackageDescription # toConstr :: PackageDescription -> Constr # dataTypeOf :: PackageDescription -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PackageDescription) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PackageDescription) # gmapT :: (forall b. Data b => b -> b) -> PackageDescription -> PackageDescription # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageDescription -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageDescription -> r # gmapQ :: (forall d. Data d => d -> u) -> PackageDescription -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageDescription -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageDescription -> m PackageDescription # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageDescription -> m PackageDescription # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageDescription -> m PackageDescription # | |||||
Generic PackageDescription | |||||
Defined in Distribution.Types.PackageDescription Associated Types
Methods from :: PackageDescription -> Rep PackageDescription x # to :: Rep PackageDescription x -> PackageDescription # | |||||
Read PackageDescription | |||||
Defined in Distribution.Types.PackageDescription Methods readsPrec :: Int -> ReadS PackageDescription # readList :: ReadS [PackageDescription] # | |||||
Show PackageDescription | |||||
Defined in Distribution.Types.PackageDescription Methods showsPrec :: Int -> PackageDescription -> ShowS # show :: PackageDescription -> String # showList :: [PackageDescription] -> ShowS # | |||||
Eq PackageDescription | |||||
Defined in Distribution.Types.PackageDescription Methods (==) :: PackageDescription -> PackageDescription -> Bool # (/=) :: PackageDescription -> PackageDescription -> Bool # | |||||
Ord PackageDescription | |||||
Defined in Distribution.Types.PackageDescription Methods compare :: PackageDescription -> PackageDescription -> Ordering # (<) :: PackageDescription -> PackageDescription -> Bool # (<=) :: PackageDescription -> PackageDescription -> Bool # (>) :: PackageDescription -> PackageDescription -> Bool # (>=) :: PackageDescription -> PackageDescription -> Bool # max :: PackageDescription -> PackageDescription -> PackageDescription # min :: PackageDescription -> PackageDescription -> PackageDescription # | |||||
type Rep PackageDescription | |||||
Defined in Distribution.Types.PackageDescription type Rep PackageDescription = D1 ('MetaData "PackageDescription" "Distribution.Types.PackageDescription" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "PackageDescription" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "specVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CabalSpecVersion) :*: (S1 ('MetaSel ('Just "package") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageIdentifier) :*: S1 ('MetaSel ('Just "licenseRaw") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either License License)))) :*: ((S1 ('MetaSel ('Just "licenseFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath Pkg 'File]) :*: S1 ('MetaSel ('Just "copyright") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText)) :*: (S1 ('MetaSel ('Just "maintainer") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "author") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText)))) :*: (((S1 ('MetaSel ('Just "stability") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "testedWith") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(CompilerFlavor, VersionRange)])) :*: (S1 ('MetaSel ('Just "homepage") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "pkgUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText))) :*: ((S1 ('MetaSel ('Just "bugReports") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "sourceRepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SourceRepo])) :*: (S1 ('MetaSel ('Just "synopsis") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "description") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText))))) :*: ((((S1 ('MetaSel ('Just "category") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "customFieldsPD") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, String)])) :*: (S1 ('MetaSel ('Just "buildTypeRaw") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe BuildType)) :*: S1 ('MetaSel ('Just "setupBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SetupBuildInfo)))) :*: ((S1 ('MetaSel ('Just "library") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Library)) :*: S1 ('MetaSel ('Just "subLibraries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Library])) :*: (S1 ('MetaSel ('Just "executables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Executable]) :*: S1 ('MetaSel ('Just "foreignLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ForeignLib])))) :*: (((S1 ('MetaSel ('Just "testSuites") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TestSuite]) :*: S1 ('MetaSel ('Just "benchmarks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Benchmark])) :*: (S1 ('MetaSel ('Just "dataFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath DataDir 'File]) :*: S1 ('MetaSel ('Just "dataDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SymbolicPath Pkg ('Dir DataDir))))) :*: ((S1 ('MetaSel ('Just "extraSrcFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath Pkg 'File]) :*: S1 ('MetaSel ('Just "extraTmpFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath Pkg 'File])) :*: (S1 ('MetaSel ('Just "extraDocFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath Pkg 'File]) :*: S1 ('MetaSel ('Just "extraFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath Pkg 'File]))))))) |
Component information
Constructors
CLib Library | |
CFLib ForeignLib | |
CExe Executable | |
CTest TestSuite | |
CBench Benchmark |
Instances
HasBuildInfo Component | |||||
Defined in Distribution.Types.Component Methods buildInfo :: Lens' Component BuildInfo buildable :: Lens' Component Bool buildTools :: Lens' Component [LegacyExeDependency] buildToolDepends :: Lens' Component [ExeDependency] cppOptions :: Lens' Component [String] asmOptions :: Lens' Component [String] cmmOptions :: Lens' Component [String] ccOptions :: Lens' Component [String] cxxOptions :: Lens' Component [String] jsppOptions :: Lens' Component [String] ldOptions :: Lens' Component [String] hsc2hsOptions :: Lens' Component [String] pkgconfigDepends :: Lens' Component [PkgconfigDependency] frameworks :: Lens' Component [RelativePath Framework 'File] extraFrameworkDirs :: Lens' Component [SymbolicPath Pkg ('Dir Framework)] asmSources :: Lens' Component [SymbolicPath Pkg 'File] cmmSources :: Lens' Component [SymbolicPath Pkg 'File] cSources :: Lens' Component [SymbolicPath Pkg 'File] cxxSources :: Lens' Component [SymbolicPath Pkg 'File] jsSources :: Lens' Component [SymbolicPath Pkg 'File] hsSourceDirs :: Lens' Component [SymbolicPath Pkg ('Dir Source)] otherModules :: Lens' Component [ModuleName] virtualModules :: Lens' Component [ModuleName] autogenModules :: Lens' Component [ModuleName] defaultLanguage :: Lens' Component (Maybe Language) otherLanguages :: Lens' Component [Language] defaultExtensions :: Lens' Component [Extension] otherExtensions :: Lens' Component [Extension] oldExtensions :: Lens' Component [Extension] extraLibs :: Lens' Component [String] extraLibsStatic :: Lens' Component [String] extraGHCiLibs :: Lens' Component [String] extraBundledLibs :: Lens' Component [String] extraLibFlavours :: Lens' Component [String] extraDynLibFlavours :: Lens' Component [String] extraLibDirs :: Lens' Component [SymbolicPath Pkg ('Dir Lib)] extraLibDirsStatic :: Lens' Component [SymbolicPath Pkg ('Dir Lib)] includeDirs :: Lens' Component [SymbolicPath Pkg ('Dir Include)] includes :: Lens' Component [SymbolicPath Include 'File] autogenIncludes :: Lens' Component [RelativePath Include 'File] installIncludes :: Lens' Component [RelativePath Include 'File] options :: Lens' Component (PerCompilerFlavor [String]) profOptions :: Lens' Component (PerCompilerFlavor [String]) sharedOptions :: Lens' Component (PerCompilerFlavor [String]) profSharedOptions :: Lens' Component (PerCompilerFlavor [String]) staticOptions :: Lens' Component (PerCompilerFlavor [String]) customFieldsBI :: Lens' Component [(String, String)] targetBuildDepends :: Lens' Component [Dependency] | |||||
Structured Component | |||||
Defined in Distribution.Types.Component | |||||
Binary Component | |||||
Semigroup Component | |||||
Generic Component | |||||
Defined in Distribution.Types.Component Associated Types
| |||||
Read Component | |||||
Show Component | |||||
Eq Component | |||||
type Rep Component | |||||
Defined in Distribution.Types.Component type Rep Component = D1 ('MetaData "Component" "Distribution.Types.Component" "Cabal-syntax-3.16.0.0-inplace" 'False) ((C1 ('MetaCons "CLib" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Library)) :+: C1 ('MetaCons "CFLib" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ForeignLib))) :+: (C1 ('MetaCons "CExe" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Executable)) :+: (C1 ('MetaCons "CTest" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TestSuite)) :+: C1 ('MetaCons "CBench" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Benchmark))))) |
data ComponentName #
Constructors
CLibName LibraryName | |
CNotLibName NotLibComponentName |
Bundled Patterns
pattern CBenchName :: UnqualComponentName -> ComponentName | |
pattern CExeName :: UnqualComponentName -> ComponentName | |
pattern CFLibName :: UnqualComponentName -> ComponentName | |
pattern CTestName :: UnqualComponentName -> ComponentName |
Instances
Parsec ComponentName | |||||
Defined in Distribution.Types.ComponentName Methods parsec :: CabalParsing m => m ComponentName | |||||
Pretty ComponentName | |||||
Defined in Distribution.Types.ComponentName | |||||
Structured ComponentName | |||||
Defined in Distribution.Types.ComponentName | |||||
Binary ComponentName | |||||
Defined in Distribution.Types.ComponentName | |||||
Generic ComponentName | |||||
Defined in Distribution.Types.ComponentName Associated Types
| |||||
Read ComponentName | |||||
Defined in Distribution.Types.ComponentName Methods readsPrec :: Int -> ReadS ComponentName # readList :: ReadS [ComponentName] # | |||||
Show ComponentName | |||||
Defined in Distribution.Types.ComponentName Methods showsPrec :: Int -> ComponentName -> ShowS # show :: ComponentName -> String # showList :: [ComponentName] -> ShowS # | |||||
Eq ComponentName | |||||
Defined in Distribution.Types.ComponentName Methods (==) :: ComponentName -> ComponentName -> Bool # (/=) :: ComponentName -> ComponentName -> Bool # | |||||
Ord ComponentName | |||||
Defined in Distribution.Types.ComponentName Methods compare :: ComponentName -> ComponentName -> Ordering # (<) :: ComponentName -> ComponentName -> Bool # (<=) :: ComponentName -> ComponentName -> Bool # (>) :: ComponentName -> ComponentName -> Bool # (>=) :: ComponentName -> ComponentName -> Bool # max :: ComponentName -> ComponentName -> ComponentName # min :: ComponentName -> ComponentName -> ComponentName # | |||||
type Rep ComponentName | |||||
Defined in Distribution.Types.ComponentName type Rep ComponentName = D1 ('MetaData "ComponentName" "Distribution.Types.ComponentName" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "CLibName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LibraryName)) :+: C1 ('MetaCons "CNotLibName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NotLibComponentName))) |
componentName :: Component -> ComponentName #
Constructors
BuildInfo | |
Fields
|
Instances
FromBuildInfo BuildInfo | |||||
Defined in Distribution.PackageDescription.Parsec Methods fromBuildInfo' :: UnqualComponentName -> BuildInfo -> BuildInfo | |||||
HasBuildInfo BuildInfo | |||||
Defined in Distribution.Types.BuildInfo.Lens Methods buildInfo :: Lens' BuildInfo BuildInfo buildable :: Lens' BuildInfo Bool buildTools :: Lens' BuildInfo [LegacyExeDependency] buildToolDepends :: Lens' BuildInfo [ExeDependency] cppOptions :: Lens' BuildInfo [String] asmOptions :: Lens' BuildInfo [String] cmmOptions :: Lens' BuildInfo [String] ccOptions :: Lens' BuildInfo [String] cxxOptions :: Lens' BuildInfo [String] jsppOptions :: Lens' BuildInfo [String] ldOptions :: Lens' BuildInfo [String] hsc2hsOptions :: Lens' BuildInfo [String] pkgconfigDepends :: Lens' BuildInfo [PkgconfigDependency] frameworks :: Lens' BuildInfo [RelativePath Framework 'File] extraFrameworkDirs :: Lens' BuildInfo [SymbolicPath Pkg ('Dir Framework)] asmSources :: Lens' BuildInfo [SymbolicPath Pkg 'File] cmmSources :: Lens' BuildInfo [SymbolicPath Pkg 'File] cSources :: Lens' BuildInfo [SymbolicPath Pkg 'File] cxxSources :: Lens' BuildInfo [SymbolicPath Pkg 'File] jsSources :: Lens' BuildInfo [SymbolicPath Pkg 'File] hsSourceDirs :: Lens' BuildInfo [SymbolicPath Pkg ('Dir Source)] otherModules :: Lens' BuildInfo [ModuleName] virtualModules :: Lens' BuildInfo [ModuleName] autogenModules :: Lens' BuildInfo [ModuleName] defaultLanguage :: Lens' BuildInfo (Maybe Language) otherLanguages :: Lens' BuildInfo [Language] defaultExtensions :: Lens' BuildInfo [Extension] otherExtensions :: Lens' BuildInfo [Extension] oldExtensions :: Lens' BuildInfo [Extension] extraLibs :: Lens' BuildInfo [String] extraLibsStatic :: Lens' BuildInfo [String] extraGHCiLibs :: Lens' BuildInfo [String] extraBundledLibs :: Lens' BuildInfo [String] extraLibFlavours :: Lens' BuildInfo [String] extraDynLibFlavours :: Lens' BuildInfo [String] extraLibDirs :: Lens' BuildInfo [SymbolicPath Pkg ('Dir Lib)] extraLibDirsStatic :: Lens' BuildInfo [SymbolicPath Pkg ('Dir Lib)] includeDirs :: Lens' BuildInfo [SymbolicPath Pkg ('Dir Include)] includes :: Lens' BuildInfo [SymbolicPath Include 'File] autogenIncludes :: Lens' BuildInfo [RelativePath Include 'File] installIncludes :: Lens' BuildInfo [RelativePath Include 'File] options :: Lens' BuildInfo (PerCompilerFlavor [String]) profOptions :: Lens' BuildInfo (PerCompilerFlavor [String]) sharedOptions :: Lens' BuildInfo (PerCompilerFlavor [String]) profSharedOptions :: Lens' BuildInfo (PerCompilerFlavor [String]) staticOptions :: Lens' BuildInfo (PerCompilerFlavor [String]) customFieldsBI :: Lens' BuildInfo [(String, String)] targetBuildDepends :: Lens' BuildInfo [Dependency] | |||||
Structured BuildInfo | |||||
Defined in Distribution.Types.BuildInfo | |||||
Binary BuildInfo | |||||
NFData BuildInfo | |||||
Defined in Distribution.Types.BuildInfo | |||||
Monoid BuildInfo | |||||
Semigroup BuildInfo | |||||
Data BuildInfo | |||||
Defined in Distribution.Types.BuildInfo Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BuildInfo -> c BuildInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BuildInfo # toConstr :: BuildInfo -> Constr # dataTypeOf :: BuildInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BuildInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuildInfo) # gmapT :: (forall b. Data b => b -> b) -> BuildInfo -> BuildInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BuildInfo -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BuildInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> BuildInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BuildInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo # | |||||
Generic BuildInfo | |||||
Defined in Distribution.Types.BuildInfo Associated Types
| |||||
Read BuildInfo | |||||
Show BuildInfo | |||||
Eq BuildInfo | |||||
Ord BuildInfo | |||||
type Rep BuildInfo | |||||
Defined in Distribution.Types.BuildInfo type Rep BuildInfo = D1 ('MetaData "BuildInfo" "Distribution.Types.BuildInfo" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "BuildInfo" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "buildable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "buildTools") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [LegacyExeDependency]) :*: S1 ('MetaSel ('Just "buildToolDepends") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ExeDependency]))) :*: (S1 ('MetaSel ('Just "cppOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "asmOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "cmmOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))) :*: ((S1 ('MetaSel ('Just "ccOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "cxxOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "jsppOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :*: (S1 ('MetaSel ('Just "ldOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "hsc2hsOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "pkgconfigDepends") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PkgconfigDependency]))))) :*: (((S1 ('MetaSel ('Just "frameworks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath Framework 'File]) :*: (S1 ('MetaSel ('Just "extraFrameworkDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg ('Dir Framework)]) :*: S1 ('MetaSel ('Just "asmSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg 'File]))) :*: (S1 ('MetaSel ('Just "cmmSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg 'File]) :*: (S1 ('MetaSel ('Just "cSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg 'File]) :*: S1 ('MetaSel ('Just "cxxSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg 'File])))) :*: ((S1 ('MetaSel ('Just "jsSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg 'File]) :*: (S1 ('MetaSel ('Just "hsSourceDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg ('Dir Source)]) :*: S1 ('MetaSel ('Just "otherModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName]))) :*: (S1 ('MetaSel ('Just "virtualModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName]) :*: (S1 ('MetaSel ('Just "autogenModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName]) :*: S1 ('MetaSel ('Just "defaultLanguage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Language))))))) :*: ((((S1 ('MetaSel ('Just "otherLanguages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Language]) :*: (S1 ('MetaSel ('Just "defaultExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Extension]) :*: S1 ('MetaSel ('Just "otherExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Extension]))) :*: (S1 ('MetaSel ('Just "oldExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Extension]) :*: (S1 ('MetaSel ('Just "extraLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "extraLibsStatic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))) :*: ((S1 ('MetaSel ('Just "extraGHCiLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "extraBundledLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "extraLibFlavours") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :*: (S1 ('MetaSel ('Just "extraDynLibFlavours") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "extraLibDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg ('Dir Lib)]) :*: S1 ('MetaSel ('Just "extraLibDirsStatic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg ('Dir Lib)]))))) :*: (((S1 ('MetaSel ('Just "includeDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Pkg ('Dir Include)]) :*: (S1 ('MetaSel ('Just "includes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SymbolicPath Include 'File]) :*: S1 ('MetaSel ('Just "autogenIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath Include 'File]))) :*: (S1 ('MetaSel ('Just "installIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath Include 'File]) :*: (S1 ('MetaSel ('Just "options") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCompilerFlavor [String])) :*: S1 ('MetaSel ('Just "profOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCompilerFlavor [String]))))) :*: ((S1 ('MetaSel ('Just "sharedOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCompilerFlavor [String])) :*: (S1 ('MetaSel ('Just "profSharedOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCompilerFlavor [String])) :*: S1 ('MetaSel ('Just "staticOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCompilerFlavor [String])))) :*: (S1 ('MetaSel ('Just "customFieldsBI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, String)]) :*: (S1 ('MetaSel ('Just "targetBuildDepends") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Dependency]) :*: S1 ('MetaSel ('Just "mixins") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Mixin])))))))) |
data TargetInfo #
Constructors
TargetInfo | |
Fields |
Instances
IsNode TargetInfo | |||||
Defined in Distribution.Types.TargetInfo Associated Types
| |||||
Structured TargetInfo | |||||
Defined in Distribution.Types.TargetInfo | |||||
Binary TargetInfo | |||||
Defined in Distribution.Types.TargetInfo | |||||
Generic TargetInfo | |||||
Defined in Distribution.Types.TargetInfo Associated Types
| |||||
Show TargetInfo | |||||
Defined in Distribution.Types.TargetInfo Methods showsPrec :: Int -> TargetInfo -> ShowS # show :: TargetInfo -> String # showList :: [TargetInfo] -> ShowS # | |||||
type Key TargetInfo | |||||
Defined in Distribution.Types.TargetInfo type Key TargetInfo = UnitId | |||||
type Rep TargetInfo | |||||
Defined in Distribution.Types.TargetInfo type Rep TargetInfo = D1 ('MetaData "TargetInfo" "Distribution.Types.TargetInfo" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "TargetInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "targetCLBI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentLocalBuildInfo) :*: S1 ('MetaSel ('Just "targetComponent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Component))) |
data ComponentLocalBuildInfo #
Constructors
LibComponentLocalBuildInfo | |
Fields
| |
FLibComponentLocalBuildInfo | |
Fields
| |
ExeComponentLocalBuildInfo | |
Fields
| |
TestComponentLocalBuildInfo | |
Fields
| |
BenchComponentLocalBuildInfo | |
Fields
|
Instances
IsNode ComponentLocalBuildInfo | |||||
Defined in Distribution.Types.ComponentLocalBuildInfo Associated Types
Methods nodeKey :: ComponentLocalBuildInfo -> Key ComponentLocalBuildInfo nodeNeighbors :: ComponentLocalBuildInfo -> [Key ComponentLocalBuildInfo] | |||||
Structured ComponentLocalBuildInfo | |||||
Defined in Distribution.Types.ComponentLocalBuildInfo Methods structure :: Proxy ComponentLocalBuildInfo -> Structure structureHash' :: Tagged ComponentLocalBuildInfo MD5 | |||||
Binary ComponentLocalBuildInfo | |||||
Defined in Distribution.Types.ComponentLocalBuildInfo Methods put :: ComponentLocalBuildInfo -> Put # get :: Get ComponentLocalBuildInfo # putList :: [ComponentLocalBuildInfo] -> Put # | |||||
Generic ComponentLocalBuildInfo | |||||
Defined in Distribution.Types.ComponentLocalBuildInfo Associated Types
Methods from :: ComponentLocalBuildInfo -> Rep ComponentLocalBuildInfo x # to :: Rep ComponentLocalBuildInfo x -> ComponentLocalBuildInfo # | |||||
Read ComponentLocalBuildInfo | |||||
Defined in Distribution.Types.ComponentLocalBuildInfo | |||||
Show ComponentLocalBuildInfo | |||||
Defined in Distribution.Types.ComponentLocalBuildInfo Methods showsPrec :: Int -> ComponentLocalBuildInfo -> ShowS # show :: ComponentLocalBuildInfo -> String # showList :: [ComponentLocalBuildInfo] -> ShowS # | |||||
type Key ComponentLocalBuildInfo | |||||
Defined in Distribution.Types.ComponentLocalBuildInfo type Key ComponentLocalBuildInfo = UnitId | |||||
type Rep ComponentLocalBuildInfo | |||||
Defined in Distribution.Types.ComponentLocalBuildInfo type Rep ComponentLocalBuildInfo = D1 ('MetaData "ComponentLocalBuildInfo" "Distribution.Types.ComponentLocalBuildInfo" "Cabal-3.16.0.0-inplace" 'False) ((C1 ('MetaCons "LibComponentLocalBuildInfo" 'PrefixI 'True) (((S1 ('MetaSel ('Just "componentLocalName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentName) :*: (S1 ('MetaSel ('Just "componentComponentId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentId) :*: S1 ('MetaSel ('Just "componentUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId))) :*: (S1 ('MetaSel ('Just "componentIsIndefinite_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "componentInstantiatedWith") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ModuleName, OpenModule)]) :*: S1 ('MetaSel ('Just "componentPackageDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(UnitId, MungedPackageId)])))) :*: ((S1 ('MetaSel ('Just "componentIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(OpenUnitId, ModuleRenaming)]) :*: (S1 ('MetaSel ('Just "componentExeDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]) :*: S1 ('MetaSel ('Just "componentInternalDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]))) :*: ((S1 ('MetaSel ('Just "componentCompatPackageKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "componentCompatPackageName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MungedPackageName)) :*: (S1 ('MetaSel ('Just "componentExposedModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ExposedModule]) :*: S1 ('MetaSel ('Just "componentIsPublic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))) :+: C1 ('MetaCons "FLibComponentLocalBuildInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "componentLocalName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentName) :*: (S1 ('MetaSel ('Just "componentComponentId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentId) :*: S1 ('MetaSel ('Just "componentUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId))) :*: ((S1 ('MetaSel ('Just "componentPackageDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(UnitId, MungedPackageId)]) :*: S1 ('MetaSel ('Just "componentIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(OpenUnitId, ModuleRenaming)])) :*: (S1 ('MetaSel ('Just "componentExeDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]) :*: S1 ('MetaSel ('Just "componentInternalDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]))))) :+: (C1 ('MetaCons "ExeComponentLocalBuildInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "componentLocalName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentName) :*: (S1 ('MetaSel ('Just "componentComponentId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentId) :*: S1 ('MetaSel ('Just "componentUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId))) :*: ((S1 ('MetaSel ('Just "componentPackageDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(UnitId, MungedPackageId)]) :*: S1 ('MetaSel ('Just "componentIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(OpenUnitId, ModuleRenaming)])) :*: (S1 ('MetaSel ('Just "componentExeDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]) :*: S1 ('MetaSel ('Just "componentInternalDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId])))) :+: (C1 ('MetaCons "TestComponentLocalBuildInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "componentLocalName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentName) :*: (S1 ('MetaSel ('Just "componentComponentId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentId) :*: S1 ('MetaSel ('Just "componentUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId))) :*: ((S1 ('MetaSel ('Just "componentPackageDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(UnitId, MungedPackageId)]) :*: S1 ('MetaSel ('Just "componentIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(OpenUnitId, ModuleRenaming)])) :*: (S1 ('MetaSel ('Just "componentExeDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]) :*: S1 ('MetaSel ('Just "componentInternalDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId])))) :+: C1 ('MetaCons "BenchComponentLocalBuildInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "componentLocalName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentName) :*: (S1 ('MetaSel ('Just "componentComponentId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentId) :*: S1 ('MetaSel ('Just "componentUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId))) :*: ((S1 ('MetaSel ('Just "componentPackageDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(UnitId, MungedPackageId)]) :*: S1 ('MetaSel ('Just "componentIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(OpenUnitId, ModuleRenaming)])) :*: (S1 ('MetaSel ('Just "componentExeDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]) :*: S1 ('MetaSel ('Just "componentInternalDeps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId]))))))) |
Components
Constructors
Library | |
Fields
|
Instances
HasBuildInfo Library | |||||
Defined in Distribution.Types.Library Methods buildInfo :: Lens' Library BuildInfo buildable :: Lens' Library Bool buildTools :: Lens' Library [LegacyExeDependency] buildToolDepends :: Lens' Library [ExeDependency] cppOptions :: Lens' Library [String] asmOptions :: Lens' Library [String] cmmOptions :: Lens' Library [String] ccOptions :: Lens' Library [String] cxxOptions :: Lens' Library [String] jsppOptions :: Lens' Library [String] ldOptions :: Lens' Library [String] hsc2hsOptions :: Lens' Library [String] pkgconfigDepends :: Lens' Library [PkgconfigDependency] frameworks :: Lens' Library [RelativePath Framework 'File] extraFrameworkDirs :: Lens' Library [SymbolicPath Pkg ('Dir Framework)] asmSources :: Lens' Library [SymbolicPath Pkg 'File] cmmSources :: Lens' Library [SymbolicPath Pkg 'File] cSources :: Lens' Library [SymbolicPath Pkg 'File] cxxSources :: Lens' Library [SymbolicPath Pkg 'File] jsSources :: Lens' Library [SymbolicPath Pkg 'File] hsSourceDirs :: Lens' Library [SymbolicPath Pkg ('Dir Source)] otherModules :: Lens' Library [ModuleName] virtualModules :: Lens' Library [ModuleName] autogenModules :: Lens' Library [ModuleName] defaultLanguage :: Lens' Library (Maybe Language) otherLanguages :: Lens' Library [Language] defaultExtensions :: Lens' Library [Extension] otherExtensions :: Lens' Library [Extension] oldExtensions :: Lens' Library [Extension] extraLibs :: Lens' Library [String] extraLibsStatic :: Lens' Library [String] extraGHCiLibs :: Lens' Library [String] extraBundledLibs :: Lens' Library [String] extraLibFlavours :: Lens' Library [String] extraDynLibFlavours :: Lens' Library [String] extraLibDirs :: Lens' Library [SymbolicPath Pkg ('Dir Lib)] extraLibDirsStatic :: Lens' Library [SymbolicPath Pkg ('Dir Lib)] includeDirs :: Lens' Library [SymbolicPath Pkg ('Dir Include)] includes :: Lens' Library [SymbolicPath Include 'File] autogenIncludes :: Lens' Library [RelativePath Include 'File] installIncludes :: Lens' Library [RelativePath Include 'File] options :: Lens' Library (PerCompilerFlavor [String]) profOptions :: Lens' Library (PerCompilerFlavor [String]) sharedOptions :: Lens' Library (PerCompilerFlavor [String]) profSharedOptions :: Lens' Library (PerCompilerFlavor [String]) staticOptions :: Lens' Library (PerCompilerFlavor [String]) customFieldsBI :: Lens' Library [(String, String)] targetBuildDepends :: Lens' Library [Dependency] | |||||
Structured Library | |||||
Defined in Distribution.Types.Library | |||||
Binary Library | |||||
NFData Library | |||||
Defined in Distribution.Types.Library | |||||
Monoid Library | |||||
Semigroup Library | |||||
Data Library | |||||
Defined in Distribution.Types.Library Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Library -> c Library # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Library # toConstr :: Library -> Constr # dataTypeOf :: Library -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Library) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Library) # gmapT :: (forall b. Data b => b -> b) -> Library -> Library # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Library -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Library -> r # gmapQ :: (forall d. Data d => d -> u) -> Library -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Library -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Library -> m Library # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Library -> m Library # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Library -> m Library # | |||||
Generic Library | |||||
Defined in Distribution.Types.Library Associated Types
| |||||
Read Library | |||||
Show Library | |||||
Eq Library | |||||
Ord Library | |||||
Defined in Distribution.Types.Library | |||||
type Rep Library | |||||
Defined in Distribution.Types.Library type Rep Library = D1 ('MetaData "Library" "Distribution.Types.Library" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "Library" 'PrefixI 'True) ((S1 ('MetaSel ('Just "libName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LibraryName) :*: (S1 ('MetaSel ('Just "exposedModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName]) :*: S1 ('MetaSel ('Just "reexportedModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleReexport]))) :*: ((S1 ('MetaSel ('Just "signatures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName]) :*: S1 ('MetaSel ('Just "libExposed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "libVisibility") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LibraryVisibility) :*: S1 ('MetaSel ('Just "libBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildInfo))))) |
data ForeignLib #
Constructors
ForeignLib | |
Fields
|
Instances
FromBuildInfo ForeignLib | |||||
Defined in Distribution.PackageDescription.Parsec Methods fromBuildInfo' :: UnqualComponentName -> BuildInfo -> ForeignLib | |||||
HasBuildInfo ForeignLib | |||||
Defined in Distribution.Types.ForeignLib Methods buildInfo :: Lens' ForeignLib BuildInfo buildable :: Lens' ForeignLib Bool buildTools :: Lens' ForeignLib [LegacyExeDependency] buildToolDepends :: Lens' ForeignLib [ExeDependency] cppOptions :: Lens' ForeignLib [String] asmOptions :: Lens' ForeignLib [String] cmmOptions :: Lens' ForeignLib [String] ccOptions :: Lens' ForeignLib [String] cxxOptions :: Lens' ForeignLib [String] jsppOptions :: Lens' ForeignLib [String] ldOptions :: Lens' ForeignLib [String] hsc2hsOptions :: Lens' ForeignLib [String] pkgconfigDepends :: Lens' ForeignLib [PkgconfigDependency] frameworks :: Lens' ForeignLib [RelativePath Framework 'File] extraFrameworkDirs :: Lens' ForeignLib [SymbolicPath Pkg ('Dir Framework)] asmSources :: Lens' ForeignLib [SymbolicPath Pkg 'File] cmmSources :: Lens' ForeignLib [SymbolicPath Pkg 'File] cSources :: Lens' ForeignLib [SymbolicPath Pkg 'File] cxxSources :: Lens' ForeignLib [SymbolicPath Pkg 'File] jsSources :: Lens' ForeignLib [SymbolicPath Pkg 'File] hsSourceDirs :: Lens' ForeignLib [SymbolicPath Pkg ('Dir Source)] otherModules :: Lens' ForeignLib [ModuleName] virtualModules :: Lens' ForeignLib [ModuleName] autogenModules :: Lens' ForeignLib [ModuleName] defaultLanguage :: Lens' ForeignLib (Maybe Language) otherLanguages :: Lens' ForeignLib [Language] defaultExtensions :: Lens' ForeignLib [Extension] otherExtensions :: Lens' ForeignLib [Extension] oldExtensions :: Lens' ForeignLib [Extension] extraLibs :: Lens' ForeignLib [String] extraLibsStatic :: Lens' ForeignLib [String] extraGHCiLibs :: Lens' ForeignLib [String] extraBundledLibs :: Lens' ForeignLib [String] extraLibFlavours :: Lens' ForeignLib [String] extraDynLibFlavours :: Lens' ForeignLib [String] extraLibDirs :: Lens' ForeignLib [SymbolicPath Pkg ('Dir Lib)] extraLibDirsStatic :: Lens' ForeignLib [SymbolicPath Pkg ('Dir Lib)] includeDirs :: Lens' ForeignLib [SymbolicPath Pkg ('Dir Include)] includes :: Lens' ForeignLib [SymbolicPath Include 'File] autogenIncludes :: Lens' ForeignLib [RelativePath Include 'File] installIncludes :: Lens' ForeignLib [RelativePath Include 'File] options :: Lens' ForeignLib (PerCompilerFlavor [String]) profOptions :: Lens' ForeignLib (PerCompilerFlavor [String]) sharedOptions :: Lens' ForeignLib (PerCompilerFlavor [String]) profSharedOptions :: Lens' ForeignLib (PerCompilerFlavor [String]) staticOptions :: Lens' ForeignLib (PerCompilerFlavor [String]) customFieldsBI :: Lens' ForeignLib [(String, String)] targetBuildDepends :: Lens' ForeignLib [Dependency] mixins :: Lens' ForeignLib [Mixin] | |||||
Structured ForeignLib | |||||
Defined in Distribution.Types.ForeignLib | |||||
Binary ForeignLib | |||||
Defined in Distribution.Types.ForeignLib | |||||
NFData ForeignLib | |||||
Defined in Distribution.Types.ForeignLib Methods rnf :: ForeignLib -> () # | |||||
Monoid ForeignLib | |||||
Defined in Distribution.Types.ForeignLib Methods mempty :: ForeignLib # mappend :: ForeignLib -> ForeignLib -> ForeignLib # mconcat :: [ForeignLib] -> ForeignLib # | |||||
Semigroup ForeignLib | |||||
Defined in Distribution.Types.ForeignLib Methods (<>) :: ForeignLib -> ForeignLib -> ForeignLib # sconcat :: NonEmpty ForeignLib -> ForeignLib # stimes :: Integral b => b -> ForeignLib -> ForeignLib # | |||||
Data ForeignLib | |||||
Defined in Distribution.Types.ForeignLib Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignLib -> c ForeignLib # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ForeignLib # toConstr :: ForeignLib -> Constr # dataTypeOf :: ForeignLib -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ForeignLib) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ForeignLib) # gmapT :: (forall b. Data b => b -> b) -> ForeignLib -> ForeignLib # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignLib -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignLib -> r # gmapQ :: (forall d. Data d => d -> u) -> ForeignLib -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignLib -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignLib -> m ForeignLib # | |||||
Generic ForeignLib | |||||
Defined in Distribution.Types.ForeignLib Associated Types
| |||||
Read ForeignLib | |||||
Defined in Distribution.Types.ForeignLib Methods readsPrec :: Int -> ReadS ForeignLib # readList :: ReadS [ForeignLib] # readPrec :: ReadPrec ForeignLib # readListPrec :: ReadPrec [ForeignLib] # | |||||
Show ForeignLib | |||||
Defined in Distribution.Types.ForeignLib Methods showsPrec :: Int -> ForeignLib -> ShowS # show :: ForeignLib -> String # showList :: [ForeignLib] -> ShowS # | |||||
Eq ForeignLib | |||||
Defined in Distribution.Types.ForeignLib | |||||
Ord ForeignLib | |||||
Defined in Distribution.Types.ForeignLib Methods compare :: ForeignLib -> ForeignLib -> Ordering # (<) :: ForeignLib -> ForeignLib -> Bool # (<=) :: ForeignLib -> ForeignLib -> Bool # (>) :: ForeignLib -> ForeignLib -> Bool # (>=) :: ForeignLib -> ForeignLib -> Bool # max :: ForeignLib -> ForeignLib -> ForeignLib # min :: ForeignLib -> ForeignLib -> ForeignLib # | |||||
type Rep ForeignLib | |||||
Defined in Distribution.Types.ForeignLib type Rep ForeignLib = D1 ('MetaData "ForeignLib" "Distribution.Types.ForeignLib" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "ForeignLib" 'PrefixI 'True) ((S1 ('MetaSel ('Just "foreignLibName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnqualComponentName) :*: (S1 ('MetaSel ('Just "foreignLibType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ForeignLibType) :*: S1 ('MetaSel ('Just "foreignLibOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ForeignLibOption]))) :*: ((S1 ('MetaSel ('Just "foreignLibBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildInfo) :*: S1 ('MetaSel ('Just "foreignLibVersionInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LibVersionInfo))) :*: (S1 ('MetaSel ('Just "foreignLibVersionLinux") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version)) :*: S1 ('MetaSel ('Just "foreignLibModDefFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RelativePath Source 'File]))))) |
data Executable #
Constructors
Executable | |
Fields
|
Instances
FromBuildInfo Executable | |||||
Defined in Distribution.PackageDescription.Parsec Methods fromBuildInfo' :: UnqualComponentName -> BuildInfo -> Executable | |||||
HasBuildInfo Executable | |||||
Defined in Distribution.Types.Executable Methods buildInfo :: Lens' Executable BuildInfo buildable :: Lens' Executable Bool buildTools :: Lens' Executable [LegacyExeDependency] buildToolDepends :: Lens' Executable [ExeDependency] cppOptions :: Lens' Executable [String] asmOptions :: Lens' Executable [String] cmmOptions :: Lens' Executable [String] ccOptions :: Lens' Executable [String] cxxOptions :: Lens' Executable [String] jsppOptions :: Lens' Executable [String] ldOptions :: Lens' Executable [String] hsc2hsOptions :: Lens' Executable [String] pkgconfigDepends :: Lens' Executable [PkgconfigDependency] frameworks :: Lens' Executable [RelativePath Framework 'File] extraFrameworkDirs :: Lens' Executable [SymbolicPath Pkg ('Dir Framework)] asmSources :: Lens' Executable [SymbolicPath Pkg 'File] cmmSources :: Lens' Executable [SymbolicPath Pkg 'File] cSources :: Lens' Executable [SymbolicPath Pkg 'File] cxxSources :: Lens' Executable [SymbolicPath Pkg 'File] jsSources :: Lens' Executable [SymbolicPath Pkg 'File] hsSourceDirs :: Lens' Executable [SymbolicPath Pkg ('Dir Source)] otherModules :: Lens' Executable [ModuleName] virtualModules :: Lens' Executable [ModuleName] autogenModules :: Lens' Executable [ModuleName] defaultLanguage :: Lens' Executable (Maybe Language) otherLanguages :: Lens' Executable [Language] defaultExtensions :: Lens' Executable [Extension] otherExtensions :: Lens' Executable [Extension] oldExtensions :: Lens' Executable [Extension] extraLibs :: Lens' Executable [String] extraLibsStatic :: Lens' Executable [String] extraGHCiLibs :: Lens' Executable [String] extraBundledLibs :: Lens' Executable [String] extraLibFlavours :: Lens' Executable [String] extraDynLibFlavours :: Lens' Executable [String] extraLibDirs :: Lens' Executable [SymbolicPath Pkg ('Dir Lib)] extraLibDirsStatic :: Lens' Executable [SymbolicPath Pkg ('Dir Lib)] includeDirs :: Lens' Executable [SymbolicPath Pkg ('Dir Include)] includes :: Lens' Executable [SymbolicPath Include 'File] autogenIncludes :: Lens' Executable [RelativePath Include 'File] installIncludes :: Lens' Executable [RelativePath Include 'File] options :: Lens' Executable (PerCompilerFlavor [String]) profOptions :: Lens' Executable (PerCompilerFlavor [String]) sharedOptions :: Lens' Executable (PerCompilerFlavor [String]) profSharedOptions :: Lens' Executable (PerCompilerFlavor [String]) staticOptions :: Lens' Executable (PerCompilerFlavor [String]) customFieldsBI :: Lens' Executable [(String, String)] targetBuildDepends :: Lens' Executable [Dependency] mixins :: Lens' Executable [Mixin] | |||||
Structured Executable | |||||
Defined in Distribution.Types.Executable | |||||
Binary Executable | |||||
Defined in Distribution.Types.Executable | |||||
NFData Executable | |||||
Defined in Distribution.Types.Executable Methods rnf :: Executable -> () # | |||||
Monoid Executable | |||||
Defined in Distribution.Types.Executable Methods mempty :: Executable # mappend :: Executable -> Executable -> Executable # mconcat :: [Executable] -> Executable # | |||||
Semigroup Executable | |||||
Defined in Distribution.Types.Executable Methods (<>) :: Executable -> Executable -> Executable # sconcat :: NonEmpty Executable -> Executable # stimes :: Integral b => b -> Executable -> Executable # | |||||
Data Executable | |||||
Defined in Distribution.Types.Executable Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Executable -> c Executable # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Executable # toConstr :: Executable -> Constr # dataTypeOf :: Executable -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Executable) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Executable) # gmapT :: (forall b. Data b => b -> b) -> Executable -> Executable # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Executable -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Executable -> r # gmapQ :: (forall d. Data d => d -> u) -> Executable -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Executable -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Executable -> m Executable # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Executable -> m Executable # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Executable -> m Executable # | |||||
Generic Executable | |||||
Defined in Distribution.Types.Executable Associated Types
| |||||
Read Executable | |||||
Defined in Distribution.Types.Executable Methods readsPrec :: Int -> ReadS Executable # readList :: ReadS [Executable] # readPrec :: ReadPrec Executable # readListPrec :: ReadPrec [Executable] # | |||||
Show Executable | |||||
Defined in Distribution.Types.Executable Methods showsPrec :: Int -> Executable -> ShowS # show :: Executable -> String # showList :: [Executable] -> ShowS # | |||||
Eq Executable | |||||
Defined in Distribution.Types.Executable | |||||
Ord Executable | |||||
Defined in Distribution.Types.Executable Methods compare :: Executable -> Executable -> Ordering # (<) :: Executable -> Executable -> Bool # (<=) :: Executable -> Executable -> Bool # (>) :: Executable -> Executable -> Bool # (>=) :: Executable -> Executable -> Bool # max :: Executable -> Executable -> Executable # min :: Executable -> Executable -> Executable # | |||||
type Rep Executable | |||||
Defined in Distribution.Types.Executable type Rep Executable = D1 ('MetaData "Executable" "Distribution.Types.Executable" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "Executable" 'PrefixI 'True) ((S1 ('MetaSel ('Just "exeName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnqualComponentName) :*: S1 ('MetaSel ('Just "modulePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RelativePath Source 'File))) :*: (S1 ('MetaSel ('Just "exeScope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExecutableScope) :*: S1 ('MetaSel ('Just "buildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildInfo)))) |
Constructors
TestSuite | |
Fields
|
Instances
HasBuildInfo TestSuite | |||||
Defined in Distribution.Types.TestSuite Methods buildInfo :: Lens' TestSuite BuildInfo buildable :: Lens' TestSuite Bool buildTools :: Lens' TestSuite [LegacyExeDependency] buildToolDepends :: Lens' TestSuite [ExeDependency] cppOptions :: Lens' TestSuite [String] asmOptions :: Lens' TestSuite [String] cmmOptions :: Lens' TestSuite [String] ccOptions :: Lens' TestSuite [String] cxxOptions :: Lens' TestSuite [String] jsppOptions :: Lens' TestSuite [String] ldOptions :: Lens' TestSuite [String] hsc2hsOptions :: Lens' TestSuite [String] pkgconfigDepends :: Lens' TestSuite [PkgconfigDependency] frameworks :: Lens' TestSuite [RelativePath Framework 'File] extraFrameworkDirs :: Lens' TestSuite [SymbolicPath Pkg ('Dir Framework)] asmSources :: Lens' TestSuite [SymbolicPath Pkg 'File] cmmSources :: Lens' TestSuite [SymbolicPath Pkg 'File] cSources :: Lens' TestSuite [SymbolicPath Pkg 'File] cxxSources :: Lens' TestSuite [SymbolicPath Pkg 'File] jsSources :: Lens' TestSuite [SymbolicPath Pkg 'File] hsSourceDirs :: Lens' TestSuite [SymbolicPath Pkg ('Dir Source)] otherModules :: Lens' TestSuite [ModuleName] virtualModules :: Lens' TestSuite [ModuleName] autogenModules :: Lens' TestSuite [ModuleName] defaultLanguage :: Lens' TestSuite (Maybe Language) otherLanguages :: Lens' TestSuite [Language] defaultExtensions :: Lens' TestSuite [Extension] otherExtensions :: Lens' TestSuite [Extension] oldExtensions :: Lens' TestSuite [Extension] extraLibs :: Lens' TestSuite [String] extraLibsStatic :: Lens' TestSuite [String] extraGHCiLibs :: Lens' TestSuite [String] extraBundledLibs :: Lens' TestSuite [String] extraLibFlavours :: Lens' TestSuite [String] extraDynLibFlavours :: Lens' TestSuite [String] extraLibDirs :: Lens' TestSuite [SymbolicPath Pkg ('Dir Lib)] extraLibDirsStatic :: Lens' TestSuite [SymbolicPath Pkg ('Dir Lib)] includeDirs :: Lens' TestSuite [SymbolicPath Pkg ('Dir Include)] includes :: Lens' TestSuite [SymbolicPath Include 'File] autogenIncludes :: Lens' TestSuite [RelativePath Include 'File] installIncludes :: Lens' TestSuite [RelativePath Include 'File] options :: Lens' TestSuite (PerCompilerFlavor [String]) profOptions :: Lens' TestSuite (PerCompilerFlavor [String]) sharedOptions :: Lens' TestSuite (PerCompilerFlavor [String]) profSharedOptions :: Lens' TestSuite (PerCompilerFlavor [String]) staticOptions :: Lens' TestSuite (PerCompilerFlavor [String]) customFieldsBI :: Lens' TestSuite [(String, String)] targetBuildDepends :: Lens' TestSuite [Dependency] | |||||
Structured TestSuite | |||||
Defined in Distribution.Types.TestSuite | |||||
Binary TestSuite | |||||
NFData TestSuite | |||||
Defined in Distribution.Types.TestSuite | |||||
Monoid TestSuite | |||||
Semigroup TestSuite | |||||
Data TestSuite | |||||
Defined in Distribution.Types.TestSuite Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TestSuite -> c TestSuite # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TestSuite # toConstr :: TestSuite -> Constr # dataTypeOf :: TestSuite -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TestSuite) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TestSuite) # gmapT :: (forall b. Data b => b -> b) -> TestSuite -> TestSuite # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TestSuite -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TestSuite -> r # gmapQ :: (forall d. Data d => d -> u) -> TestSuite -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TestSuite -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TestSuite -> m TestSuite # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TestSuite -> m TestSuite # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TestSuite -> m TestSuite # | |||||
Generic TestSuite | |||||
Defined in Distribution.Types.TestSuite Associated Types
| |||||
Read TestSuite | |||||
Show TestSuite | |||||
Eq TestSuite | |||||
Ord TestSuite | |||||
type Rep TestSuite | |||||
Defined in Distribution.Types.TestSuite type Rep TestSuite = D1 ('MetaData "TestSuite" "Distribution.Types.TestSuite" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "TestSuite" 'PrefixI 'True) ((S1 ('MetaSel ('Just "testName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnqualComponentName) :*: S1 ('MetaSel ('Just "testInterface") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TestSuiteInterface)) :*: (S1 ('MetaSel ('Just "testBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildInfo) :*: S1 ('MetaSel ('Just "testCodeGenerators") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))) |
Constructors
Benchmark | |
Fields
|
Instances
HasBuildInfo Benchmark | |||||
Defined in Distribution.Types.Benchmark Methods buildInfo :: Lens' Benchmark BuildInfo buildable :: Lens' Benchmark Bool buildTools :: Lens' Benchmark [LegacyExeDependency] buildToolDepends :: Lens' Benchmark [ExeDependency] cppOptions :: Lens' Benchmark [String] asmOptions :: Lens' Benchmark [String] cmmOptions :: Lens' Benchmark [String] ccOptions :: Lens' Benchmark [String] cxxOptions :: Lens' Benchmark [String] jsppOptions :: Lens' Benchmark [String] ldOptions :: Lens' Benchmark [String] hsc2hsOptions :: Lens' Benchmark [String] pkgconfigDepends :: Lens' Benchmark [PkgconfigDependency] frameworks :: Lens' Benchmark [RelativePath Framework 'File] extraFrameworkDirs :: Lens' Benchmark [SymbolicPath Pkg ('Dir Framework)] asmSources :: Lens' Benchmark [SymbolicPath Pkg 'File] cmmSources :: Lens' Benchmark [SymbolicPath Pkg 'File] cSources :: Lens' Benchmark [SymbolicPath Pkg 'File] cxxSources :: Lens' Benchmark [SymbolicPath Pkg 'File] jsSources :: Lens' Benchmark [SymbolicPath Pkg 'File] hsSourceDirs :: Lens' Benchmark [SymbolicPath Pkg ('Dir Source)] otherModules :: Lens' Benchmark [ModuleName] virtualModules :: Lens' Benchmark [ModuleName] autogenModules :: Lens' Benchmark [ModuleName] defaultLanguage :: Lens' Benchmark (Maybe Language) otherLanguages :: Lens' Benchmark [Language] defaultExtensions :: Lens' Benchmark [Extension] otherExtensions :: Lens' Benchmark [Extension] oldExtensions :: Lens' Benchmark [Extension] extraLibs :: Lens' Benchmark [String] extraLibsStatic :: Lens' Benchmark [String] extraGHCiLibs :: Lens' Benchmark [String] extraBundledLibs :: Lens' Benchmark [String] extraLibFlavours :: Lens' Benchmark [String] extraDynLibFlavours :: Lens' Benchmark [String] extraLibDirs :: Lens' Benchmark [SymbolicPath Pkg ('Dir Lib)] extraLibDirsStatic :: Lens' Benchmark [SymbolicPath Pkg ('Dir Lib)] includeDirs :: Lens' Benchmark [SymbolicPath Pkg ('Dir Include)] includes :: Lens' Benchmark [SymbolicPath Include 'File] autogenIncludes :: Lens' Benchmark [RelativePath Include 'File] installIncludes :: Lens' Benchmark [RelativePath Include 'File] options :: Lens' Benchmark (PerCompilerFlavor [String]) profOptions :: Lens' Benchmark (PerCompilerFlavor [String]) sharedOptions :: Lens' Benchmark (PerCompilerFlavor [String]) profSharedOptions :: Lens' Benchmark (PerCompilerFlavor [String]) staticOptions :: Lens' Benchmark (PerCompilerFlavor [String]) customFieldsBI :: Lens' Benchmark [(String, String)] targetBuildDepends :: Lens' Benchmark [Dependency] | |||||
Structured Benchmark | |||||
Defined in Distribution.Types.Benchmark | |||||
Binary Benchmark | |||||
NFData Benchmark | |||||
Defined in Distribution.Types.Benchmark | |||||
Monoid Benchmark | |||||
Semigroup Benchmark | |||||
Data Benchmark | |||||
Defined in Distribution.Types.Benchmark Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Benchmark -> c Benchmark # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Benchmark # toConstr :: Benchmark -> Constr # dataTypeOf :: Benchmark -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Benchmark) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Benchmark) # gmapT :: (forall b. Data b => b -> b) -> Benchmark -> Benchmark # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Benchmark -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Benchmark -> r # gmapQ :: (forall d. Data d => d -> u) -> Benchmark -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Benchmark -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Benchmark -> m Benchmark # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Benchmark -> m Benchmark # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Benchmark -> m Benchmark # | |||||
Generic Benchmark | |||||
Defined in Distribution.Types.Benchmark Associated Types
| |||||
Read Benchmark | |||||
Show Benchmark | |||||
Eq Benchmark | |||||
Ord Benchmark | |||||
type Rep Benchmark | |||||
Defined in Distribution.Types.Benchmark type Rep Benchmark = D1 ('MetaData "Benchmark" "Distribution.Types.Benchmark" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "Benchmark" 'PrefixI 'True) (S1 ('MetaSel ('Just "benchmarkName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnqualComponentName) :*: (S1 ('MetaSel ('Just "benchmarkInterface") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BenchmarkInterface) :*: S1 ('MetaSel ('Just "benchmarkBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildInfo)))) |
data LibraryName #
Constructors
LMainLibName | |
LSubLibName UnqualComponentName |
Instances
Structured LibraryName | |||||
Defined in Distribution.Types.LibraryName | |||||
Binary LibraryName | |||||
Defined in Distribution.Types.LibraryName | |||||
NFData LibraryName | |||||
Defined in Distribution.Types.LibraryName Methods rnf :: LibraryName -> () # | |||||
Data LibraryName | |||||
Defined in Distribution.Types.LibraryName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LibraryName -> c LibraryName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LibraryName # toConstr :: LibraryName -> Constr # dataTypeOf :: LibraryName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LibraryName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LibraryName) # gmapT :: (forall b. Data b => b -> b) -> LibraryName -> LibraryName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LibraryName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LibraryName -> r # gmapQ :: (forall d. Data d => d -> u) -> LibraryName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LibraryName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LibraryName -> m LibraryName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LibraryName -> m LibraryName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LibraryName -> m LibraryName # | |||||
Generic LibraryName | |||||
Defined in Distribution.Types.LibraryName Associated Types
| |||||
Read LibraryName | |||||
Defined in Distribution.Types.LibraryName Methods readsPrec :: Int -> ReadS LibraryName # readList :: ReadS [LibraryName] # readPrec :: ReadPrec LibraryName # readListPrec :: ReadPrec [LibraryName] # | |||||
Show LibraryName | |||||
Defined in Distribution.Types.LibraryName Methods showsPrec :: Int -> LibraryName -> ShowS # show :: LibraryName -> String # showList :: [LibraryName] -> ShowS # | |||||
Eq LibraryName | |||||
Defined in Distribution.Types.LibraryName | |||||
Ord LibraryName | |||||
Defined in Distribution.Types.LibraryName Methods compare :: LibraryName -> LibraryName -> Ordering # (<) :: LibraryName -> LibraryName -> Bool # (<=) :: LibraryName -> LibraryName -> Bool # (>) :: LibraryName -> LibraryName -> Bool # (>=) :: LibraryName -> LibraryName -> Bool # max :: LibraryName -> LibraryName -> LibraryName # min :: LibraryName -> LibraryName -> LibraryName # | |||||
type Rep LibraryName | |||||
Defined in Distribution.Types.LibraryName type Rep LibraryName = D1 ('MetaData "LibraryName" "Distribution.Types.LibraryName" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "LMainLibName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LSubLibName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnqualComponentName))) |
emptyLibrary :: Library #