cabal-file-th-0.2.6: Template Haskell expressions for reading fields from a project's cabal file.

Safe HaskellNone
LanguageHaskell98

Distribution.PackageDescription.TH

Contents

Description

Utility functions for reading cabal file fields through template haskell.

Synopsis

Template Haskell functions

packageVariable :: Text a => (PackageDescription -> a) -> Q Exp Source #

Renders the package variable specified by the function. The cabal file interrogated is the first one that is found in the current working directory.

packageVariableFrom :: Text a => FilePath -> (PackageDescription -> a) -> Q Exp Source #

Renders the package variable specified by the function, from a cabal file and the given path.

packageString :: String -> DocString Source #

Provides a Text instance for String, allowing text fields to be used in packageVariable. Use it composed with an accessor, eg. packageVariable (packageString . copyright)

Cabal file data structures

The data structures for the cabal file are re-exported here for ease of use.

data PackageDescription #

This data type is the internal representation of the file pkg.cabal. It contains two kinds of information about the package: information which is needed for all packages, such as the package name and version, and information which is needed for the simple build system only, such as the compiler options and library name.

Constructors

PackageDescription 

Fields

Instances
Eq PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Data PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageDescription -> c PackageDescription #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PackageDescription #

toConstr :: PackageDescription -> Constr #

dataTypeOf :: PackageDescription -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PackageDescription) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PackageDescription) #

gmapT :: (forall b. Data b => b -> b) -> PackageDescription -> PackageDescription #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageDescription -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageDescription -> r #

gmapQ :: (forall d. Data d => d -> u) -> PackageDescription -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageDescription -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageDescription -> m PackageDescription #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageDescription -> m PackageDescription #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageDescription -> m PackageDescription #

Read PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Show PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Generic PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Associated Types

type Rep PackageDescription :: Type -> Type #

HasBuildInfos PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Package PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

NFData PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Methods

rnf :: PackageDescription -> () #

Binary PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

type Rep PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

type Rep PackageDescription = D1 (MetaData "PackageDescription" "Distribution.Types.PackageDescription" "Cabal-2.4.0.1" False) (C1 (MetaCons "PackageDescription" PrefixI True) ((((S1 (MetaSel (Just "specVersionRaw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either Version VersionRange)) :*: (S1 (MetaSel (Just "package") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PackageIdentifier) :*: S1 (MetaSel (Just "licenseRaw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either License License)))) :*: ((S1 (MetaSel (Just "licenseFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]) :*: S1 (MetaSel (Just "copyright") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :*: (S1 (MetaSel (Just "maintainer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "author") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) :*: (((S1 (MetaSel (Just "stability") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "testedWith") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(CompilerFlavor, VersionRange)])) :*: (S1 (MetaSel (Just "homepage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "pkgUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) :*: ((S1 (MetaSel (Just "bugReports") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "sourceRepos") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SourceRepo])) :*: (S1 (MetaSel (Just "synopsis") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "description") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) :*: (((S1 (MetaSel (Just "category") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Just "customFieldsPD") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, String)]) :*: S1 (MetaSel (Just "buildTypeRaw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe BuildType)))) :*: ((S1 (MetaSel (Just "setupBuildInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SetupBuildInfo)) :*: S1 (MetaSel (Just "library") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Library))) :*: (S1 (MetaSel (Just "subLibraries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Library]) :*: S1 (MetaSel (Just "executables") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Executable])))) :*: (((S1 (MetaSel (Just "foreignLibs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ForeignLib]) :*: S1 (MetaSel (Just "testSuites") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TestSuite])) :*: (S1 (MetaSel (Just "benchmarks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Benchmark]) :*: S1 (MetaSel (Just "dataFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]))) :*: ((S1 (MetaSel (Just "dataDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath) :*: S1 (MetaSel (Just "extraSrcFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath])) :*: (S1 (MetaSel (Just "extraTmpFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]) :*: S1 (MetaSel (Just "extraDocFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath])))))))

data PackageIdentifier #

The name and version of a package.

Constructors

PackageIdentifier 

Fields

Instances
Eq PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Data PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageIdentifier -> c PackageIdentifier #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PackageIdentifier #

toConstr :: PackageIdentifier -> Constr #

dataTypeOf :: PackageIdentifier -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PackageIdentifier) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PackageIdentifier) #

gmapT :: (forall b. Data b => b -> b) -> PackageIdentifier -> PackageIdentifier #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageIdentifier -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageIdentifier -> r #

gmapQ :: (forall d. Data d => d -> u) -> PackageIdentifier -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageIdentifier -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageIdentifier -> m PackageIdentifier #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageIdentifier -> m PackageIdentifier #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageIdentifier -> m PackageIdentifier #

Ord PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Read PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Show PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Generic PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Associated Types

type Rep PackageIdentifier :: Type -> Type #

Package PackageIdentifier 
Instance details

Defined in Distribution.Package

Text PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Parsec PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Pretty PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

NFData PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Methods

rnf :: PackageIdentifier -> () #

Binary PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

type Rep PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

type Rep PackageIdentifier = D1 (MetaData "PackageIdentifier" "Distribution.Types.PackageId" "Cabal-2.4.0.1" False) (C1 (MetaCons "PackageIdentifier" PrefixI True) (S1 (MetaSel (Just "pkgName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PackageName) :*: S1 (MetaSel (Just "pkgVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version)))

data Version #

A Version represents the version of a software entity.

Instances of Eq and Ord are provided, which gives exact equality and lexicographic ordering of the version number components (i.e. 2.1 > 2.0, 1.2.3 > 1.2.2, etc.).

This type is opaque and distinct from the Version type in Data.Version since Cabal-2.0. The difference extends to the Binary instance using a different (and more compact) encoding.

Since: Cabal-2.0.0.2

Instances
Eq Version 
Instance details

Defined in Distribution.Types.Version

Methods

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

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

Data Version 
Instance details

Defined in Distribution.Types.Version

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Version -> c Version #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Version #

toConstr :: Version -> Constr #

dataTypeOf :: Version -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Version) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version) #

gmapT :: (forall b. Data b => b -> b) -> Version -> Version #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r #

gmapQ :: (forall d. Data d => d -> u) -> Version -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Version -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Version -> m Version #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version #

Ord Version 
Instance details

Defined in Distribution.Types.Version

Read Version 
Instance details

Defined in Distribution.Types.Version

Show Version 
Instance details

Defined in Distribution.Types.Version

Generic Version 
Instance details

Defined in Distribution.Types.Version

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Text Version 
Instance details

Defined in Distribution.Types.Version

Methods

disp :: Version -> Doc #

parse :: ReadP r Version #

Parsec Version 
Instance details

Defined in Distribution.Types.Version

Methods

parsec :: CabalParsing m => m Version #

Pretty Version 
Instance details

Defined in Distribution.Types.Version

Methods

pretty :: Version -> Doc #

NFData Version 
Instance details

Defined in Distribution.Types.Version

Methods

rnf :: Version -> () #

Binary Version 
Instance details

Defined in Distribution.Types.Version

Methods

put :: Version -> Put #

get :: Get Version #

putList :: [Version] -> Put #

type Rep Version 
Instance details

Defined in Distribution.Types.Version