License | AGPL-3 |
---|---|
Maintainer | dxld@darkboxed.org |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
- data Query m a
- runQuery :: Monad m => QueryEnv -> Query m a -> m a
- packageId :: MonadIO m => Query m (String, Version)
- packageDbStack :: MonadIO m => Query m [ChPkgDb]
- packageFlags :: MonadIO m => Query m [(String, Bool)]
- compilerVersion :: MonadIO m => Query m (String, Version)
- ghcMergedPkgOptions :: MonadIO m => Query m [String]
- configFlags :: MonadIO m => Query m [(String, Bool)]
- nonDefaultConfigFlags :: MonadIO m => Query m [(String, Bool)]
- data ComponentQuery m a
- components :: Monad m => ComponentQuery m (ChComponentName -> b) -> Query m [b]
- ghcSrcOptions :: MonadIO m => ComponentQuery m [String]
- ghcPkgOptions :: MonadIO m => ComponentQuery m [String]
- ghcLangOptions :: MonadIO m => ComponentQuery m [String]
- ghcOptions :: MonadIO m => ComponentQuery m [String]
- sourceDirs :: MonadIO m => ComponentQuery m [FilePath]
- entrypoints :: MonadIO m => ComponentQuery m ChEntrypoint
- needsBuildOutput :: MonadIO m => ComponentQuery m NeedsBuildOutput
- data QueryEnv
- mkQueryEnv :: FilePath -> FilePath -> QueryEnv
- qeReadProcess :: QueryEnv -> FilePath -> [String] -> String -> IO String
- qePrograms :: QueryEnv -> Programs
- qeProjectDir :: QueryEnv -> FilePath
- qeDistDir :: QueryEnv -> FilePath
- qeCabalPkgDb :: QueryEnv -> Maybe FilePath
- qeCabalVer :: QueryEnv -> Maybe Version
- data Programs = Programs {}
- defaultPrograms :: Programs
- newtype ChModuleName = ChModuleName String
- data ChComponentName
- data ChPkgDb
- data ChEntrypoint
- = ChSetupEntrypoint
- | ChLibEntrypoint { }
- | ChExeEntrypoint { }
- data NeedsBuildOutput
- buildPlatform :: (FilePath -> [String] -> String -> IO String) -> IO String
- getSandboxPkgDb :: (FilePath -> [String] -> String -> IO String) -> FilePath -> Version -> IO (Maybe FilePath)
- prepare :: MonadIO m => QueryEnv -> m ()
- reconfigure :: MonadIO m => (FilePath -> [String] -> String -> IO String) -> Programs -> [String] -> m ()
- writeAutogenFiles :: MonadIO m => QueryEnv -> m ()
- data LibexecNotFoundError = LibexecNotFoundError String FilePath
- libexecNotFoundError :: String -> FilePath -> String -> String
- module Data.Functor.Apply
Running Queries
A lazy, cached, query against a package's Cabal configuration. Use
runQuery
to execute it.
Queries against Cabal's on disk state
Package queries
packageId :: MonadIO m => Query m (String, Version) Source #
Package identifier, i.e. package name and version
compilerVersion :: MonadIO m => Query m (String, Version) Source #
The version of GHC the project is configured to use
ghcMergedPkgOptions :: MonadIO m => Query m [String] Source #
Like ghcPkgOptions
but for the whole package not just one component
cabal-install queries
nonDefaultConfigFlags :: MonadIO m => Query m [(String, Bool)] Source #
Flag assignments from setup-config which differ from the default setting. This can also include flags which cabal decided to modify, i.e. don't rely on these being the flags set by the user directly.
Component queries
data ComponentQuery m a Source #
A Query
to run on all components of a package. Use components
to get a
regular Query
.
components :: Monad m => ComponentQuery m (ChComponentName -> b) -> Query m [b] Source #
Run a ComponentQuery on all components of the package.
ghcSrcOptions :: MonadIO m => ComponentQuery m [String] Source #
Only search path related GHC options.
ghcPkgOptions :: MonadIO m => ComponentQuery m [String] Source #
Only package related GHC options, sufficient for things don't need to access any home modules.
ghcLangOptions :: MonadIO m => ComponentQuery m [String] Source #
Only language related options, i.e. -XSomeExtension
ghcOptions :: MonadIO m => ComponentQuery m [String] Source #
All options Cabal would pass to GHC.
sourceDirs :: MonadIO m => ComponentQuery m [FilePath] Source #
A component's source-dirs
field, beware since if this is empty implicit
behaviour in GHC kicks in.
entrypoints :: MonadIO m => ComponentQuery m ChEntrypoint Source #
Modules or files Cabal would have the compiler build directly. Can be used to compute the home module closure for a component.
needsBuildOutput :: MonadIO m => ComponentQuery m NeedsBuildOutput Source #
The component has a non-default module renaming, so needs build output ().
Query environment
Environment for running a Query
. The real constructor is not exposed,
the field accessors are however. See below. Use the mkQueryEnv
smart
constructor to construct one.
:: FilePath | Path to the project directory, i.e. the directory containing a
|
-> FilePath | Path to the |
-> QueryEnv |
mkQueryEnv projdir distdir
. Smart constructor for QueryEnv
.
Sets fields qeProjectDir
and qeDistDir
to projdir
and distdir
respectively and provides sensible defaults for the other fields.
qeReadProcess :: QueryEnv -> FilePath -> [String] -> String -> IO String Source #
Field accessor for QueryEnv
. Defines how to start the cabal-helper
process. Useful if you need to capture stderr output from the helper.
qeProjectDir :: QueryEnv -> FilePath Source #
Field accessor for QueryEnv
. Defines path to the project directory,
i.e. a directory containing a project.cabal
file
qeDistDir :: QueryEnv -> FilePath Source #
Field accessor for QueryEnv
. Defines path to the dist/
directory,
builddir in Cabal terminology.
qeCabalPkgDb :: QueryEnv -> Maybe FilePath Source #
Field accessor for QueryEnv
. Defines where to look for the Cabal
library when linking the helper.
qeCabalVer :: QueryEnv -> Maybe Version Source #
Field accessor for QueryEnv
. If dist/setup-config
wasn't written
by this version of Cabal an error is thrown when running the query.
Paths or names of various programs we need.
Programs | |
|
defaultPrograms :: Programs Source #
Default all programs to their unqualified names, i.e. they will be searched
for on PATH
.
Result types
newtype ChModuleName Source #
data ChComponentName Source #
data ChEntrypoint Source #
ChSetupEntrypoint | Almost like |
ChLibEntrypoint | |
| |
ChExeEntrypoint | |
|
data NeedsBuildOutput Source #
General information
Stuff that cabal-install really should export
:: (FilePath -> [String] -> String -> IO String) | |
-> FilePath | Cabal build platform, i.e. |
-> Version | GHC version ( |
-> IO (Maybe FilePath) |
Get the path to the sandbox package-db in a project
Managing dist/
prepare :: MonadIO m => QueryEnv -> m () Source #
Make sure the appropriate helper executable for the given project is installed and ready to run queries.
:: MonadIO m | |
=> (FilePath -> [String] -> String -> IO String) | |
-> Programs | Program paths |
-> [String] | Command line arguments to be passed to |
-> m () |
Run cabal configure
writeAutogenFiles :: MonadIO m => QueryEnv -> m () Source #
Create cabal_macros.h
and Paths_<pkg>
possibly other generated files
in the usual place.
$libexec related error handling
data LibexecNotFoundError Source #
This exception is thrown by all runQuery
functions if the internal
wrapper executable cannot be found. You may catch this and present the user
an appropriate error message however the default is to print
libexecNotFoundError
.
Reexports
module Data.Functor.Apply