simple-cabal-0.1.3.1: Cabal file wrapper library
Safe HaskellNone
LanguageHaskell2010

SimpleCabal

Synopsis

Documentation

findCabalFile :: IO FilePath Source #

Find the .cabal file in the current directory.

Errors if more than one or no file found.

Since: 0.0.0.1

readFinalPackageDescription :: [(FlagName, Bool)] -> FilePath -> IO PackageDescription Source #

get PackageDescription from a cabal file

deprecates finalPackageDescription

Since: 0.1.2

finalPackageDescription :: [(FlagName, Bool)] -> FilePath -> IO PackageDescription Source #

Generate PackageDescription from the specified .cabal file and flags.

deprecated in favour of readFinalPackageDescription

Since: 0.0.0.1

parseFinalPackageDescription :: [(FlagName, Bool)] -> ByteString -> IO (Maybe PackageDescription) Source #

only available with Cabal-2.2+

Since: 0.1.2

makeFinalPackageDescription :: [(FlagName, Bool)] -> GenericPackageDescription -> IO PackageDescription Source #

convert a GenericPackageDescription to a final PackageDescription

Since: 0.1.2

getPackageId :: IO PackageIdentifier Source #

Get the package name-version from the .cabal file in the current directory.

Since: 0.0.0.1

buildDepends :: PackageDescription -> [Dependency] Source #

List build dependencies

buildDependencies :: PackageDescription -> [PackageName] Source #

Return the list of build dependencies of a package, excluding itself

setupDependencies Source #

Arguments

:: PackageDescription

pkg description

-> [PackageName]

depends

List of setup dependencies

testsuiteDependencies :: PackageDescription -> [PackageName] Source #

Return the list of testsuite dependencies of a package, excluding itself

data BuildInfo #

Constructors

BuildInfo 

Fields

Instances

Instances details
Eq BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Methods

(==) :: BuildInfo -> BuildInfo -> Bool

(/=) :: BuildInfo -> BuildInfo -> Bool

Data BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Methods

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

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

toConstr :: BuildInfo -> Constr

dataTypeOf :: BuildInfo -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> BuildInfo -> BuildInfo

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

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

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

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

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

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

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

Read BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Methods

readsPrec :: Int -> ReadS BuildInfo

readList :: ReadS [BuildInfo]

readPrec :: ReadPrec BuildInfo

readListPrec :: ReadPrec [BuildInfo]

Show BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Methods

showsPrec :: Int -> BuildInfo -> ShowS

show :: BuildInfo -> String

showList :: [BuildInfo] -> ShowS

Generic BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Associated Types

type Rep BuildInfo :: Type -> Type

Methods

from :: BuildInfo -> Rep BuildInfo x

to :: Rep BuildInfo x -> BuildInfo

Semigroup BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Methods

(<>) :: BuildInfo -> BuildInfo -> BuildInfo

sconcat :: NonEmpty BuildInfo -> BuildInfo

stimes :: Integral b => b -> BuildInfo -> BuildInfo

Monoid BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Binary BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Methods

put :: BuildInfo -> Put

get :: Get BuildInfo

putList :: [BuildInfo] -> Put

NFData BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Methods

rnf :: BuildInfo -> ()

Structured BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

Methods

structure :: Proxy BuildInfo -> Structure

structureHash' :: Tagged BuildInfo MD5

FromBuildInfo BuildInfo 
Instance details

Defined in Distribution.PackageDescription.Parsec

Methods

fromBuildInfo' :: UnqualComponentName -> BuildInfo -> BuildInfo

type Rep BuildInfo 
Instance details

Defined in Distribution.Types.BuildInfo

type Rep BuildInfo = D1 ('MetaData "BuildInfo" "Distribution.Types.BuildInfo" "Cabal-3.2.1.0" 'False) (C1 ('MetaCons "BuildInfo" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "buildable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "buildTools") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [LegacyExeDependency])) :*: (S1 ('MetaSel ('Just "buildToolDepends") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ExeDependency]) :*: (S1 ('MetaSel ('Just "cppOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "asmOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))) :*: ((S1 ('MetaSel ('Just "cmmOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "ccOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :*: (S1 ('MetaSel ('Just "cxxOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "ldOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "pkgconfigDepends") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PkgconfigDependency]))))) :*: (((S1 ('MetaSel ('Just "frameworks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "extraFrameworkDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :*: (S1 ('MetaSel ('Just "asmSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: (S1 ('MetaSel ('Just "cmmSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: S1 ('MetaSel ('Just "cSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath])))) :*: ((S1 ('MetaSel ('Just "cxxSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: (S1 ('MetaSel ('Just "jsSources") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: S1 ('MetaSel ('Just "hsSourceDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]))) :*: (S1 ('MetaSel ('Just "otherModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName]) :*: (S1 ('MetaSel ('Just "virtualModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName]) :*: S1 ('MetaSel ('Just "autogenModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName])))))) :*: ((((S1 ('MetaSel ('Just "defaultLanguage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Language)) :*: S1 ('MetaSel ('Just "otherLanguages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Language])) :*: (S1 ('MetaSel ('Just "defaultExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Extension]) :*: (S1 ('MetaSel ('Just "otherExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Extension]) :*: S1 ('MetaSel ('Just "oldExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Extension])))) :*: ((S1 ('MetaSel ('Just "extraLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "extraGHCiLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "extraBundledLibs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :*: (S1 ('MetaSel ('Just "extraLibFlavours") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "extraDynLibFlavours") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "extraLibDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))))) :*: (((S1 ('MetaSel ('Just "includeDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: S1 ('MetaSel ('Just "includes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath])) :*: (S1 ('MetaSel ('Just "autogenIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: (S1 ('MetaSel ('Just "installIncludes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: S1 ('MetaSel ('Just "options") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCompilerFlavor [String]))))) :*: ((S1 ('MetaSel ('Just "profOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCompilerFlavor [String])) :*: (S1 ('MetaSel ('Just "sharedOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCompilerFlavor [String])) :*: S1 ('MetaSel ('Just "staticOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PerCompilerFlavor [String])))) :*: (S1 ('MetaSel ('Just "customFieldsBI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, String)]) :*: (S1 ('MetaSel ('Just "targetBuildDepends") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Dependency]) :*: S1 ('MetaSel ('Just "mixins") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Mixin]))))))))

data Library #

Constructors

Library 

Fields

Instances

Instances details
Eq Library 
Instance details

Defined in Distribution.Types.Library

Methods

(==) :: Library -> Library -> Bool

(/=) :: Library -> Library -> Bool

Data Library 
Instance details

Defined in Distribution.Types.Library

Methods

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

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

toConstr :: Library -> Constr

dataTypeOf :: Library -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> Library -> Library

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

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

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

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

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

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

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

Read Library 
Instance details

Defined in Distribution.Types.Library

Methods

readsPrec :: Int -> ReadS Library

readList :: ReadS [Library]

readPrec :: ReadPrec Library

readListPrec :: ReadPrec [Library]

Show Library 
Instance details

Defined in Distribution.Types.Library

Methods

showsPrec :: Int -> Library -> ShowS

show :: Library -> String

showList :: [Library] -> ShowS

Generic Library 
Instance details

Defined in Distribution.Types.Library

Associated Types

type Rep Library :: Type -> Type

Methods

from :: Library -> Rep Library x

to :: Rep Library x -> Library

Semigroup Library 
Instance details

Defined in Distribution.Types.Library

Methods

(<>) :: Library -> Library -> Library

sconcat :: NonEmpty Library -> Library

stimes :: Integral b => b -> Library -> Library

Monoid Library 
Instance details

Defined in Distribution.Types.Library

Binary Library 
Instance details

Defined in Distribution.Types.Library

Methods

put :: Library -> Put

get :: Get Library

putList :: [Library] -> Put

NFData Library 
Instance details

Defined in Distribution.Types.Library

Methods

rnf :: Library -> ()

Structured Library 
Instance details

Defined in Distribution.Types.Library

Methods

structure :: Proxy Library -> Structure

structureHash' :: Tagged Library MD5

HasBuildInfo Library 
Instance details

Defined in Distribution.Types.Library

Methods

buildInfo :: Lens' Library BuildInfo

buildable :: Lens' Library Bool

buildTools :: Lens' Library [LegacyExeDependency]

buildToolDepends :: Lens' Library [ExeDependency]

cppOptions :: Lens' Library [String]

asmOptions :: Lens' Library [String]

cmmOptions :: Lens' Library [String]

ccOptions :: Lens' Library [String]

cxxOptions :: Lens' Library [String]

ldOptions :: Lens' Library [String]

pkgconfigDepends :: Lens' Library [PkgconfigDependency]

frameworks :: Lens' Library [String]

extraFrameworkDirs :: Lens' Library [String]

asmSources :: Lens' Library [FilePath]

cmmSources :: Lens' Library [FilePath]

cSources :: Lens' Library [FilePath]

cxxSources :: Lens' Library [FilePath]

jsSources :: Lens' Library [FilePath]

hsSourceDirs :: Lens' Library [FilePath]

otherModules :: Lens' Library [ModuleName]

virtualModules :: Lens' Library [ModuleName]

autogenModules :: Lens' Library [ModuleName]

defaultLanguage :: Lens' Library (Maybe Language)

otherLanguages :: Lens' Library [Language]

defaultExtensions :: Lens' Library [Extension]

otherExtensions :: Lens' Library [Extension]

oldExtensions :: Lens' Library [Extension]

extraLibs :: Lens' Library [String]

extraGHCiLibs :: Lens' Library [String]

extraBundledLibs :: Lens' Library [String]

extraLibFlavours :: Lens' Library [String]

extraDynLibFlavours :: Lens' Library [String]

extraLibDirs :: Lens' Library [String]

includeDirs :: Lens' Library [FilePath]

includes :: Lens' Library [FilePath]

autogenIncludes :: Lens' Library [FilePath]

installIncludes :: Lens' Library [FilePath]

options :: Lens' Library (PerCompilerFlavor [String])

profOptions :: Lens' Library (PerCompilerFlavor [String])

sharedOptions :: Lens' Library (PerCompilerFlavor [String])

staticOptions :: Lens' Library (PerCompilerFlavor [String])

customFieldsBI :: Lens' Library [(String, String)]

targetBuildDepends :: Lens' Library [Dependency]

mixins :: Lens' Library [Mixin]

type Rep Library 
Instance details

Defined in Distribution.Types.Library

type Rep Library = D1 ('MetaData "Library" "Distribution.Types.Library" "Cabal-3.2.1.0" 'False) (C1 ('MetaCons "Library" 'PrefixI 'True) ((S1 ('MetaSel ('Just "libName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LibraryName) :*: (S1 ('MetaSel ('Just "exposedModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName]) :*: S1 ('MetaSel ('Just "reexportedModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleReexport]))) :*: ((S1 ('MetaSel ('Just "signatures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName]) :*: S1 ('MetaSel ('Just "libExposed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "libVisibility") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LibraryVisibility) :*: S1 ('MetaSel ('Just "libBuildInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuildInfo)))))

depPkgName :: Dependency -> PackageName #

exeDepName :: LegacyExeDependency -> String Source #

name of legacy exe dep

pkgcfgDepName :: PkgconfigDependency -> String Source #

pkgconfig dep name

data FlagName #

Instances

Instances details
Eq FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

(==) :: FlagName -> FlagName -> Bool

(/=) :: FlagName -> FlagName -> Bool

Data FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

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

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

toConstr :: FlagName -> Constr

dataTypeOf :: FlagName -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> FlagName -> FlagName

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

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

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

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

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

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

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

Ord FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

compare :: FlagName -> FlagName -> Ordering

(<) :: FlagName -> FlagName -> Bool

(<=) :: FlagName -> FlagName -> Bool

(>) :: FlagName -> FlagName -> Bool

(>=) :: FlagName -> FlagName -> Bool

max :: FlagName -> FlagName -> FlagName

min :: FlagName -> FlagName -> FlagName

Read FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

readsPrec :: Int -> ReadS FlagName

readList :: ReadS [FlagName]

readPrec :: ReadPrec FlagName

readListPrec :: ReadPrec [FlagName]

Show FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

showsPrec :: Int -> FlagName -> ShowS

show :: FlagName -> String

showList :: [FlagName] -> ShowS

IsString FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

fromString :: String -> FlagName

Generic FlagName 
Instance details

Defined in Distribution.Types.Flag

Associated Types

type Rep FlagName :: Type -> Type

Methods

from :: FlagName -> Rep FlagName x

to :: Rep FlagName x -> FlagName

Binary FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

put :: FlagName -> Put

get :: Get FlagName

putList :: [FlagName] -> Put

NFData FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

rnf :: FlagName -> ()

Parsec FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

parsec :: CabalParsing m => m FlagName

Pretty FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

pretty :: FlagName -> Doc

prettyVersioned :: CabalSpecVersion -> FlagName -> Doc

Structured FlagName 
Instance details

Defined in Distribution.Types.Flag

Methods

structure :: Proxy FlagName -> Structure

structureHash' :: Tagged FlagName MD5

type Rep FlagName 
Instance details

Defined in Distribution.Types.Flag

type Rep FlagName = D1 ('MetaData "FlagName" "Distribution.Types.Flag" "Cabal-3.2.1.0" 'True) (C1 ('MetaCons "FlagName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortText)))

mkFlagName :: String -> FlagName #

data PackageDescription #

Constructors

PackageDescription 

Fields

Instances

Instances details
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 :: forall r r'. (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

Methods

showsPrec :: Int -> PackageDescription -> ShowS

show :: PackageDescription -> String

showList :: [PackageDescription] -> ShowS

Generic PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Associated Types

type Rep PackageDescription :: Type -> Type

Binary PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

NFData PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Methods

rnf :: PackageDescription -> ()

Structured PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Methods

structure :: Proxy PackageDescription -> Structure

structureHash' :: Tagged PackageDescription MD5

Package PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

HasBuildInfos 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-3.2.1.0" '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 'SourceStrict 'DecidedUnpack) (Rec0 ShortText)) :*: (S1 ('MetaSel ('Just "maintainer") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "author") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText)))) :*: (((S1 ('MetaSel ('Just "stability") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "testedWith") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(CompilerFlavor, VersionRange)])) :*: (S1 ('MetaSel ('Just "homepage") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "pkgUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText))) :*: ((S1 ('MetaSel ('Just "bugReports") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "sourceRepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SourceRepo])) :*: (S1 ('MetaSel ('Just "synopsis") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "description") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText))))) :*: (((S1 ('MetaSel ('Just "category") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShortText) :*: (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 #

Constructors

PackageIdentifier 

Fields

Instances

Instances details
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 :: forall r r'. (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

Methods

showsPrec :: Int -> PackageIdentifier -> ShowS

show :: PackageIdentifier -> String

showList :: [PackageIdentifier] -> ShowS

Generic PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Associated Types

type Rep PackageIdentifier :: Type -> Type

Binary PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

NFData PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Methods

rnf :: PackageIdentifier -> ()

Parsec PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Methods

parsec :: CabalParsing m => m PackageIdentifier

Pretty PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Methods

pretty :: PackageIdentifier -> Doc

prettyVersioned :: CabalSpecVersion -> PackageIdentifier -> Doc

Structured PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Methods

structure :: Proxy PackageIdentifier -> Structure

structureHash' :: Tagged PackageIdentifier MD5

Package PackageIdentifier 
Instance details

Defined in Distribution.Package

type Rep PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

type Rep PackageIdentifier = D1 ('MetaData "PackageIdentifier" "Distribution.Types.PackageId" "Cabal-3.2.1.0" '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 PackageName #

Instances

Instances details
Eq PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

(==) :: PackageName -> PackageName -> Bool

(/=) :: PackageName -> PackageName -> Bool

Data PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

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

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

toConstr :: PackageName -> Constr

dataTypeOf :: PackageName -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> PackageName -> PackageName

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

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

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

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

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

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

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

Ord PackageName 
Instance details

Defined in Distribution.Types.PackageName

Read PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

readsPrec :: Int -> ReadS PackageName

readList :: ReadS [PackageName]

readPrec :: ReadPrec PackageName

readListPrec :: ReadPrec [PackageName]

Show PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

showsPrec :: Int -> PackageName -> ShowS

show :: PackageName -> String

showList :: [PackageName] -> ShowS

IsString PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

fromString :: String -> PackageName

Generic PackageName 
Instance details

Defined in Distribution.Types.PackageName

Associated Types

type Rep PackageName :: Type -> Type

Methods

from :: PackageName -> Rep PackageName x

to :: Rep PackageName x -> PackageName

Binary PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

put :: PackageName -> Put

get :: Get PackageName

putList :: [PackageName] -> Put

NFData PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

rnf :: PackageName -> ()

Parsec PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

parsec :: CabalParsing m => m PackageName

Pretty PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

pretty :: PackageName -> Doc

prettyVersioned :: CabalSpecVersion -> PackageName -> Doc

Structured PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

structure :: Proxy PackageName -> Structure

structureHash' :: Tagged PackageName MD5

type Rep PackageName 
Instance details

Defined in Distribution.Types.PackageName

type Rep PackageName = D1 ('MetaData "PackageName" "Distribution.Types.PackageName" "Cabal-3.2.1.0" 'True) (C1 ('MetaCons "PackageName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortText)))

packageName :: Package pkg => pkg -> PackageName #

packageVersion :: PackageIdentifier -> String Source #

version string from PackageIdentifier

readGenericPackageDescription :: Verbosity -> FilePath -> IO GenericPackageDescription #

showPkgId :: PackageIdentifier -> String Source #

convert PackageIdentifier to a displayable string

showVersion :: Version -> String Source #

render a Version

simpleParse :: Parsec a => String -> Maybe a #

tryFindPackageDesc :: FilePath -> IO FilePath Source #

Find cabal file