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

LicenseGPL-3
Maintainercabal-helper@dxld.at
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Distribution.Helper

Contents

Description

 
Synopsis

Running Queries

data Query m a Source #

A lazy, cached, query against a package's Cabal configuration. Use runQuery to execute it.

Instances
MonadTrans Query Source # 
Instance details

Defined in Distribution.Helper

Methods

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

Monad m => Monad (Query m) Source # 
Instance details

Defined in Distribution.Helper

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 # 
Instance details

Defined in Distribution.Helper

Methods

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

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

Monad m => Applicative (Query m) Source # 
Instance details

Defined in Distribution.Helper

Methods

pure :: a -> Query m a #

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

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

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

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

MonadIO m => MonadIO (Query m) Source # 
Instance details

Defined in Distribution.Helper

Methods

liftIO :: IO a -> Query m a #

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

runQuery env query. Run a Query under a given QueryEnv.

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

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

List of package databases to use.

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

Flag definitions from cabal file

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

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.

Component queries

data ComponentQuery m a Source #

A Query to run on all components of a package. Use components to get a regular Query.

Instances
Functor m => Functor (ComponentQuery m) Source # 
Instance details

Defined in Distribution.Helper

Methods

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

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

(Functor m, Monad m) => Apply (ComponentQuery m) Source # 
Instance details

Defined in Distribution.Helper

Methods

(<.>) :: ComponentQuery m (a -> b) -> ComponentQuery m a -> ComponentQuery m b #

(.>) :: ComponentQuery m a -> ComponentQuery m b -> ComponentQuery m b #

(<.) :: ComponentQuery m a -> ComponentQuery m b -> ComponentQuery m a #

liftF2 :: (a -> b -> c) -> ComponentQuery m a -> ComponentQuery m b -> ComponentQuery m c #

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

data QueryEnv Source #

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.

mkQueryEnv Source #

Arguments

:: FilePath

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

-> FilePath

Path to the dist/ directory, called builddir in Cabal terminology.

-> 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.

qePrograms :: QueryEnv -> Programs Source #

Field accessor for QueryEnv.

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.

data Programs Source #

Paths or names of various programs we need.

Constructors

Programs 

Fields

Instances
Eq Programs Source # 
Instance details

Defined in Distribution.Helper

Ord Programs Source # 
Instance details

Defined in Distribution.Helper

Read Programs Source # 
Instance details

Defined in Distribution.Helper

Show Programs Source # 
Instance details

Defined in Distribution.Helper

Generic Programs Source # 
Instance details

Defined in Distribution.Helper

Associated Types

type Rep Programs :: * -> * #

Methods

from :: Programs -> Rep Programs x #

to :: Rep Programs x -> Programs #

type Rep Programs Source # 
Instance details

Defined in Distribution.Helper

type Rep Programs = D1 (MetaData "Programs" "Distribution.Helper" "cabal-helper-0.8.1.2-GZRDs0tuzrL2LsbHyH4QnY" False) (C1 (MetaCons "Programs" PrefixI True) (S1 (MetaSel (Just "cabalProgram") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath) :*: (S1 (MetaSel (Just "ghcProgram") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath) :*: S1 (MetaSel (Just "ghcPkgProgram") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath))))

defaultPrograms :: Programs Source #

Default all programs to their unqualified names, i.e. they will be searched for on PATH.

Result types

newtype ChModuleName Source #

Constructors

ChModuleName String 
Instances
Eq ChModuleName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Ord ChModuleName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Read ChModuleName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Show ChModuleName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Generic ChModuleName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Associated Types

type Rep ChModuleName :: * -> * #

type Rep ChModuleName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

type Rep ChModuleName = D1 (MetaData "ChModuleName" "CabalHelper.Shared.InterfaceTypes" "cabal-helper-0.8.1.2-GZRDs0tuzrL2LsbHyH4QnY" True) (C1 (MetaCons "ChModuleName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

data ChComponentName Source #

Instances
Eq ChComponentName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Ord ChComponentName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Read ChComponentName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Show ChComponentName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Generic ChComponentName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Associated Types

type Rep ChComponentName :: * -> * #

type Rep ChComponentName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

data ChPkgDb Source #

Instances
Eq ChPkgDb Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Methods

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

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

Ord ChPkgDb Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Read ChPkgDb Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Show ChPkgDb Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Generic ChPkgDb Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Associated Types

type Rep ChPkgDb :: * -> * #

Methods

from :: ChPkgDb -> Rep ChPkgDb x #

to :: Rep ChPkgDb x -> ChPkgDb #

type Rep ChPkgDb Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

type Rep ChPkgDb = D1 (MetaData "ChPkgDb" "CabalHelper.Shared.InterfaceTypes" "cabal-helper-0.8.1.2-GZRDs0tuzrL2LsbHyH4QnY" False) (C1 (MetaCons "ChPkgGlobal" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "ChPkgUser" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ChPkgSpecific" PrefixI False) (S1 (MetaSel (Nothing :: Maybe 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 # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Ord ChEntrypoint Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Read ChEntrypoint Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Show ChEntrypoint Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Generic ChEntrypoint Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Associated Types

type Rep ChEntrypoint :: * -> * #

type Rep ChEntrypoint Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

type Rep ChEntrypoint = D1 (MetaData "ChEntrypoint" "CabalHelper.Shared.InterfaceTypes" "cabal-helper-0.8.1.2-GZRDs0tuzrL2LsbHyH4QnY" False) (C1 (MetaCons "ChSetupEntrypoint" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "ChLibEntrypoint" PrefixI True) (S1 (MetaSel (Just "chExposedModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ChModuleName]) :*: (S1 (MetaSel (Just "chOtherModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ChModuleName]) :*: S1 (MetaSel (Just "chSignatures") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ChModuleName]))) :+: C1 (MetaCons "ChExeEntrypoint" PrefixI True) (S1 (MetaSel (Just "chMainIs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath) :*: S1 (MetaSel (Just "chOtherModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ChModuleName]))))

data NeedsBuildOutput Source #

Instances
Eq NeedsBuildOutput Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Ord NeedsBuildOutput Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Read NeedsBuildOutput Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Show NeedsBuildOutput Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Generic NeedsBuildOutput Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Associated Types

type Rep NeedsBuildOutput :: * -> * #

type Rep NeedsBuildOutput Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

type Rep NeedsBuildOutput = D1 (MetaData "NeedsBuildOutput" "CabalHelper.Shared.InterfaceTypes" "cabal-helper-0.8.1.2-GZRDs0tuzrL2LsbHyH4QnY" False) (C1 (MetaCons "ProduceBuildOutput" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "NoBuildOutput" PrefixI False) (U1 :: * -> *))

General information

Stuff that cabal-install really should export

getSandboxPkgDb Source #

Arguments

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

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 => 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 :: 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 

Reexports