| License | Apache-2.0 | 
|---|---|
| Safe Haskell | None | 
| Language | Haskell2010 | 
CabalHelper.Compiletime.Types
Description
Synopsis
- data ProjType
- data CabalProjType
- data SProjType pt where
- data SCabalProjType pt where
- demoteSProjType :: SProjType pt -> ProjType
- data ProjLoc (pt :: ProjType) where- ProjLocV1CabalFile :: {..} -> ProjLoc (Cabal CV1)
- ProjLocV1Dir :: {..} -> ProjLoc (Cabal CV1)
- ProjLocV2File :: {..} -> ProjLoc (Cabal CV2)
- ProjLocV2Dir :: {..} -> ProjLoc (Cabal CV2)
- ProjLocStackYaml :: {..} -> ProjLoc Stack
 
- plV1Dir :: ProjLoc (Cabal CV1) -> FilePath
- plCabalProjectDir :: ProjLoc (Cabal cpt) -> FilePath
- plStackProjectDir :: ProjLoc Stack -> FilePath
- projTypeOfProjLoc :: ProjLoc pt -> SProjType pt
- data DistDir (pt :: ProjType) where- DistDirCabal :: !(SCabalProjType pt) -> !FilePath -> DistDir (Cabal pt)
- DistDirStack :: !(Maybe RelativePath) -> DistDir Stack
 
- projTypeOfDistDir :: DistDir pt -> SProjType pt
- data Ex a = Ex (a x)
- type QueryEnv pt = QueryEnvI QueryCache pt
- data QueryEnvI c (pt :: ProjType) = QueryEnv {- qeReadProcess :: !ReadProcessWithCwdAndEnv
- qeCallProcess :: !(CallProcessWithCwdAndEnv ())
- qePrograms :: !Programs
- qeProjLoc :: !(ProjLoc pt)
- qeDistDir :: !(DistDir pt)
- qeCacheRef :: !(IORef (c pt))
- qeCacheKeys :: IORef (CacheKeyCache pt)
 
- projTypeOfQueryEnv :: QueryEnvI c pt -> SProjType pt
- type ReadProcessWithCwdAndEnv = String -> CallProcessWithCwdAndEnv String
- type CallProcessWithCwdAndEnv a = Maybe FilePath -> [(String, EnvOverride)] -> FilePath -> [String] -> IO a
- type QueryCache = QueryCacheI PreInfo Programs ProjInfo UnitInfo
- type QCPreInfo progs proj_info unit_info = QueryCacheI PreInfo progs proj_info unit_info
- type QCProgs proj_info unit_info = QueryCacheI PreInfo Programs proj_info unit_info
- data QueryCacheI pre_info progs proj_info unit_info pt = QueryCache {- qcPreInfo :: !(Maybe ((ProjConf pt, ProjConfModTimes), pre_info pt))
- qcConfProgs :: !(Maybe (Programs, progs))
- qcProjInfo :: !(Maybe ((ProjConf pt, ProjConfModTimes), proj_info pt))
- qcUnitInfos :: !(Map DistDirLib unit_info)
 
- data CacheKeyCache pt = CacheKeyCache {- ckcProjConf :: !(Maybe (ProjConf pt, ProjConfModTimes))
 
- newtype DistDirLib = DistDirLib FilePath
- type Package pt = Package' (NonEmpty (Unit pt))
- data Package' units = Package {- pPackageName :: !String
- pSourceDir :: !FilePath
- pCabalFile :: !CabalFile
- pFlags :: ![(String, Bool)]
- pUnits :: !units
 
- data Unit pt = Unit {}
- data UnitImpl pt where- UnitImplV1 :: UnitImpl (Cabal CV1)
- UnitImplV2 :: {..} -> UnitImpl (Cabal CV2)
- UnitImplStack :: UnitImpl Stack
 
- uComponentName :: Unit pt -> Maybe ChComponentName
- data UnitHeader = UnitHeader {- uhPackageId :: !(ByteString, Version)
- uhSetupId :: !(ByteString, Version)
- uhCompilerId :: !(ByteString, Version)
 
- newtype UnitId = UnitId String
- data UnitInfo = UnitInfo {- uiUnitId :: !UnitId
- uiPackageId :: !(String, Version)
- uiComponents :: !(Map ChComponentName ChComponentInfo)
- uiCompilerId :: !(String, Version)
- uiPackageFlags :: ![(String, Bool)]
- uiConfigFlags :: ![(String, Bool)]
- uiNonDefaultConfigFlags :: ![(String, Bool)]
- uiModTimes :: !UnitModTimes
 
- data ProjConf pt where- ProjConfV1 :: {..} -> ProjConf (Cabal CV1)
- ProjConfV2 :: {..} -> ProjConf (Cabal CV2)
- ProjConfStack :: {..} -> ProjConf Stack
 
- projTypeOfProjConf :: ProjConf pt -> SProjType pt
- newtype ProjConfModTimes = ProjConfModTimes [(FilePath, EpochTime)]
- data ProjInfo pt = ProjInfo {- piCabalVersion :: !Version
- piPackages :: !(NonEmpty (Package pt))
- piImpl :: !(ProjInfoImpl pt)
- piProjConfModTimes :: !ProjConfModTimes
 
- data ProjInfoImpl pt where- ProjInfoV1 :: {..} -> ProjInfoImpl (Cabal CV1)
- ProjInfoV2 :: {..} -> ProjInfoImpl (Cabal CV2)
- ProjInfoStack :: ProjInfoImpl Stack
 
- data UnitModTimes = UnitModTimes {- umtPkgYaml :: !(Maybe (FilePath, EpochTime))
- umtCabalFile :: !(FilePath, EpochTime)
- umtSetupConfig :: !(Maybe (FilePath, EpochTime))
 
- data PreInfo pt where- PreInfoCabal :: PreInfo (Cabal cpt)
- PreInfoStack :: {..} -> PreInfo Stack
 
- newtype CabalFile = CabalFile FilePath
- data StackProjPaths = StackProjPaths {}
- type Verbose = ?verbose :: Word -> Bool
- type Env = (?progs :: Programs, ?verbose :: Word -> Bool)
- type Progs = ?progs :: Programs
- data Programs = Programs {- cabalProgram :: !FilePath
- cabalProjArgs :: ![String]
- cabalUnitArgs :: ![String]
- stackProgram :: !FilePath
- stackProjArgs :: ![String]
- stackUnitArgs :: ![String]
- stackEnv :: ![(String, EnvOverride)]
- ghcProgram :: !FilePath
- ghcPkgProgram :: !FilePath
- haddockProgram :: !FilePath
 
- defaultPrograms :: Programs
- data EnvOverride
- data CompileOptions = CompileOptions {}
- oCabalProgram :: Env => FilePath
- defaultCompileOptions :: CompileOptions
- newtype PackageDbDir = PackageDbDir {}
- newtype PackageEnvFile = PackageEnvFile {}
Documentation
The kind of project being managed by a QueryEnv (pun intended). Used
 as a phantom-type variable throughout to make the project type being
 passed into various functions correspond to the correct implementation.
Constructors
| Cabal CabalProjType | 
 | 
| Stack | 
 | 
data CabalProjType Source #
The kind of a cabal project.
Instances
| Eq CabalProjType Source # | |
| Defined in CabalHelper.Compiletime.Types Methods (==) :: CabalProjType -> CabalProjType -> Bool # (/=) :: CabalProjType -> CabalProjType -> Bool # | |
| Ord CabalProjType Source # | |
| Defined in CabalHelper.Compiletime.Types Methods compare :: CabalProjType -> CabalProjType -> Ordering # (<) :: CabalProjType -> CabalProjType -> Bool # (<=) :: CabalProjType -> CabalProjType -> Bool # (>) :: CabalProjType -> CabalProjType -> Bool # (>=) :: CabalProjType -> CabalProjType -> Bool # max :: CabalProjType -> CabalProjType -> CabalProjType # min :: CabalProjType -> CabalProjType -> CabalProjType # | |
| Read CabalProjType Source # | |
| Defined in CabalHelper.Compiletime.Types Methods readsPrec :: Int -> ReadS CabalProjType # readList :: ReadS [CabalProjType] # | |
| Show CabalProjType Source # | |
| Defined in CabalHelper.Compiletime.Types Methods showsPrec :: Int -> CabalProjType -> ShowS # show :: CabalProjType -> String # showList :: [CabalProjType] -> ShowS # | |
data SProjType pt where Source #
A "singleton" datatype for ProjType which allows us to establish a
 correspondence between a runtime representation of ProjType to the
 compile-time value at the type level.
If you just want to know the runtime ProjType use demoteSProjType to
 convert to that.
data SCabalProjType pt where Source #
This is a singleton, like SProjType, but restricted to just the
 Cabal project types. We use this to restrict some functions which don't
 make sense for Stack to just the Cabal project types.
Constructors
| SCV1 :: SCabalProjType CV1 | |
| SCV2 :: SCabalProjType CV2 | 
Instances
| Show (SCabalProjType pt) Source # | |
| Defined in CabalHelper.Compiletime.Types Methods showsPrec :: Int -> SCabalProjType pt -> ShowS # show :: SCabalProjType pt -> String # showList :: [SCabalProjType pt] -> ShowS # | |
demoteSProjType :: SProjType pt -> ProjType Source #
data ProjLoc (pt :: ProjType) where Source #
Location of a project context. This is usually just the path project's top-level source code directory together with an optional project-type specific config file path.
To find any recognized default project contexts in a given directory
 use findProjects.
Build tools usually allow the user to specify the location of their
 project config files manually, so we also support passing this path here
 with the *File constructors.
Correspondence between Project and Package Source Directories
Note that the project's source directory does not necessarily correspond to the directory containing the project config file, though in some cases it does.
For example cabal v2-build allows the cabal.project file to be
 positively anywhere in the filesystem when specified via the
 --cabal-project command-line flag, corresponding to the
 ProjLocV2File constructor here. This config file can then refer to
 package directories with absolute paths in the packages: declaration.
Hence it isn't actually possible to find one directory which contains
 the whole project's source code but rather we have to consider each
 package's source directory individually, see pSourceDir
Constructors
| ProjLocV1CabalFile | A fully specified  Note that more than one such files existing in a package directory is a user error and while cabal will still complain about that we won't. Also note that for this project type the concepts of project and package coincide. | 
| Fields 
 | |
| ProjLocV1Dir | A  If more than one  | 
| Fields 
 | |
| ProjLocV2File | A  | 
| Fields 
 | |
| ProjLocV2Dir | This is equivalent to  | 
| Fields 
 | |
| ProjLocStackYaml | A  Note: with Stack the invariant  | 
| Fields 
 | |
projTypeOfProjLoc :: ProjLoc pt -> SProjType pt Source #
data DistDir (pt :: ProjType) where Source #
A build directory for a certain project type. The pt type variable
 must be compatible with the ProjLoc used. This is enforced by the type
 system so you can't get this wrong.
Constructors
| DistDirCabal :: !(SCabalProjType pt) -> !FilePath -> DistDir (Cabal pt) | A build-directory for cabal, aka. dist-dir in Cabal
 terminology.  | 
| DistDirStack :: !(Maybe RelativePath) -> DistDir Stack | A build-directory for stack, aka. work-dir. Optionally override
 Stack's work-dir. If you just want to use Stack's default set to
  | 
projTypeOfDistDir :: DistDir pt -> SProjType pt Source #
General purpose existential wrapper. Useful for hiding a phantom type argument.
Say you have:
{-# LANGUAGE DataKinds, GADTS #-}
data K = A | B | ...
data Q k where
  QA :: ... -> Q 'A
  QB :: ... -> Q 'B
and you want a list of Q. You can use Ex to hide the phantom type
 argument and recover it later by matching on the GADT constructors:
qa :: Q A qa = QA qb :: Q B qb = QB mylist :: [Ex Q] mylist = [Ex qa, Ex qb]
Constructors
| Ex (a x) | 
type QueryEnv pt = QueryEnvI QueryCache pt Source #
Environment for running a Query. The constructor is not exposed in the
 API to allow extending it with more fields without breaking user code.
To create a QueryEnv use the mkQueryEnv smart constructor instead. Some
 field accessors are exported and may be used to override the defaults filled
 in by mkQueryEnv. See below.
Note that this environment contains an IORef used as a cache. If you want
 to take advantage of this you should not simply discard the value returned by
 the smart constructor after one use.
data QueryEnvI c (pt :: ProjType) Source #
Constructors
| QueryEnv | |
| Fields 
 | |
projTypeOfQueryEnv :: QueryEnvI c pt -> SProjType pt Source #
type CallProcessWithCwdAndEnv a = Maybe FilePath -> [(String, EnvOverride)] -> FilePath -> [String] -> IO a Source #
type QueryCache = QueryCacheI PreInfo Programs ProjInfo UnitInfo Source #
Full instansiation of QueryCacheI, with all cache fields visible
type QCPreInfo progs proj_info unit_info = QueryCacheI PreInfo progs proj_info unit_info Source #
QueryCacheI, only instantiated with PreInfo cache.
type QCProgs proj_info unit_info = QueryCacheI PreInfo Programs proj_info unit_info Source #
QueryCacheI, only instantiated with PreInfo and configured
 Programs cache.
data QueryCacheI pre_info progs proj_info unit_info pt Source #
Constructors
| QueryCache | |
| Fields 
 | |
data CacheKeyCache pt Source #
Constructors
| CacheKeyCache | |
| Fields 
 | |
newtype DistDirLib Source #
Constructors
| DistDirLib FilePath | 
Instances
| Eq DistDirLib Source # | |
| Defined in CabalHelper.Compiletime.Types | |
| Ord DistDirLib Source # | |
| Defined in CabalHelper.Compiletime.Types Methods compare :: DistDirLib -> DistDirLib -> Ordering # (<) :: DistDirLib -> DistDirLib -> Bool # (<=) :: DistDirLib -> DistDirLib -> Bool # (>) :: DistDirLib -> DistDirLib -> Bool # (>=) :: DistDirLib -> DistDirLib -> Bool # max :: DistDirLib -> DistDirLib -> DistDirLib # min :: DistDirLib -> DistDirLib -> DistDirLib # | |
| Read DistDirLib Source # | |
| Defined in CabalHelper.Compiletime.Types Methods readsPrec :: Int -> ReadS DistDirLib # readList :: ReadS [DistDirLib] # readPrec :: ReadPrec DistDirLib # readListPrec :: ReadPrec [DistDirLib] # | |
| Show DistDirLib Source # | |
| Defined in CabalHelper.Compiletime.Types Methods showsPrec :: Int -> DistDirLib -> ShowS # show :: DistDirLib -> String # showList :: [DistDirLib] -> ShowS # | |
Constructors
| Package | |
| Fields 
 | |
A Unit is essentially a "build target". It is used to refer to a set
 of components (exes, libs, tests etc.) which are managed by a certain
 instance of the Cabal build-system[1]. We may get information on the
 components in a unit by retriving the corresponding UnitInfo.
[1]: No I'm not talking about the cabal-install build-tool, I'm
 talking about the Cabal build-system. Note the distinction. Both
 cabal-install and Stack use the Cabal build-system (aka lib:Cabal)
 underneath.
Note that a Unit value is only valid within the QueryEnv context it
 was created in, this is however this is not enforced by the
 API. Furthermore if the user changes the underlying project
 configuration while your application is running even a properly scoped
 Unit could become invalid because the component it belongs to was
 removed from the cabal file.
Constructors
| Unit | |
data UnitImpl pt where Source #
Constructors
| UnitImplV1 :: UnitImpl (Cabal CV1) | |
| UnitImplV2 | |
| Fields 
 | |
| UnitImplStack :: UnitImpl Stack | |
uComponentName :: Unit pt -> Maybe ChComponentName Source #
This returns the component a Unit corresponds to. This information is
 only available if the correspondence happens to be unique and known before
 querying setup-config for the respective project type. Currently this only
 applies to pt=V2.
This is intended to be used as an optimization, to allow reducing the number of helper invocations for clients that don't need to know the entire project structure.
data UnitHeader Source #
The setup-config header. Note that Cabal writes all the package names in
 the header using Char8 and hence all characters are
 truncated from Unicode codepoints to 8-bit Latin-1.
We can be fairly confident that uhSetupId and uhCompilerId won't have
 names that cause trouble here so it's ok to look at them but user packages
 are free to have any unicode name.
Constructors
| UnitHeader | |
| Fields 
 | |
Instances
| Eq UnitHeader Source # | |
| Defined in CabalHelper.Compiletime.Types | |
| Ord UnitHeader Source # | |
| Defined in CabalHelper.Compiletime.Types Methods compare :: UnitHeader -> UnitHeader -> Ordering # (<) :: UnitHeader -> UnitHeader -> Bool # (<=) :: UnitHeader -> UnitHeader -> Bool # (>) :: UnitHeader -> UnitHeader -> Bool # (>=) :: UnitHeader -> UnitHeader -> Bool # max :: UnitHeader -> UnitHeader -> UnitHeader # min :: UnitHeader -> UnitHeader -> UnitHeader # | |
| Read UnitHeader Source # | |
| Defined in CabalHelper.Compiletime.Types Methods readsPrec :: Int -> ReadS UnitHeader # readList :: ReadS [UnitHeader] # readPrec :: ReadPrec UnitHeader # readListPrec :: ReadPrec [UnitHeader] # | |
| Show UnitHeader Source # | |
| Defined in CabalHelper.Compiletime.Types Methods showsPrec :: Int -> UnitHeader -> ShowS # show :: UnitHeader -> String # showList :: [UnitHeader] -> ShowS # | |
The information extracted from a 'Unit'\'s on-disk configuration cache.
Constructors
| UnitInfo | |
| Fields 
 | |
data ProjConf pt where Source #
Files relevant to the project-scope configuration. We gather them here so we can refer to their paths conveniently throughout the code. These files are not necessarily guaranteed to even exist.
Constructors
| ProjConfV1 | |
| Fields 
 | |
| ProjConfV2 | |
| Fields 
 | |
| ProjConfStack | |
| Fields 
 | |
projTypeOfProjConf :: ProjConf pt -> SProjType pt Source #
newtype ProjConfModTimes Source #
Constructors
| ProjConfModTimes [(FilePath, EpochTime)] | 
Instances
| Eq ProjConfModTimes Source # | |
| Defined in CabalHelper.Compiletime.Types Methods (==) :: ProjConfModTimes -> ProjConfModTimes -> Bool # (/=) :: ProjConfModTimes -> ProjConfModTimes -> Bool # | |
| Show ProjConfModTimes Source # | |
| Defined in CabalHelper.Compiletime.Types Methods showsPrec :: Int -> ProjConfModTimes -> ShowS # show :: ProjConfModTimes -> String # showList :: [ProjConfModTimes] -> ShowS # | |
Project-scope information cache.
Constructors
| ProjInfo | |
| Fields 
 | |
data ProjInfoImpl pt where Source #
Constructors
| ProjInfoV1 | |
| Fields 
 | |
| ProjInfoV2 | |
| Fields 
 | |
| ProjInfoStack :: ProjInfoImpl Stack | |
Instances
| Show (ProjInfoImpl pt) Source # | |
| Defined in CabalHelper.Compiletime.Types Methods showsPrec :: Int -> ProjInfoImpl pt -> ShowS # show :: ProjInfoImpl pt -> String # showList :: [ProjInfoImpl pt] -> ShowS # | |
data UnitModTimes Source #
Constructors
| UnitModTimes | |
| Fields 
 | |
Instances
| Eq UnitModTimes Source # | |
| Defined in CabalHelper.Compiletime.Types | |
| Ord UnitModTimes Source # | |
| Defined in CabalHelper.Compiletime.Types Methods compare :: UnitModTimes -> UnitModTimes -> Ordering # (<) :: UnitModTimes -> UnitModTimes -> Bool # (<=) :: UnitModTimes -> UnitModTimes -> Bool # (>) :: UnitModTimes -> UnitModTimes -> Bool # (>=) :: UnitModTimes -> UnitModTimes -> Bool # max :: UnitModTimes -> UnitModTimes -> UnitModTimes # min :: UnitModTimes -> UnitModTimes -> UnitModTimes # | |
| Read UnitModTimes Source # | |
| Defined in CabalHelper.Compiletime.Types Methods readsPrec :: Int -> ReadS UnitModTimes # readList :: ReadS [UnitModTimes] # | |
| Show UnitModTimes Source # | |
| Defined in CabalHelper.Compiletime.Types Methods showsPrec :: Int -> UnitModTimes -> ShowS # show :: UnitModTimes -> String # showList :: [UnitModTimes] -> ShowS # | |
data PreInfo pt where Source #
Constructors
| PreInfoCabal :: PreInfo (Cabal cpt) | |
| PreInfoStack | |
| Fields 
 | |
data StackProjPaths Source #
Constructors
| StackProjPaths | |
| Fields | |
Instances
| Show StackProjPaths Source # | |
| Defined in CabalHelper.Compiletime.Types Methods showsPrec :: Int -> StackProjPaths -> ShowS # show :: StackProjPaths -> String # showList :: [StackProjPaths] -> ShowS # | |
Configurable paths to various programs we use.
Constructors
| Programs | |
| Fields 
 | |
Instances
defaultPrograms :: Programs Source #
By default all programs use their unqualified names, i.e. they will be
 searched for on PATH.
data EnvOverride Source #
Constructors
| EnvPrepend String | |
| EnvAppend String | |
| EnvReplace String | 
Instances
data CompileOptions Source #
Constructors
| CompileOptions | |
| Fields 
 | |
oCabalProgram :: Env => FilePath Source #
newtype PackageDbDir Source #
Constructors
| PackageDbDir | |
| Fields | |
Instances
| Show PackageDbDir Source # | |
| Defined in CabalHelper.Compiletime.Types Methods showsPrec :: Int -> PackageDbDir -> ShowS # show :: PackageDbDir -> String # showList :: [PackageDbDir] -> ShowS # | |
newtype PackageEnvFile Source #
Constructors
| PackageEnvFile | |
| Fields | |
Instances
| Show PackageEnvFile Source # | |
| Defined in CabalHelper.Compiletime.Types Methods showsPrec :: Int -> PackageEnvFile -> ShowS # show :: PackageEnvFile -> String # showList :: [PackageEnvFile] -> ShowS # | |