cabal-file-th-0.2.4: 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 
Data 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 
Show PackageDescription 
Generic PackageDescription 
Binary PackageDescription 
Package PackageDescription 
type Rep PackageDescription 
type Rep PackageDescription = D1 (MetaData "PackageDescription" "Distribution.PackageDescription" "Cabal-1.24.0.0" False) (C1 (MetaCons "PackageDescription" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "package") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PackageIdentifier)) ((:*:) (S1 (MetaSel (Just Symbol "license") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 License)) (S1 (MetaSel (Just Symbol "licenseFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath])))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "copyright") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "maintainer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) ((:*:) (S1 (MetaSel (Just Symbol "author") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "stability") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "testedWith") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(CompilerFlavor, VersionRange)])) ((:*:) (S1 (MetaSel (Just Symbol "homepage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "pkgUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "bugReports") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "sourceRepos") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SourceRepo]))) ((:*:) (S1 (MetaSel (Just Symbol "synopsis") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "description") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "category") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) ((:*:) (S1 (MetaSel (Just Symbol "customFieldsPD") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, String)])) (S1 (MetaSel (Just Symbol "buildDepends") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Dependency])))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "specVersionRaw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either Version VersionRange))) (S1 (MetaSel (Just Symbol "buildType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe BuildType)))) ((:*:) (S1 (MetaSel (Just Symbol "setupBuildInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SetupBuildInfo))) (S1 (MetaSel (Just Symbol "library") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Library)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "executables") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Executable])) (S1 (MetaSel (Just Symbol "testSuites") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TestSuite]))) ((:*:) (S1 (MetaSel (Just Symbol "benchmarks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Benchmark])) (S1 (MetaSel (Just Symbol "dataFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath])))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dataDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)) (S1 (MetaSel (Just Symbol "extraSrcFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]))) ((:*:) (S1 (MetaSel (Just Symbol "extraTmpFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath])) (S1 (MetaSel (Just Symbol "extraDocFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]))))))))

data PackageIdentifier :: * #

The name and version of a package.

Constructors

PackageIdentifier 

Fields

Instances

Eq PackageIdentifier 
Data PackageIdentifier 

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 
Read PackageIdentifier 
Show PackageIdentifier 
Generic PackageIdentifier 
Binary PackageIdentifier 
Package PackageIdentifier 
Text PackageIdentifier 
NFData PackageIdentifier 

Methods

rnf :: PackageIdentifier -> () #

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

data Version :: * #

A Version represents the version of a software entity.

An instance of Eq is provided, which implements exact equality modulo reordering of the tags in the versionTags field.

An instance of Ord is also provided, which gives lexicographic ordering on the versionBranch fields (i.e. 2.1 > 2.0, 1.2.3 > 1.2.2, etc.). This is expected to be sufficient for many uses, but note that you may need to use a more specific ordering for your versioning scheme. For example, some versioning schemes may include pre-releases which have tags "pre1", "pre2", and so on, and these would need to be taken into account when determining ordering. In some cases, date ordering may be more appropriate, so the application would have to look for date tags in the versionTags field and compare those. The bottom line is, don't always assume that compare and other Ord operations are the right thing for every Version.

Similarly, concrete representations of versions may differ. One possible concrete representation is provided (see showVersion and parseVersion), but depending on the application a different concrete representation may be more appropriate.

Constructors

Version 

Fields

  • versionBranch :: [Int]

    The numeric branch for this version. This reflects the fact that most software versions are tree-structured; there is a main trunk which is tagged with versions at various points (1,2,3...), and the first branch off the trunk after version 3 is 3.1, the second branch off the trunk after version 3 is 3.2, and so on. The tree can be branched arbitrarily, just by adding more digits.

    We represent the branch as a list of Int, so version 3.2.1 becomes [3,2,1]. Lexicographic ordering (i.e. the default instance of Ord for [Int]) gives the natural ordering of branches.

  • versionTags :: [String]

    A version can be tagged with an arbitrary list of strings. The interpretation of the list of tags is entirely dependent on the entity that this version applies to.