License | Apache-2.0 |
---|---|
Maintainer | cabal-helper@dxld.at |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Query pt a
- runQuery :: Query pt a -> QueryEnv pt -> IO a
- compilerVersion :: Query pt (String, Version)
- projectPackages :: Query pt (NonEmpty (Package pt))
- type Package pt = Package' (NonEmpty (Unit pt))
- pPackageName :: Package' units -> String
- pSourceDir :: Package' units -> FilePath
- pUnits :: Package' units -> units
- data Unit pt
- uComponentName :: Unit pt -> Maybe ChComponentName
- data UnitId
- 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
- unitInfo :: Unit pt -> Query pt UnitInfo
- allUnits :: (UnitInfo -> a) -> Query pt (NonEmpty a)
- type QueryEnv pt = QueryEnvI QueryCache pt
- data QueryEnvI c (pt :: ProjType)
- mkQueryEnv :: ProjLoc pt -> DistDir pt -> IO (QueryEnv pt)
- qeReadProcess :: QueryEnvI c pt -> ReadProcessWithCwdAndEnv
- qeCallProcess :: QueryEnvI c pt -> CallProcessWithCwdAndEnv ()
- qePrograms :: QueryEnvI c pt -> Programs
- qeProjLoc :: QueryEnvI c pt -> ProjLoc pt
- qeDistDir :: QueryEnvI c pt -> DistDir pt
- data ProjType
- data CabalProjType
- data ProjLoc (pt :: ProjType) where
- ProjLocV1CabalFile :: {..} -> ProjLoc (Cabal CV1)
- ProjLocV1Dir :: {..} -> ProjLoc (Cabal CV1)
- ProjLocV2File :: {..} -> ProjLoc (Cabal CV2)
- ProjLocV2Dir :: {..} -> ProjLoc (Cabal CV2)
- ProjLocStackYaml :: {..} -> ProjLoc Stack
- data DistDir (pt :: ProjType) where
- DistDirCabal :: !(SCabalProjType pt) -> !FilePath -> DistDir (Cabal pt)
- DistDirStack :: !(Maybe RelativePath) -> DistDir Stack
- data SProjType pt where
- demoteSProjType :: SProjType pt -> ProjType
- projTypeOfDistDir :: DistDir pt -> SProjType pt
- projTypeOfProjLoc :: ProjLoc pt -> SProjType pt
- data SCabalProjType pt where
- data Ex a = Ex (a x)
- 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 ChComponentInfo = ChComponentInfo {}
- data ChComponentName
- data ChLibraryName
- newtype ChModuleName = ChModuleName {}
- data ChPkgDb
- data ChEntrypoint
- = ChSetupEntrypoint { }
- | ChLibEntrypoint { }
- | ChExeEntrypoint { }
- buildPlatform :: String
- getSandboxPkgDb :: String -> GhcVersion -> FilePath -> IO (Maybe FilePath)
- prepare :: Query pt ()
- writeAutogenFiles :: Unit pt -> Query pt ()
- buildProject :: Query pt ()
- buildUnits :: [Unit pt] -> Query pt ()
Type Variable Naming Conventions
Throughout the API we use the following conventions for type variables:
pt
stands for "project type", when instantiated it is always of kindProjType
.c
stands for "cache". It is used internally to make the cache inaccessible for some parts of the implementation. Users of the API may completely ignore this parameter. See the internalqeCacheRef
field accessor ofQueryEnv
for details.
Running Queries
A query against a package's Cabal configuration. Use runQuery
to
execute it.
Queries against Cabal's on disk state
Project queries
compilerVersion :: Query pt (String, Version) Source #
The version of GHC the project is configured to use for compilation.
projectPackages :: Query pt (NonEmpty (Package pt)) Source #
All local packages currently active in a project's build plan.
Package
queries
pPackageName :: Package' units -> String Source #
pSourceDir :: Package' units -> FilePath Source #
pUnits :: Package' units -> units Source #
Cabal flags to set when configuring and building this package.
Unit
queries
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.
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.
The information extracted from a 'Unit'\'s on-disk configuration cache.
UnitInfo | |
|
Convenience Queries
allUnits :: (UnitInfo -> a) -> Query pt (NonEmpty a) Source #
Get information on all units in a project.
Query environment
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.
qeReadProcess :: QueryEnvI c pt -> ReadProcessWithCwdAndEnv Source #
Field accessor for QueryEnv
. Function used to to start processes
and capture output. Useful if you need to, for example, redirect
standard error output of programs started by cabal-helper.
qeCallProcess :: QueryEnvI c pt -> CallProcessWithCwdAndEnv () Source #
Field accessor for QueryEnv
. Function used to to start processes
without capturing output. See also qeReadProcess
.
qePrograms :: QueryEnvI c pt -> Programs Source #
Field accessor for QueryEnv
. Paths to various programs we use.
qeProjLoc :: QueryEnvI c pt -> ProjLoc pt Source #
Field accessor for QueryEnv
. Defines path to the project directory,
i.e. a directory containing a cabal.project
file
qeDistDir :: QueryEnvI c pt -> DistDir pt Source #
Field accessor for QueryEnv
. Defines path to the dist/
or
dist-newstyle/
directory, aka. builddir in Cabal terminology.
GADTs
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.
Cabal CabalProjType |
|
Stack |
|
data CabalProjType Source #
The kind of a cabal
project.
Instances
Eq CabalProjType Source # | |
Defined in CabalHelper.Compiletime.Types (==) :: CabalProjType -> CabalProjType -> Bool # (/=) :: CabalProjType -> CabalProjType -> Bool # | |
Ord CabalProjType Source # | |
Defined in CabalHelper.Compiletime.Types 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 readsPrec :: Int -> ReadS CabalProjType # readList :: ReadS [CabalProjType] # | |
Show CabalProjType Source # | |
Defined in CabalHelper.Compiletime.Types showsPrec :: Int -> CabalProjType -> ShowS # show :: CabalProjType -> String # showList :: [CabalProjType] -> ShowS # |
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
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. |
| |
ProjLocV1Dir | A If more than one |
| |
ProjLocV2File | A |
| |
ProjLocV2Dir | This is equivalent to |
| |
ProjLocStackYaml | A Note: with Stack the invariant |
|
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.
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
|
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.
demoteSProjType :: SProjType pt -> ProjType Source #
projTypeOfDistDir :: DistDir pt -> SProjType pt Source #
projTypeOfProjLoc :: ProjLoc pt -> SProjType pt Source #
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.
SCV1 :: SCabalProjType CV1 | |
SCV2 :: SCabalProjType CV2 |
Instances
Show (SCabalProjType pt) Source # | |
Defined in CabalHelper.Compiletime.Types showsPrec :: Int -> SCabalProjType pt -> ShowS # show :: SCabalProjType pt -> String # showList :: [SCabalProjType pt] -> ShowS # |
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]
Ex (a x) |
Programs
Configurable paths to various programs we use.
Programs | |
|
Instances
defaultPrograms :: Programs Source #
By default all programs use their unqualified names, i.e. they will be
searched for on PATH
.
data EnvOverride Source #
Instances
Query result types
data ChComponentInfo Source #
ChComponentInfo | |
|
Instances
Eq ChComponentInfo Source # | |
Defined in CabalHelper.Shared.InterfaceTypes (==) :: ChComponentInfo -> ChComponentInfo -> Bool # (/=) :: ChComponentInfo -> ChComponentInfo -> Bool # | |
Ord ChComponentInfo Source # | |
Defined in CabalHelper.Shared.InterfaceTypes compare :: ChComponentInfo -> ChComponentInfo -> Ordering # (<) :: ChComponentInfo -> ChComponentInfo -> Bool # (<=) :: ChComponentInfo -> ChComponentInfo -> Bool # (>) :: ChComponentInfo -> ChComponentInfo -> Bool # (>=) :: ChComponentInfo -> ChComponentInfo -> Bool # max :: ChComponentInfo -> ChComponentInfo -> ChComponentInfo # min :: ChComponentInfo -> ChComponentInfo -> ChComponentInfo # | |
Read ChComponentInfo Source # | |
Defined in CabalHelper.Shared.InterfaceTypes | |
Show ChComponentInfo Source # | |
Defined in CabalHelper.Shared.InterfaceTypes showsPrec :: Int -> ChComponentInfo -> ShowS # show :: ChComponentInfo -> String # showList :: [ChComponentInfo] -> ShowS # |
data ChComponentName Source #
ChSetupHsName | |
ChLibName ChLibraryName | |
ChFLibName String | |
ChExeName String | |
ChTestName String | |
ChBenchName String |
Instances
data ChLibraryName Source #
Instances
newtype ChModuleName Source #
Instances
Instances
Eq ChPkgDb Source # | |
Ord ChPkgDb Source # | |
Defined in CabalHelper.Shared.InterfaceTypes | |
Read ChPkgDb Source # | |
Show ChPkgDb Source # | |
Generic ChPkgDb Source # | |
type Rep ChPkgDb Source # | |
Defined in CabalHelper.Shared.InterfaceTypes type Rep ChPkgDb = D1 (MetaData "ChPkgDb" "CabalHelper.Shared.InterfaceTypes" "cabal-helper-1.1.0.0-8hQYifbIUuK6Vc5oLdO5q5" False) (C1 (MetaCons "ChPkgGlobal" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ChPkgUser" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ChPkgSpecific" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)))) |
data ChEntrypoint Source #
Instances
General information
Legacy v1-build helpers
:: String | Cabal build platform, i.e. |
-> GhcVersion | GHC version ( |
-> FilePath | Path to the project directory, i.e. a directory containing a
|
-> IO (Maybe FilePath) |
Get the path to the sandbox package-db in a project
Build actions
prepare :: Query pt () Source #
Make sure the appropriate helper executable for the given project is installed and ready to run queries.
The idea is you can run this at a convinient time instead of having the helper compilation happen during a time-sensitive user interaction. This will however happen automatically as needed if you don't run it first.
writeAutogenFiles :: Unit pt -> Query pt () Source #
Create cabal_macros.h
, Paths_<pkg>.hs
and other generated files
in the usual place. See initialBuildSteps
.
This is usually only needed on the first load of a unit or after the cabal file changes.
buildProject :: Query pt () Source #
buildUnits :: [Unit pt] -> Query pt () Source #