Copyright | Isaac Jones 2003-2004 |
---|---|
License | BSD3 |
Maintainer | cabal-devel@haskell.org |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Once a package has been configured we have resolved conditionals and
dependencies, configured the compiler and other needed external programs.
The LocalBuildInfo
is used to hold all this information. It holds the
install dirs, the compiler, the exact package dependencies, the configured
programs, the package database to use and a bunch of miscellaneous configure
flags. It gets saved and reloaded from a file (dist/setup-config
). It gets
passed in to very many subsequent build actions.
Synopsis
- data LocalBuildInfo where
- NewLocalBuildInfo { }
- pattern LocalBuildInfo :: ConfigFlags -> FlagAssignment -> ComponentRequestedSpec -> [String] -> InstallDirTemplates -> Compiler -> Platform -> Maybe (SymbolicPath Pkg 'File) -> Graph ComponentLocalBuildInfo -> Map ComponentName [ComponentLocalBuildInfo] -> Map (PackageName, ComponentName) PromisedComponent -> InstalledPackageIndex -> PackageDescription -> ProgramDb -> PackageDBStack -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> ProfDetailLevel -> ProfDetailLevel -> OptimisationLevel -> DebugInfoLevel -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> [UnitId] -> Bool -> LocalBuildInfo
- localComponentId :: LocalBuildInfo -> ComponentId
- localUnitId :: LocalBuildInfo -> UnitId
- localCompatPackageKey :: LocalBuildInfo -> String
- buildDir :: LocalBuildInfo -> SymbolicPath Pkg ('Dir Build)
- packageRoot :: CommonSetupFlags -> FilePath
- progPrefix :: LocalBuildInfo -> PathTemplate
- progSuffix :: LocalBuildInfo -> PathTemplate
- interpretSymbolicPathLBI :: forall (allowAbsolute :: AllowAbsolute) (to :: FileOrDir). LocalBuildInfo -> SymbolicPathX allowAbsolute Pkg to -> FilePath
- mbWorkDirLBI :: LocalBuildInfo -> Maybe (SymbolicPath CWD ('Dir Pkg))
- absoluteWorkingDirLBI :: LocalBuildInfo -> IO (AbsolutePath ('Dir Pkg))
- buildWays :: LocalBuildInfo -> (Bool -> [BuildWay], Bool -> BuildWay, BuildWay)
- 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
- data LibraryName
- defaultLibName :: LibraryName
- showComponentName :: ComponentName -> String
- componentNameString :: ComponentName -> Maybe UnqualComponentName
- 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 { }
- | ExeComponentLocalBuildInfo { }
- | TestComponentLocalBuildInfo { }
- | BenchComponentLocalBuildInfo { }
- = LibComponentLocalBuildInfo {
- componentBuildDir :: LocalBuildInfo -> ComponentLocalBuildInfo -> SymbolicPath Pkg ('Dir Build)
- foldComponent :: (Library -> a) -> (ForeignLib -> a) -> (Executable -> a) -> (TestSuite -> a) -> (Benchmark -> a) -> Component -> a
- componentName :: Component -> ComponentName
- componentBuildInfo :: Component -> BuildInfo
- componentBuildable :: Component -> Bool
- pkgComponents :: PackageDescription -> [Component]
- pkgBuildableComponents :: PackageDescription -> [Component]
- lookupComponent :: PackageDescription -> ComponentName -> Maybe Component
- getComponent :: PackageDescription -> ComponentName -> Component
- allComponentsInBuildOrder :: LocalBuildInfo -> [ComponentLocalBuildInfo]
- depLibraryPaths :: Bool -> Bool -> LocalBuildInfo -> ComponentLocalBuildInfo -> IO [FilePath]
- allLibModules :: Library -> ComponentLocalBuildInfo -> [ModuleName]
- withAllComponentsInBuildOrder :: PackageDescription -> LocalBuildInfo -> (Component -> ComponentLocalBuildInfo -> IO ()) -> IO ()
- withLibLBI :: PackageDescription -> LocalBuildInfo -> (Library -> ComponentLocalBuildInfo -> IO ()) -> IO ()
- withExeLBI :: PackageDescription -> LocalBuildInfo -> (Executable -> ComponentLocalBuildInfo -> IO ()) -> IO ()
- withBenchLBI :: PackageDescription -> LocalBuildInfo -> (Benchmark -> ComponentLocalBuildInfo -> IO ()) -> IO ()
- withTestLBI :: PackageDescription -> LocalBuildInfo -> (TestSuite -> ComponentLocalBuildInfo -> IO ()) -> IO ()
- enabledTestLBIs :: PackageDescription -> LocalBuildInfo -> [(TestSuite, ComponentLocalBuildInfo)]
- enabledBenchLBIs :: PackageDescription -> LocalBuildInfo -> [(Benchmark, ComponentLocalBuildInfo)]
- abiTemplateEnv :: CompilerInfo -> Platform -> PathTemplateEnv
- combineInstallDirs :: (a -> b -> c) -> InstallDirs a -> InstallDirs b -> InstallDirs c
- combinePathTemplate :: PathTemplate -> PathTemplate -> PathTemplate
- compilerTemplateEnv :: CompilerInfo -> PathTemplateEnv
- defaultInstallDirs :: CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplates
- defaultInstallDirs' :: Bool -> CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplates
- fromPathTemplate :: PathTemplate -> FilePath
- initialPathTemplateEnv :: PackageIdentifier -> UnitId -> CompilerInfo -> Platform -> PathTemplateEnv
- installDirsTemplateEnv :: InstallDirs PathTemplate -> PathTemplateEnv
- packageTemplateEnv :: PackageIdentifier -> UnitId -> PathTemplateEnv
- platformTemplateEnv :: Platform -> PathTemplateEnv
- substituteInstallDirTemplates :: PathTemplateEnv -> InstallDirTemplates -> InstallDirTemplates
- toPathTemplate :: FilePath -> PathTemplate
- data CopyDest
- type InstallDirTemplates = InstallDirs PathTemplate
- data InstallDirs dir = InstallDirs {
- prefix :: dir
- bindir :: dir
- libdir :: dir
- libsubdir :: dir
- dynlibdir :: dir
- flibdir :: dir
- libexecdir :: dir
- libexecsubdir :: dir
- includedir :: dir
- datadir :: dir
- datasubdir :: dir
- docdir :: dir
- mandir :: dir
- htmldir :: dir
- haddockdir :: dir
- sysconfdir :: dir
- data PathTemplate
- type PathTemplateEnv = [(PathTemplateVariable, PathTemplate)]
- data PathTemplateVariable
- absoluteInstallDirs :: PackageDescription -> LocalBuildInfo -> CopyDest -> InstallDirs FilePath
- prefixRelativeInstallDirs :: PackageId -> LocalBuildInfo -> InstallDirs (Maybe FilePath)
- absoluteInstallCommandDirs :: PackageDescription -> LocalBuildInfo -> UnitId -> CopyDest -> InstallDirs FilePath
- absoluteComponentInstallDirs :: PackageDescription -> LocalBuildInfo -> UnitId -> CopyDest -> InstallDirs FilePath
- prefixRelativeComponentInstallDirs :: PackageId -> LocalBuildInfo -> UnitId -> InstallDirs (Maybe FilePath)
- substPathTemplate :: PackageId -> LocalBuildInfo -> UnitId -> PathTemplate -> FilePath
Documentation
data LocalBuildInfo Source #
Data cached after configuration step. See also
ConfigFlags
.
NewLocalBuildInfo | |
|
pattern LocalBuildInfo :: ConfigFlags -> FlagAssignment -> ComponentRequestedSpec -> [String] -> InstallDirTemplates -> Compiler -> Platform -> Maybe (SymbolicPath Pkg 'File) -> Graph ComponentLocalBuildInfo -> Map ComponentName [ComponentLocalBuildInfo] -> Map (PackageName, ComponentName) PromisedComponent -> InstalledPackageIndex -> PackageDescription -> ProgramDb -> PackageDBStack -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> ProfDetailLevel -> ProfDetailLevel -> OptimisationLevel -> DebugInfoLevel -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> [UnitId] -> Bool -> LocalBuildInfo | This pattern synonym is for backwards compatibility, to adapt
to |
Instances
localComponentId :: LocalBuildInfo -> ComponentId Source #
Extract the ComponentId
from the public library component of a
LocalBuildInfo
if it exists, or make a fake component ID based
on the package ID.
localUnitId :: LocalBuildInfo -> UnitId Source #
Extract the UnitId
from the library component of a
LocalBuildInfo
if it exists, or make a fake unit ID based on
the package ID.
localCompatPackageKey :: LocalBuildInfo -> String Source #
Extract the compatibility package key from the public library component of a
LocalBuildInfo
if it exists, or make a fake package key based
on the package ID.
Convenience accessors
buildDir :: LocalBuildInfo -> SymbolicPath Pkg ('Dir Build) Source #
packageRoot :: CommonSetupFlags -> FilePath Source #
The (relative or absolute) path to the package root, based on
- the working directory flag
- the
.cabal
path
interpretSymbolicPathLBI :: forall (allowAbsolute :: AllowAbsolute) (to :: FileOrDir). LocalBuildInfo -> SymbolicPathX allowAbsolute Pkg to -> FilePath Source #
Interpret a symbolic path with respect to the working directory
stored in LocalBuildInfo
.
Use this before directly interacting with the file system.
NB: when invoking external programs (such as GHC
), it is preferable to set
the working directory of the process rather than calling this function, as
this function will turn relative paths into absolute paths if the working
directory is an absolute path. This can degrade error messages, or worse,
break the behaviour entirely (because the program might expect certain paths
to be relative).
See Note [Symbolic paths] in Distribution.Utils.Path
mbWorkDirLBI :: LocalBuildInfo -> Maybe (SymbolicPath CWD ('Dir Pkg)) Source #
Retrieve an optional working directory from LocalBuildInfo
.
absoluteWorkingDirLBI :: LocalBuildInfo -> IO (AbsolutePath ('Dir Pkg)) Source #
Absolute path to the current working directory.
buildWays :: LocalBuildInfo -> (Bool -> [BuildWay], Bool -> BuildWay, BuildWay) Source #
Returns a list of ways, in the order which they should be built, and the way we build executable and foreign library components.
Ideally all this info should be fixed at configure time and not dependent on
additional info but LocalBuildInfo
is per package (not per component) so it's
currently not possible to configure components to be built in certain ways.
Buildable package components
Instances
HasBuildInfo Component Source # | |||||
Defined in Distribution.Types.Component buildInfo :: Lens' Component BuildInfo Source # buildable :: Lens' Component Bool Source # buildTools :: Lens' Component [LegacyExeDependency] Source # buildToolDepends :: Lens' Component [ExeDependency] Source # cppOptions :: Lens' Component [String] Source # asmOptions :: Lens' Component [String] Source # cmmOptions :: Lens' Component [String] Source # ccOptions :: Lens' Component [String] Source # cxxOptions :: Lens' Component [String] Source # ldOptions :: Lens' Component [String] Source # hsc2hsOptions :: Lens' Component [String] Source # pkgconfigDepends :: Lens' Component [PkgconfigDependency] Source # frameworks :: Lens' Component [RelativePath Framework 'File] Source # extraFrameworkDirs :: Lens' Component [SymbolicPath Pkg ('Dir Framework)] Source # asmSources :: Lens' Component [SymbolicPath Pkg 'File] Source # cmmSources :: Lens' Component [SymbolicPath Pkg 'File] Source # cSources :: Lens' Component [SymbolicPath Pkg 'File] Source # cxxSources :: Lens' Component [SymbolicPath Pkg 'File] Source # jsSources :: Lens' Component [SymbolicPath Pkg 'File] Source # hsSourceDirs :: Lens' Component [SymbolicPath Pkg ('Dir Source)] Source # otherModules :: Lens' Component [ModuleName] Source # virtualModules :: Lens' Component [ModuleName] Source # autogenModules :: Lens' Component [ModuleName] Source # defaultLanguage :: Lens' Component (Maybe Language) Source # otherLanguages :: Lens' Component [Language] Source # defaultExtensions :: Lens' Component [Extension] Source # otherExtensions :: Lens' Component [Extension] Source # oldExtensions :: Lens' Component [Extension] Source # extraLibs :: Lens' Component [String] Source # extraLibsStatic :: Lens' Component [String] Source # extraGHCiLibs :: Lens' Component [String] Source # extraBundledLibs :: Lens' Component [String] Source # extraLibFlavours :: Lens' Component [String] Source # extraDynLibFlavours :: Lens' Component [String] Source # extraLibDirs :: Lens' Component [SymbolicPath Pkg ('Dir Lib)] Source # extraLibDirsStatic :: Lens' Component [SymbolicPath Pkg ('Dir Lib)] Source # includeDirs :: Lens' Component [SymbolicPath Pkg ('Dir Include)] Source # includes :: Lens' Component [SymbolicPath Include 'File] Source # autogenIncludes :: Lens' Component [RelativePath Include 'File] Source # installIncludes :: Lens' Component [RelativePath Include 'File] Source # options :: Lens' Component (PerCompilerFlavor [String]) Source # profOptions :: Lens' Component (PerCompilerFlavor [String]) Source # sharedOptions :: Lens' Component (PerCompilerFlavor [String]) Source # profSharedOptions :: Lens' Component (PerCompilerFlavor [String]) Source # staticOptions :: Lens' Component (PerCompilerFlavor [String]) Source # customFieldsBI :: Lens' Component [(String, String)] Source # | |||||
Structured Component Source # | |||||
Defined in Distribution.Types.Component | |||||
Binary Component Source # | |||||
Semigroup Component Source # | |||||
Generic Component Source # | |||||
Defined in Distribution.Types.Component
| |||||
Read Component Source # | |||||
Show Component Source # | |||||
Eq Component Source # | |||||
type Rep Component Source # | |||||
Defined in Distribution.Types.Component type Rep Component = D1 ('MetaData "Component" "Distribution.Types.Component" "Cabal-syntax-3.14.0.0-e3f5" '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 Source #
CLibName LibraryName | |
CNotLibName NotLibComponentName |
pattern CBenchName :: UnqualComponentName -> ComponentName | |
pattern CExeName :: UnqualComponentName -> ComponentName | |
pattern CFLibName :: UnqualComponentName -> ComponentName | |
pattern CTestName :: UnqualComponentName -> ComponentName |
Instances
Parsec ComponentName Source # | |||||
Defined in Distribution.Types.ComponentName parsec :: CabalParsing m => m ComponentName Source # | |||||
Pretty ComponentName Source # | |||||
Defined in Distribution.Types.ComponentName pretty :: ComponentName -> Doc Source # prettyVersioned :: CabalSpecVersion -> ComponentName -> Doc Source # | |||||
Structured ComponentName Source # | |||||
Defined in Distribution.Types.ComponentName structure :: Proxy ComponentName -> Structure Source # structureHash' :: Tagged ComponentName MD5 | |||||
Binary ComponentName Source # | |||||
Defined in Distribution.Types.ComponentName | |||||
Generic ComponentName Source # | |||||
Defined in Distribution.Types.ComponentName
from :: ComponentName -> Rep ComponentName x # to :: Rep ComponentName x -> ComponentName # | |||||
Read ComponentName Source # | |||||
Defined in Distribution.Types.ComponentName readsPrec :: Int -> ReadS ComponentName # readList :: ReadS [ComponentName] # | |||||
Show ComponentName Source # | |||||
Defined in Distribution.Types.ComponentName showsPrec :: Int -> ComponentName -> ShowS # show :: ComponentName -> String # showList :: [ComponentName] -> ShowS # | |||||
Eq ComponentName Source # | |||||
Defined in Distribution.Types.ComponentName (==) :: ComponentName -> ComponentName -> Bool # (/=) :: ComponentName -> ComponentName -> Bool # | |||||
Ord ComponentName Source # | |||||
Defined in Distribution.Types.ComponentName 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 Source # | |||||
Defined in Distribution.Types.ComponentName type Rep ComponentName = D1 ('MetaData "ComponentName" "Distribution.Types.ComponentName" "Cabal-syntax-3.14.0.0-e3f5" '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))) |
data LibraryName Source #
Instances
Structured LibraryName Source # | |||||
Defined in Distribution.Types.LibraryName structure :: Proxy LibraryName -> Structure Source # structureHash' :: Tagged LibraryName MD5 | |||||
Binary LibraryName Source # | |||||
Defined in Distribution.Types.LibraryName | |||||
NFData LibraryName Source # | |||||
Defined in Distribution.Types.LibraryName rnf :: LibraryName -> () Source # | |||||
Data LibraryName Source # | |||||
Defined in Distribution.Types.LibraryName 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 Source # | |||||
Defined in Distribution.Types.LibraryName
from :: LibraryName -> Rep LibraryName x # to :: Rep LibraryName x -> LibraryName # | |||||
Read LibraryName Source # | |||||
Defined in Distribution.Types.LibraryName readsPrec :: Int -> ReadS LibraryName # readList :: ReadS [LibraryName] # readPrec :: ReadPrec LibraryName # readListPrec :: ReadPrec [LibraryName] # | |||||
Show LibraryName Source # | |||||
Defined in Distribution.Types.LibraryName showsPrec :: Int -> LibraryName -> ShowS # show :: LibraryName -> String # showList :: [LibraryName] -> ShowS # | |||||
Eq LibraryName Source # | |||||
Defined in Distribution.Types.LibraryName (==) :: LibraryName -> LibraryName -> Bool # (/=) :: LibraryName -> LibraryName -> Bool # | |||||
Ord LibraryName Source # | |||||
Defined in Distribution.Types.LibraryName 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 Source # | |||||
Defined in Distribution.Types.LibraryName type Rep LibraryName = D1 ('MetaData "LibraryName" "Distribution.Types.LibraryName" "Cabal-syntax-3.14.0.0-e3f5" 'False) (C1 ('MetaCons "LMainLibName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LSubLibName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnqualComponentName))) |
componentNameString :: ComponentName -> Maybe UnqualComponentName Source #
This gets the underlying unqualified component name. In fact, it is
guaranteed to uniquely identify a component, returning
Nothing
if the ComponentName
was for the public
library.
data ComponentLocalBuildInfo Source #
The first five fields are common across all algebraic variants.
LibComponentLocalBuildInfo | |
| |
FLibComponentLocalBuildInfo | |
| |
ExeComponentLocalBuildInfo | |
| |
TestComponentLocalBuildInfo | |
| |
BenchComponentLocalBuildInfo | |
|
Instances
IsNode ComponentLocalBuildInfo Source # | |||||
Defined in Distribution.Types.ComponentLocalBuildInfo
| |||||
Structured ComponentLocalBuildInfo Source # | |||||
Defined in Distribution.Types.ComponentLocalBuildInfo | |||||
Binary ComponentLocalBuildInfo Source # | |||||
Defined in Distribution.Types.ComponentLocalBuildInfo put :: ComponentLocalBuildInfo -> Put # get :: Get ComponentLocalBuildInfo # putList :: [ComponentLocalBuildInfo] -> Put # | |||||
Generic ComponentLocalBuildInfo Source # | |||||
Defined in Distribution.Types.ComponentLocalBuildInfo
| |||||
Read ComponentLocalBuildInfo Source # | |||||
Show ComponentLocalBuildInfo Source # | |||||
Defined in Distribution.Types.ComponentLocalBuildInfo showsPrec :: Int -> ComponentLocalBuildInfo -> ShowS # show :: ComponentLocalBuildInfo -> String # showList :: [ComponentLocalBuildInfo] -> ShowS # | |||||
type Key ComponentLocalBuildInfo Source # | |||||
Defined in Distribution.Types.ComponentLocalBuildInfo | |||||
type Rep ComponentLocalBuildInfo Source # | |||||
Defined in Distribution.Types.ComponentLocalBuildInfo type Rep ComponentLocalBuildInfo = D1 ('MetaData "ComponentLocalBuildInfo" "Distribution.Types.ComponentLocalBuildInfo" "Cabal-3.14.0.0-be97" '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]))))))) |
componentBuildDir :: LocalBuildInfo -> ComponentLocalBuildInfo -> SymbolicPath Pkg ('Dir Build) Source #
foldComponent :: (Library -> a) -> (ForeignLib -> a) -> (Executable -> a) -> (TestSuite -> a) -> (Benchmark -> a) -> Component -> a Source #
componentBuildable :: Component -> Bool Source #
Is a component buildable (i.e., not marked with buildable: False
)?
See also this note in
Distribution.Types.ComponentRequestedSpec.
Since: Cabal-syntax-2.0.0.2
pkgComponents :: PackageDescription -> [Component] Source #
All the components in the package.
pkgBuildableComponents :: PackageDescription -> [Component] Source #
A list of all components in the package that are buildable,
i.e., were not marked with buildable: False
. This does NOT
indicate if we are actually going to build the component,
see enabledComponents
instead.
Since: Cabal-syntax-2.0.0.2
:: Bool | Building for inplace? |
-> Bool | Generate prefix-relative library paths |
-> LocalBuildInfo | |
-> ComponentLocalBuildInfo | Component that is being built |
-> IO [FilePath] |
Determine the directories containing the dynamic libraries of the transitive dependencies of the component we are building.
When wanted, and possible, returns paths relative to the installDirs prefix
allLibModules :: Library -> ComponentLocalBuildInfo -> [ModuleName] Source #
Get all module names that needed to be built by GHC; i.e., all
of these ModuleName
s have interface files associated with them
that need to be installed.
withAllComponentsInBuildOrder :: PackageDescription -> LocalBuildInfo -> (Component -> ComponentLocalBuildInfo -> IO ()) -> IO () Source #
Perform the action on each buildable Library
or Executable
(Component)
in the PackageDescription, subject to the build order specified by the
compBuildOrder
field of the given LocalBuildInfo
withLibLBI :: PackageDescription -> LocalBuildInfo -> (Library -> ComponentLocalBuildInfo -> IO ()) -> IO () Source #
Perform the action on each enabled library
in the package
description with the ComponentLocalBuildInfo
.
withExeLBI :: PackageDescription -> LocalBuildInfo -> (Executable -> ComponentLocalBuildInfo -> IO ()) -> IO () Source #
Perform the action on each enabled Executable
in the package
description. Extended version of withExe
that also gives corresponding
build info.
withBenchLBI :: PackageDescription -> LocalBuildInfo -> (Benchmark -> ComponentLocalBuildInfo -> IO ()) -> IO () Source #
Perform the action on each enabled Benchmark
in the package
description.
withTestLBI :: PackageDescription -> LocalBuildInfo -> (TestSuite -> ComponentLocalBuildInfo -> IO ()) -> IO () Source #
enabledTestLBIs :: PackageDescription -> LocalBuildInfo -> [(TestSuite, ComponentLocalBuildInfo)] Source #
enabledBenchLBIs :: PackageDescription -> LocalBuildInfo -> [(Benchmark, ComponentLocalBuildInfo)] Source #
Installation directories
abiTemplateEnv :: CompilerInfo -> Platform -> PathTemplateEnv Source #
combineInstallDirs :: (a -> b -> c) -> InstallDirs a -> InstallDirs b -> InstallDirs c Source #
defaultInstallDirs :: CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplates Source #
defaultInstallDirs' :: Bool -> CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplates Source #
fromPathTemplate :: PathTemplate -> FilePath Source #
Convert back to a path, any remaining vars are included
initialPathTemplateEnv :: PackageIdentifier -> UnitId -> CompilerInfo -> Platform -> PathTemplateEnv Source #
The initial environment has all the static stuff but no paths
substituteInstallDirTemplates :: PathTemplateEnv -> InstallDirTemplates -> InstallDirTemplates Source #
Substitute the install dir templates into each other.
To prevent cyclic substitutions, only some variables are allowed in particular dir templates. If out of scope vars are present, they are not substituted for. Checking for any remaining unsubstituted vars can be done as a subsequent operation.
The reason it is done this way is so that in prefixRelativeInstallDirs
we
can replace prefix
with the PrefixVar
and get resulting
PathTemplate
s that still have the PrefixVar
in them. Doing this makes it
each to check which paths are relative to the $prefix.
toPathTemplate :: FilePath -> PathTemplate Source #
Convert a FilePath
to a PathTemplate
including any template vars.
The location prefix for the copy command.
NoCopyDest | |
CopyTo FilePath | |
CopyToDb FilePath | when using the ${pkgroot} as prefix. The CopyToDb will adjust the paths to be relative to the provided package database when copying / installing. |
Instances
Structured CopyDest Source # | |||||
Defined in Distribution.Simple.InstallDirs | |||||
Binary CopyDest Source # | |||||
Generic CopyDest Source # | |||||
Defined in Distribution.Simple.InstallDirs
| |||||
Show CopyDest Source # | |||||
Eq CopyDest Source # | |||||
type Rep CopyDest Source # | |||||
Defined in Distribution.Simple.InstallDirs type Rep CopyDest = D1 ('MetaData "CopyDest" "Distribution.Simple.InstallDirs" "Cabal-3.14.0.0-be97" 'False) (C1 ('MetaCons "NoCopyDest" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CopyTo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)) :+: C1 ('MetaCons "CopyToDb" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath)))) |
type InstallDirTemplates = InstallDirs PathTemplate Source #
The installation directories in terms of PathTemplate
s that contain
variables.
The defaults for most of the directories are relative to each other, in
particular they are all relative to a single prefix. This makes it
convenient for the user to override the default installation directory
by only having to specify --prefix=... rather than overriding each
individually. This is done by allowing $-style variables in the dirs.
These are expanded by textual substitution (see substPathTemplate
).
A few of these installation directories are split into two components, the
dir and subdir. The full installation path is formed by combining the two
together with /
. The reason for this is compatibility with other Unix
build systems which also support --libdir
and --datadir
. We would like
users to be able to configure --libdir=/usr/lib64
for example but
because by default we want to support installing multiple versions of
packages and building the same package for multiple compilers we append the
libsubdir to get: /usr/lib64/$libname/$compiler
.
An additional complication is the need to support relocatable packages on systems which support such things, like Windows.
data InstallDirs dir Source #
The directories where we will install files for packages.
We have several different directories for different types of files since many systems have conventions whereby different types of files in a package are installed in different directories. This is particularly the case on Unix style systems.
InstallDirs | |
|
Instances
Functor InstallDirs Source # | |||||
Defined in Distribution.Simple.InstallDirs fmap :: (a -> b) -> InstallDirs a -> InstallDirs b # (<$) :: a -> InstallDirs b -> InstallDirs a # | |||||
Structured dir => Structured (InstallDirs dir) Source # | |||||
Defined in Distribution.Simple.InstallDirs structure :: Proxy (InstallDirs dir) -> Structure Source # structureHash' :: Tagged (InstallDirs dir) MD5 | |||||
Binary dir => Binary (InstallDirs dir) Source # | |||||
Defined in Distribution.Simple.InstallDirs | |||||
(Semigroup dir, Monoid dir) => Monoid (InstallDirs dir) Source # | |||||
Defined in Distribution.Simple.InstallDirs mempty :: InstallDirs dir # mappend :: InstallDirs dir -> InstallDirs dir -> InstallDirs dir # mconcat :: [InstallDirs dir] -> InstallDirs dir # | |||||
Semigroup dir => Semigroup (InstallDirs dir) Source # | |||||
Defined in Distribution.Simple.InstallDirs (<>) :: InstallDirs dir -> InstallDirs dir -> InstallDirs dir # sconcat :: NonEmpty (InstallDirs dir) -> InstallDirs dir # stimes :: Integral b => b -> InstallDirs dir -> InstallDirs dir # | |||||
Generic (InstallDirs dir) Source # | |||||
Defined in Distribution.Simple.InstallDirs
from :: InstallDirs dir -> Rep (InstallDirs dir) x # to :: Rep (InstallDirs dir) x -> InstallDirs dir # | |||||
Read dir => Read (InstallDirs dir) Source # | |||||
Defined in Distribution.Simple.InstallDirs readsPrec :: Int -> ReadS (InstallDirs dir) # readList :: ReadS [InstallDirs dir] # readPrec :: ReadPrec (InstallDirs dir) # readListPrec :: ReadPrec [InstallDirs dir] # | |||||
Show dir => Show (InstallDirs dir) Source # | |||||
Defined in Distribution.Simple.InstallDirs showsPrec :: Int -> InstallDirs dir -> ShowS # show :: InstallDirs dir -> String # showList :: [InstallDirs dir] -> ShowS # | |||||
Eq dir => Eq (InstallDirs dir) Source # | |||||
Defined in Distribution.Simple.InstallDirs (==) :: InstallDirs dir -> InstallDirs dir -> Bool # (/=) :: InstallDirs dir -> InstallDirs dir -> Bool # | |||||
type Rep (InstallDirs dir) Source # | |||||
Defined in Distribution.Simple.InstallDirs type Rep (InstallDirs dir) = D1 ('MetaData "InstallDirs" "Distribution.Simple.InstallDirs" "Cabal-3.14.0.0-be97" 'False) (C1 ('MetaCons "InstallDirs" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "prefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir) :*: S1 ('MetaSel ('Just "bindir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir)) :*: (S1 ('MetaSel ('Just "libdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir) :*: S1 ('MetaSel ('Just "libsubdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir))) :*: ((S1 ('MetaSel ('Just "dynlibdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir) :*: S1 ('MetaSel ('Just "flibdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir)) :*: (S1 ('MetaSel ('Just "libexecdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir) :*: S1 ('MetaSel ('Just "libexecsubdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir)))) :*: (((S1 ('MetaSel ('Just "includedir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir) :*: S1 ('MetaSel ('Just "datadir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir)) :*: (S1 ('MetaSel ('Just "datasubdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir) :*: S1 ('MetaSel ('Just "docdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir))) :*: ((S1 ('MetaSel ('Just "mandir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir) :*: S1 ('MetaSel ('Just "htmldir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir)) :*: (S1 ('MetaSel ('Just "haddockdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir) :*: S1 ('MetaSel ('Just "sysconfdir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 dir)))))) |
data PathTemplate Source #
An abstract path, possibly containing variables that need to be
substituted for to get a real FilePath
.
Instances
Structured PathTemplate Source # | |||||
Defined in Distribution.Simple.InstallDirs structure :: Proxy PathTemplate -> Structure Source # structureHash' :: Tagged PathTemplate MD5 | |||||
Binary PathTemplate Source # | |||||
Defined in Distribution.Simple.InstallDirs | |||||
Generic PathTemplate Source # | |||||
Defined in Distribution.Simple.InstallDirs
from :: PathTemplate -> Rep PathTemplate x # to :: Rep PathTemplate x -> PathTemplate # | |||||
Read PathTemplate Source # | |||||
Defined in Distribution.Simple.InstallDirs readsPrec :: Int -> ReadS PathTemplate # readList :: ReadS [PathTemplate] # | |||||
Show PathTemplate Source # | |||||
Defined in Distribution.Simple.InstallDirs showsPrec :: Int -> PathTemplate -> ShowS # show :: PathTemplate -> String # showList :: [PathTemplate] -> ShowS # | |||||
Eq PathTemplate Source # | |||||
Defined in Distribution.Simple.InstallDirs (==) :: PathTemplate -> PathTemplate -> Bool # (/=) :: PathTemplate -> PathTemplate -> Bool # | |||||
Ord PathTemplate Source # | |||||
Defined in Distribution.Simple.InstallDirs compare :: PathTemplate -> PathTemplate -> Ordering # (<) :: PathTemplate -> PathTemplate -> Bool # (<=) :: PathTemplate -> PathTemplate -> Bool # (>) :: PathTemplate -> PathTemplate -> Bool # (>=) :: PathTemplate -> PathTemplate -> Bool # max :: PathTemplate -> PathTemplate -> PathTemplate # min :: PathTemplate -> PathTemplate -> PathTemplate # | |||||
type Rep PathTemplate Source # | |||||
Defined in Distribution.Simple.InstallDirs type Rep PathTemplate = D1 ('MetaData "PathTemplate" "Distribution.Simple.InstallDirs" "Cabal-3.14.0.0-be97" 'True) (C1 ('MetaCons "PathTemplate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PathComponent]))) |
type PathTemplateEnv = [(PathTemplateVariable, PathTemplate)] Source #
data PathTemplateVariable Source #
PrefixVar | The |
BindirVar | The |
LibdirVar | The |
LibsubdirVar | The |
DynlibdirVar | The |
DatadirVar | The |
DatasubdirVar | The |
DocdirVar | The |
HtmldirVar | The |
PkgNameVar | The |
PkgVerVar | The |
PkgIdVar | The |
LibNameVar | The |
CompilerVar | The compiler name and version, eg |
OSVar | The operating system name, eg |
ArchVar | The CPU architecture name, eg |
AbiVar | The compiler's ABI identifier, |
AbiTagVar | The optional ABI tag for the compiler |
ExecutableNameVar | The executable name; used in shell wrappers |
TestSuiteNameVar | The name of the test suite being run |
TestSuiteResultVar | The result of the test suite being run, eg
|
BenchmarkNameVar | The name of the benchmark being run |
Instances
Structured PathTemplateVariable Source # | |||||
Defined in Distribution.Simple.InstallDirs.Internal structure :: Proxy PathTemplateVariable -> Structure Source # structureHash' :: Tagged PathTemplateVariable MD5 | |||||
Binary PathTemplateVariable Source # | |||||
Defined in Distribution.Simple.InstallDirs.Internal put :: PathTemplateVariable -> Put # get :: Get PathTemplateVariable # putList :: [PathTemplateVariable] -> Put # | |||||
Generic PathTemplateVariable Source # | |||||
Defined in Distribution.Simple.InstallDirs.Internal
from :: PathTemplateVariable -> Rep PathTemplateVariable x # to :: Rep PathTemplateVariable x -> PathTemplateVariable # | |||||
Read PathTemplateVariable Source # | |||||
Show PathTemplateVariable Source # | |||||
Defined in Distribution.Simple.InstallDirs.Internal showsPrec :: Int -> PathTemplateVariable -> ShowS # show :: PathTemplateVariable -> String # showList :: [PathTemplateVariable] -> ShowS # | |||||
Eq PathTemplateVariable Source # | |||||
Defined in Distribution.Simple.InstallDirs.Internal (==) :: PathTemplateVariable -> PathTemplateVariable -> Bool # (/=) :: PathTemplateVariable -> PathTemplateVariable -> Bool # | |||||
Ord PathTemplateVariable Source # | |||||
Defined in Distribution.Simple.InstallDirs.Internal compare :: PathTemplateVariable -> PathTemplateVariable -> Ordering # (<) :: PathTemplateVariable -> PathTemplateVariable -> Bool # (<=) :: PathTemplateVariable -> PathTemplateVariable -> Bool # (>) :: PathTemplateVariable -> PathTemplateVariable -> Bool # (>=) :: PathTemplateVariable -> PathTemplateVariable -> Bool # max :: PathTemplateVariable -> PathTemplateVariable -> PathTemplateVariable # min :: PathTemplateVariable -> PathTemplateVariable -> PathTemplateVariable # | |||||
type Rep PathTemplateVariable Source # | |||||
Defined in Distribution.Simple.InstallDirs.Internal type Rep PathTemplateVariable = D1 ('MetaData "PathTemplateVariable" "Distribution.Simple.InstallDirs.Internal" "Cabal-3.14.0.0-be97" 'False) ((((C1 ('MetaCons "PrefixVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BindirVar" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LibdirVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LibsubdirVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DynlibdirVar" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "DatadirVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DatasubdirVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DocdirVar" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "HtmldirVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PkgNameVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PkgVerVar" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "PkgIdVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LibNameVar" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CompilerVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OSVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArchVar" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "AbiVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AbiTagVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExecutableNameVar" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "TestSuiteNameVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TestSuiteResultVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BenchmarkNameVar" 'PrefixI 'False) (U1 :: Type -> Type)))))) |
absoluteInstallDirs :: PackageDescription -> LocalBuildInfo -> CopyDest -> InstallDirs FilePath Source #
Backwards compatibility function which computes the InstallDirs
assuming that $libname
points to the public library (or some fake
package identifier if there is no public library.) IF AT ALL
POSSIBLE, please use absoluteComponentInstallDirs
instead.
prefixRelativeInstallDirs :: PackageId -> LocalBuildInfo -> InstallDirs (Maybe FilePath) Source #
Backwards compatibility function which computes the InstallDirs
assuming that $libname
points to the public library (or some fake
package identifier if there is no public library.) IF AT ALL
POSSIBLE, please use prefixRelativeComponentInstallDirs
instead.
absoluteInstallCommandDirs :: PackageDescription -> LocalBuildInfo -> UnitId -> CopyDest -> InstallDirs FilePath Source #
absoluteComponentInstallDirs :: PackageDescription -> LocalBuildInfo -> UnitId -> CopyDest -> InstallDirs FilePath Source #
See absoluteInstallDirs
.
prefixRelativeComponentInstallDirs :: PackageId -> LocalBuildInfo -> UnitId -> InstallDirs (Maybe FilePath) Source #
substPathTemplate :: PackageId -> LocalBuildInfo -> UnitId -> PathTemplate -> FilePath Source #