cabal-helper-0.7.2.0: Simple interface to some of Cabal's configuration state used by ghc-mod

Safe HaskellNone
LanguageHaskell2010

Distribution.Helper

Contents

Synopsis

Documentation

data Programs Source #

Paths or names of various programs we need.

qeReadProcess :: QueryEnv -> FilePath -> [String] -> String -> IO String Source #

How to start the cabal-helper process. Useful if you need to capture stderr output from the helper.

qeProjectDir :: QueryEnv -> FilePath Source #

Path to project directory, i.e. the one containing the project.cabal file

qeDistDir :: QueryEnv -> FilePath Source #

Path to the dist/ directory

qeCabalPkgDb :: QueryEnv -> Maybe FilePath Source #

Where to look for the Cabal library when linking the helper

qeCabalVer :: QueryEnv -> Maybe Version Source #

If dist/setup-config wasn't written by this version of Cabal throw an error

defaultQueryEnv Source #

Arguments

:: FilePath

Path to project directory, i.e. the one containing the project.cabal file

-> FilePath

Path to the dist/ directory

-> QueryEnv 

Running Queries

data Query m a Source #

Caches helper executable result so it doesn't have to be run more than once as reading in Cabal's LocalBuildInfo datatype from disk is very slow but running all possible queries against it at once is cheap.

Instances

MonadTrans Query Source # 

Methods

lift :: Monad m => m a -> Query m a #

Monad m => Monad (Query m) Source # 

Methods

(>>=) :: Query m a -> (a -> Query m b) -> Query m b #

(>>) :: Query m a -> Query m b -> Query m b #

return :: a -> Query m a #

fail :: String -> Query m a #

Functor m => Functor (Query m) Source # 

Methods

fmap :: (a -> b) -> Query m a -> Query m b #

(<$) :: a -> Query m b -> Query m a #

Monad m => Applicative (Query m) Source # 

Methods

pure :: a -> Query m a #

(<*>) :: Query m (a -> b) -> Query m a -> Query m b #

(*>) :: Query m a -> Query m b -> Query m b #

(<*) :: Query m a -> Query m b -> Query m a #

MonadIO m => MonadIO (Query m) Source # 

Methods

liftIO :: IO a -> Query m a #

runQuery :: Monad m => QueryEnv -> Query m a -> m a Source #

runQuery query distdir. Run a Query. distdir is where Cabal's setup-config file is located.

Queries against Cabal's on disk state

packageDbStack :: MonadIO m => Query m [ChPkgDb] Source #

List of package databases to use.

entrypoints :: MonadIO m => Query m [(ChComponentName, ChEntrypoint)] Source #

Modules or files Cabal would have the compiler build directly. Can be used to compute the home module closure for a component.

sourceDirs :: MonadIO m => Query m [(ChComponentName, [FilePath])] Source #

A component's source-dirs field, beware as if this is empty implicit behaviour in GHC kicks in.

ghcOptions :: MonadIO m => Query m [(ChComponentName, [String])] Source #

All options cabal would pass to GHC.

ghcSrcOptions :: MonadIO m => Query m [(ChComponentName, [String])] Source #

Only search path related GHC options.

ghcPkgOptions :: MonadIO m => Query m [(ChComponentName, [String])] Source #

Only package related GHC options, sufficient for things don't need to access any home modules.

ghcMergedPkgOptions :: MonadIO m => Query m [String] Source #

Like ghcPkgOptions but for the whole package not just one component

ghcLangOptions :: MonadIO m => Query m [(ChComponentName, [String])] Source #

Only language related options, i.e. -XSomeExtension

pkgLicenses :: MonadIO m => Query m [(String, [(String, Version)])] Source #

Get the licenses of the packages the current project is linking against.

flags :: MonadIO m => Query m [(String, Bool)] Source #

Flag definitions from cabal file

configFlags :: MonadIO m => Query m [(String, Bool)] Source #

Flag assignments from setup-config

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.

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

Result types

data ChComponentName Source #

Instances

Eq ChComponentName Source # 
Ord ChComponentName Source # 
Read ChComponentName Source # 
Show ChComponentName Source # 
Generic ChComponentName Source # 
type Rep ChComponentName Source # 

data ChPkgDb Source #

Instances

Eq ChPkgDb Source # 

Methods

(==) :: ChPkgDb -> ChPkgDb -> Bool #

(/=) :: ChPkgDb -> ChPkgDb -> Bool #

Ord ChPkgDb Source # 
Read ChPkgDb Source # 
Show ChPkgDb Source # 
Generic ChPkgDb Source # 

Associated Types

type Rep ChPkgDb :: * -> * #

Methods

from :: ChPkgDb -> Rep ChPkgDb x #

to :: Rep ChPkgDb x -> ChPkgDb #

type Rep ChPkgDb Source # 
type Rep ChPkgDb = D1 (MetaData "ChPkgDb" "CabalHelper.Types" "cabal-helper-0.7.2.0-9btZ8QaP2mT56PTVu4AAT5" False) ((:+:) (C1 (MetaCons "ChPkgGlobal" PrefixI False) U1) ((:+:) (C1 (MetaCons "ChPkgUser" PrefixI False) U1) (C1 (MetaCons "ChPkgSpecific" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)))))

data ChEntrypoint Source #

Constructors

ChSetupEntrypoint

Almost like ChExeEntrypoint but main-is could either be "Setup.hs" or "Setup.lhs". Since we don't know where the source directory is you have to find these files.

ChLibEntrypoint 
ChExeEntrypoint 

Instances

Eq ChEntrypoint Source # 
Ord ChEntrypoint Source # 
Read ChEntrypoint Source # 
Show ChEntrypoint Source # 
Generic ChEntrypoint Source # 

Associated Types

type Rep ChEntrypoint :: * -> * #

type Rep ChEntrypoint Source # 
type Rep ChEntrypoint = D1 (MetaData "ChEntrypoint" "CabalHelper.Types" "cabal-helper-0.7.2.0-9btZ8QaP2mT56PTVu4AAT5" False) ((:+:) (C1 (MetaCons "ChSetupEntrypoint" PrefixI False) U1) ((:+:) (C1 (MetaCons "ChLibEntrypoint" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "chExposedModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ChModuleName])) (S1 (MetaSel (Just Symbol "chOtherModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ChModuleName])))) (C1 (MetaCons "ChExeEntrypoint" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "chMainIs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)) (S1 (MetaSel (Just Symbol "chOtherModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ChModuleName]))))))

General information

Stuff that cabal-install really should export

getSandboxPkgDb Source #

Arguments

:: (FilePath -> [String] -> String -> IO String) 
-> FilePath

Cabal build platform, i.e. buildPlatform

-> Version

GHC version (cProjectVersion is your friend)

-> IO (Maybe FilePath) 

Get the path to the sandbox package-db in a project

Managing dist/

prepare :: MonadIO m => (FilePath -> [String] -> String -> IO String) -> FilePath -> FilePath -> m () Source #

Deprecated: Will be replaced by prepare' in the next major release

prepare' :: MonadIO m => QueryEnv -> m () Source #

Make sure the appropriate helper executable for the given project is installed and ready to run queries.

reconfigure Source #

Arguments

:: MonadIO m 
=> (FilePath -> [String] -> String -> IO String) 
-> Programs

Program paths

-> [String]

Command line arguments to be passed to cabal

-> m () 

Run cabal configure

writeAutogenFiles Source #

Arguments

:: MonadIO m 
=> (FilePath -> [String] -> String -> IO String) 
-> FilePath

Path to project directory, i.e. the one containing the project.cabal file

-> FilePath

Path to the dist/ directory

-> m () 

Deprecated: Will be replaced by writeAutogenFiles' in the next major release

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.

libexecNotFoundError Source #

Arguments

:: String

Name of the executable we were trying to find

-> FilePath

Path to $libexecdir

-> String

URL the user will be directed towards to report a bug.

-> String