Cabal
CopyrightIsaac Jones 2003-2005
LicenseBSD3
Maintainercabal-devel@haskell.org
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Distribution.Simple

Description

This is the command line front end to the Simple build system. When given the parsed command-line args and package information, is able to perform basic commands like configure, build, install, register, etc.

This module exports the main functions that Setup.hs scripts use. It re-exports the UserHooks type, the standard entry points like defaultMain and defaultMainWithHooks and the predefined sets of UserHooks that custom Setup.hs scripts can extend to add their own behaviour.

This module isn't called "Simple" because it's simple. Far from it. It's called "Simple" because it does complicated things to simple software.

The original idea was that there could be different build systems that all presented the same compatible command line interfaces. There is still a Distribution.Make system but in practice no packages use it.

Synopsis

Documentation

data Module #

Constructors

Module DefUnitId ModuleName 

Instances

Instances details
Parsec Module 
Instance details

Defined in Distribution.Types.Module

Methods

parsec :: CabalParsing m => m Module

Pretty Module 
Instance details

Defined in Distribution.Types.Module

Methods

pretty :: Module -> Doc

prettyVersioned :: CabalSpecVersion -> Module -> Doc

Structured Module 
Instance details

Defined in Distribution.Types.Module

Methods

structure :: Proxy Module -> Structure

structureHash' :: Tagged Module MD5

Binary Module 
Instance details

Defined in Distribution.Types.Module

Methods

put :: Module -> Put #

get :: Get Module #

putList :: [Module] -> Put #

NFData Module 
Instance details

Defined in Distribution.Types.Module

Methods

rnf :: Module -> () #

Data Module 
Instance details

Defined in Distribution.Types.Module

Methods

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

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

toConstr :: Module -> Constr #

dataTypeOf :: Module -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Module 
Instance details

Defined in Distribution.Types.Module

Associated Types

type Rep Module 
Instance details

Defined in Distribution.Types.Module

type Rep Module = D1 ('MetaData "Module" "Distribution.Types.Module" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "Module" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DefUnitId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModuleName)))

Methods

from :: Module -> Rep Module x #

to :: Rep Module x -> Module #

Read Module 
Instance details

Defined in Distribution.Types.Module

Show Module 
Instance details

Defined in Distribution.Types.Module

Eq Module 
Instance details

Defined in Distribution.Types.Module

Methods

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

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

Ord Module 
Instance details

Defined in Distribution.Types.Module

type Rep Module 
Instance details

Defined in Distribution.Types.Module

type Rep Module = D1 ('MetaData "Module" "Distribution.Types.Module" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "Module" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DefUnitId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModuleName)))

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

class Package pkg where #

Methods

packageId :: pkg -> PackageIdentifier #

Instances

Instances details
Package LinkedComponent Source # 
Instance details

Defined in Distribution.Backpack.LinkedComponent

Package GenericPackageDescription 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Methods

packageId :: GenericPackageDescription -> PackageIdentifier #

Package InstalledPackageInfo 
Instance details

Defined in Distribution.Types.InstalledPackageInfo

Methods

packageId :: InstalledPackageInfo -> PackageIdentifier #

Package PackageDescription 
Instance details

Defined in Distribution.Types.PackageDescription

Methods

packageId :: PackageDescription -> PackageIdentifier #

Package PackageIdentifier 
Instance details

Defined in Distribution.Package

Package (AnnotatedId id) Source # 
Instance details

Defined in Distribution.Types.AnnotatedId

data ComponentId #

Instances

Instances details
Parsec ComponentId 
Instance details

Defined in Distribution.Types.ComponentId

Methods

parsec :: CabalParsing m => m ComponentId

Pretty ComponentId 
Instance details

Defined in Distribution.Types.ComponentId

Methods

pretty :: ComponentId -> Doc

prettyVersioned :: CabalSpecVersion -> ComponentId -> Doc

Structured ComponentId 
Instance details

Defined in Distribution.Types.ComponentId

Methods

structure :: Proxy ComponentId -> Structure

structureHash' :: Tagged ComponentId MD5

Binary ComponentId 
Instance details

Defined in Distribution.Types.ComponentId

NFData ComponentId 
Instance details

Defined in Distribution.Types.ComponentId

Methods

rnf :: ComponentId -> () #

Data ComponentId 
Instance details

Defined in Distribution.Types.ComponentId

Methods

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

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

toConstr :: ComponentId -> Constr #

dataTypeOf :: ComponentId -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString ComponentId 
Instance details

Defined in Distribution.Types.ComponentId

Generic ComponentId 
Instance details

Defined in Distribution.Types.ComponentId

Associated Types

type Rep ComponentId 
Instance details

Defined in Distribution.Types.ComponentId

type Rep ComponentId = D1 ('MetaData "ComponentId" "Distribution.Types.ComponentId" "Cabal-syntax-3.16.0.0-inplace" 'True) (C1 ('MetaCons "ComponentId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortText)))
Read ComponentId 
Instance details

Defined in Distribution.Types.ComponentId

Show ComponentId 
Instance details

Defined in Distribution.Types.ComponentId

Eq ComponentId 
Instance details

Defined in Distribution.Types.ComponentId

Ord ComponentId 
Instance details

Defined in Distribution.Types.ComponentId

type Rep ComponentId 
Instance details

Defined in Distribution.Types.ComponentId

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

data Dependency #

Instances

Instances details
Parsec Dependency 
Instance details

Defined in Distribution.Types.Dependency

Methods

parsec :: CabalParsing m => m Dependency

Pretty Dependency 
Instance details

Defined in Distribution.Types.Dependency

Methods

pretty :: Dependency -> Doc

prettyVersioned :: CabalSpecVersion -> Dependency -> Doc

Structured Dependency 
Instance details

Defined in Distribution.Types.Dependency

Methods

structure :: Proxy Dependency -> Structure

structureHash' :: Tagged Dependency MD5

Binary Dependency 
Instance details

Defined in Distribution.Types.Dependency

NFData Dependency 
Instance details

Defined in Distribution.Types.Dependency

Methods

rnf :: Dependency -> () #

Data Dependency 
Instance details

Defined in Distribution.Types.Dependency

Methods

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

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

toConstr :: Dependency -> Constr #

dataTypeOf :: Dependency -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Dependency 
Instance details

Defined in Distribution.Types.Dependency

Read Dependency 
Instance details

Defined in Distribution.Types.Dependency

Show Dependency 
Instance details

Defined in Distribution.Types.Dependency

Eq Dependency 
Instance details

Defined in Distribution.Types.Dependency

Ord Dependency 
Instance details

Defined in Distribution.Types.Dependency

type Rep Dependency 
Instance details

Defined in Distribution.Types.Dependency

data UnitId #

Instances

Instances details
Parsec UnitId 
Instance details

Defined in Distribution.Types.UnitId

Methods

parsec :: CabalParsing m => m UnitId

Pretty UnitId 
Instance details

Defined in Distribution.Types.UnitId

Methods

pretty :: UnitId -> Doc

prettyVersioned :: CabalSpecVersion -> UnitId -> Doc

Structured UnitId 
Instance details

Defined in Distribution.Types.UnitId

Methods

structure :: Proxy UnitId -> Structure

structureHash' :: Tagged UnitId MD5

Binary UnitId 
Instance details

Defined in Distribution.Types.UnitId

Methods

put :: UnitId -> Put #

get :: Get UnitId #

putList :: [UnitId] -> Put #

NFData UnitId 
Instance details

Defined in Distribution.Types.UnitId

Methods

rnf :: UnitId -> () #

Data UnitId 
Instance details

Defined in Distribution.Types.UnitId

Methods

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

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

toConstr :: UnitId -> Constr #

dataTypeOf :: UnitId -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString UnitId 
Instance details

Defined in Distribution.Types.UnitId

Methods

fromString :: String -> UnitId #

Generic UnitId 
Instance details

Defined in Distribution.Types.UnitId

Associated Types

type Rep UnitId 
Instance details

Defined in Distribution.Types.UnitId

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

Methods

from :: UnitId -> Rep UnitId x #

to :: Rep UnitId x -> UnitId #

Read UnitId 
Instance details

Defined in Distribution.Types.UnitId

Show UnitId 
Instance details

Defined in Distribution.Types.UnitId

Eq UnitId 
Instance details

Defined in Distribution.Types.UnitId

Methods

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

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

Ord UnitId 
Instance details

Defined in Distribution.Types.UnitId

type Rep UnitId 
Instance details

Defined in Distribution.Types.UnitId

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

class Package pkg => HasUnitId pkg where #

Methods

installedUnitId :: pkg -> UnitId #

Instances

Instances details
HasUnitId InstalledPackageInfo 
Instance details

Defined in Distribution.Types.InstalledPackageInfo

Methods

installedUnitId :: InstalledPackageInfo -> UnitId #

data PackageName #

Instances

Instances details
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

Binary PackageName 
Instance details

Defined in Distribution.Types.PackageName

NFData PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

rnf :: PackageName -> () #

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 #

IsString PackageName 
Instance details

Defined in Distribution.Types.PackageName

Generic PackageName 
Instance details

Defined in Distribution.Types.PackageName

Associated Types

type Rep PackageName 
Instance details

Defined in Distribution.Types.PackageName

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

Defined in Distribution.Types.PackageName

Show PackageName 
Instance details

Defined in Distribution.Types.PackageName

Eq PackageName 
Instance details

Defined in Distribution.Types.PackageName

Ord PackageName 
Instance details

Defined in Distribution.Types.PackageName

type Rep PackageName 
Instance details

Defined in Distribution.Types.PackageName

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

data PackageIdentifier #

Instances

Instances details
Package PackageIdentifier 
Instance details

Defined in Distribution.Package

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

Binary PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

NFData PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Methods

rnf :: PackageIdentifier -> () #

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 #

Generic PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Associated Types

type Rep PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

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

Defined in Distribution.Types.PackageId

Show PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Eq PackageIdentifier 
Instance details

Defined in Distribution.Types.PackageId

Ord 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-syntax-3.16.0.0-inplace" '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 DefUnitId #

Instances

Instances details
Parsec DefUnitId 
Instance details

Defined in Distribution.Types.UnitId

Methods

parsec :: CabalParsing m => m DefUnitId

Pretty DefUnitId 
Instance details

Defined in Distribution.Types.UnitId

Methods

pretty :: DefUnitId -> Doc

prettyVersioned :: CabalSpecVersion -> DefUnitId -> Doc

Structured DefUnitId 
Instance details

Defined in Distribution.Types.UnitId

Methods

structure :: Proxy DefUnitId -> Structure

structureHash' :: Tagged DefUnitId MD5

Binary DefUnitId 
Instance details

Defined in Distribution.Types.UnitId

NFData DefUnitId 
Instance details

Defined in Distribution.Types.UnitId

Methods

rnf :: DefUnitId -> () #

Data DefUnitId 
Instance details

Defined in Distribution.Types.UnitId

Methods

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

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

toConstr :: DefUnitId -> Constr #

dataTypeOf :: DefUnitId -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic DefUnitId 
Instance details

Defined in Distribution.Types.UnitId

Associated Types

type Rep DefUnitId 
Instance details

Defined in Distribution.Types.UnitId

type Rep DefUnitId = D1 ('MetaData "DefUnitId" "Distribution.Types.UnitId" "Cabal-syntax-3.16.0.0-inplace" 'True) (C1 ('MetaCons "DefUnitId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unDefUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId)))
Read DefUnitId 
Instance details

Defined in Distribution.Types.UnitId

Show DefUnitId 
Instance details

Defined in Distribution.Types.UnitId

Eq DefUnitId 
Instance details

Defined in Distribution.Types.UnitId

Ord DefUnitId 
Instance details

Defined in Distribution.Types.UnitId

type Rep DefUnitId 
Instance details

Defined in Distribution.Types.UnitId

type Rep DefUnitId = D1 ('MetaData "DefUnitId" "Distribution.Types.UnitId" "Cabal-syntax-3.16.0.0-inplace" 'True) (C1 ('MetaCons "DefUnitId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unDefUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId)))

mkPackageNameST :: ShortText -> PackageName #

unPackageNameST :: PackageName -> ShortText #

class HasMungedPackageId pkg where #

Methods

mungedId :: pkg -> MungedPackageId #

Instances

Instances details
HasMungedPackageId InstalledPackageInfo 
Instance details

Defined in Distribution.Types.InstalledPackageInfo

Methods

mungedId :: InstalledPackageInfo -> MungedPackageId #

HasMungedPackageId MungedPackageId 
Instance details

Defined in Distribution.Package

Methods

mungedId :: MungedPackageId -> MungedPackageId #

class HasUnitId pkg => PackageInstalled pkg where #

Methods

installedDepends :: pkg -> [UnitId] #

Instances

Instances details
PackageInstalled InstalledPackageInfo 
Instance details

Defined in Distribution.Types.InstalledPackageInfo

Methods

installedDepends :: InstalledPackageInfo -> [UnitId] #

packageVersion :: Package pkg => pkg -> Version #

data AbiHash #

Instances

Instances details
Parsec AbiHash 
Instance details

Defined in Distribution.Types.AbiHash

Methods

parsec :: CabalParsing m => m AbiHash

Pretty AbiHash 
Instance details

Defined in Distribution.Types.AbiHash

Methods

pretty :: AbiHash -> Doc

prettyVersioned :: CabalSpecVersion -> AbiHash -> Doc

Structured AbiHash 
Instance details

Defined in Distribution.Types.AbiHash

Methods

structure :: Proxy AbiHash -> Structure

structureHash' :: Tagged AbiHash MD5

Binary AbiHash 
Instance details

Defined in Distribution.Types.AbiHash

Methods

put :: AbiHash -> Put #

get :: Get AbiHash #

putList :: [AbiHash] -> Put #

NFData AbiHash 
Instance details

Defined in Distribution.Types.AbiHash

Methods

rnf :: AbiHash -> () #

IsString AbiHash 
Instance details

Defined in Distribution.Types.AbiHash

Methods

fromString :: String -> AbiHash #

Generic AbiHash 
Instance details

Defined in Distribution.Types.AbiHash

Associated Types

type Rep AbiHash 
Instance details

Defined in Distribution.Types.AbiHash

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

Methods

from :: AbiHash -> Rep AbiHash x #

to :: Rep AbiHash x -> AbiHash #

Read AbiHash 
Instance details

Defined in Distribution.Types.AbiHash

Show AbiHash 
Instance details

Defined in Distribution.Types.AbiHash

Eq AbiHash 
Instance details

Defined in Distribution.Types.AbiHash

Methods

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

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

type Rep AbiHash 
Instance details

Defined in Distribution.Types.AbiHash

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

data PkgconfigName #

Instances

Instances details
Parsec PkgconfigName 
Instance details

Defined in Distribution.Types.PkgconfigName

Methods

parsec :: CabalParsing m => m PkgconfigName

Pretty PkgconfigName 
Instance details

Defined in Distribution.Types.PkgconfigName

Methods

pretty :: PkgconfigName -> Doc

prettyVersioned :: CabalSpecVersion -> PkgconfigName -> Doc

Structured PkgconfigName 
Instance details

Defined in Distribution.Types.PkgconfigName

Methods

structure :: Proxy PkgconfigName -> Structure

structureHash' :: Tagged PkgconfigName MD5

Binary PkgconfigName 
Instance details

Defined in Distribution.Types.PkgconfigName

NFData PkgconfigName 
Instance details

Defined in Distribution.Types.PkgconfigName

Methods

rnf :: PkgconfigName -> () #

Data PkgconfigName 
Instance details

Defined in Distribution.Types.PkgconfigName

Methods

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

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

toConstr :: PkgconfigName -> Constr #

dataTypeOf :: PkgconfigName -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString PkgconfigName 
Instance details

Defined in Distribution.Types.PkgconfigName

Generic PkgconfigName 
Instance details

Defined in Distribution.Types.PkgconfigName

Associated Types

type Rep PkgconfigName 
Instance details

Defined in Distribution.Types.PkgconfigName

type Rep PkgconfigName = D1 ('MetaData "PkgconfigName" "Distribution.Types.PkgconfigName" "Cabal-syntax-3.16.0.0-inplace" 'True) (C1 ('MetaCons "PkgconfigName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortText)))
Read PkgconfigName 
Instance details

Defined in Distribution.Types.PkgconfigName

Show PkgconfigName 
Instance details

Defined in Distribution.Types.PkgconfigName

Eq PkgconfigName 
Instance details

Defined in Distribution.Types.PkgconfigName

Ord PkgconfigName 
Instance details

Defined in Distribution.Types.PkgconfigName

type Rep PkgconfigName 
Instance details

Defined in Distribution.Types.PkgconfigName

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

mungedName' :: HasMungedPackageId pkg => pkg -> MungedPackageName #

data Version #

Instances

Instances details
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

prettyVersioned :: CabalSpecVersion -> Version -> Doc

Structured Version 
Instance details

Defined in Distribution.Types.Version

Methods

structure :: Proxy Version -> Structure

structureHash' :: Tagged Version MD5

Binary Version 
Instance details

Defined in Distribution.Types.Version

Methods

put :: Version -> Put #

get :: Get Version #

putList :: [Version] -> Put #

NFData Version 
Instance details

Defined in Distribution.Types.Version

Methods

rnf :: Version -> () #

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

Generic Version 
Instance details

Defined in Distribution.Types.Version

Associated Types

type Rep Version 
Instance details

Defined in Distribution.Types.Version

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Read Version 
Instance details

Defined in Distribution.Types.Version

Show Version 
Instance details

Defined in Distribution.Types.Version

Eq Version 
Instance details

Defined in Distribution.Types.Version

Methods

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

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

Ord Version 
Instance details

Defined in Distribution.Types.Version

type Rep Version 
Instance details

Defined in Distribution.Types.Version

alterVersion :: ([Int] -> [Int]) -> Version -> Version #

data VersionRangeF a #

Bundled Patterns

pattern GTLowerBound :: VersionRangeF a 
pattern LEUpperBound :: VersionRangeF a 
pattern TZUpperBound :: VersionRangeF a 

Instances

Instances details
Functor VersionRangeF 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Methods

fmap :: (a -> b) -> VersionRangeF a -> VersionRangeF b #

(<$) :: a -> VersionRangeF b -> VersionRangeF a #

Foldable VersionRangeF 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Methods

fold :: Monoid m => VersionRangeF m -> m #

foldMap :: Monoid m => (a -> m) -> VersionRangeF a -> m #

foldMap' :: Monoid m => (a -> m) -> VersionRangeF a -> m #

foldr :: (a -> b -> b) -> b -> VersionRangeF a -> b #

foldr' :: (a -> b -> b) -> b -> VersionRangeF a -> b #

foldl :: (b -> a -> b) -> b -> VersionRangeF a -> b #

foldl' :: (b -> a -> b) -> b -> VersionRangeF a -> b #

foldr1 :: (a -> a -> a) -> VersionRangeF a -> a #

foldl1 :: (a -> a -> a) -> VersionRangeF a -> a #

toList :: VersionRangeF a -> [a] #

null :: VersionRangeF a -> Bool #

length :: VersionRangeF a -> Int #

elem :: Eq a => a -> VersionRangeF a -> Bool #

maximum :: Ord a => VersionRangeF a -> a #

minimum :: Ord a => VersionRangeF a -> a #

sum :: Num a => VersionRangeF a -> a #

product :: Num a => VersionRangeF a -> a #

Traversable VersionRangeF 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Methods

traverse :: Applicative f => (a -> f b) -> VersionRangeF a -> f (VersionRangeF b) #

sequenceA :: Applicative f => VersionRangeF (f a) -> f (VersionRangeF a) #

mapM :: Monad m => (a -> m b) -> VersionRangeF a -> m (VersionRangeF b) #

sequence :: Monad m => VersionRangeF (m a) -> m (VersionRangeF a) #

Data a => Data (VersionRangeF a) 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Methods

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

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

toConstr :: VersionRangeF a -> Constr #

dataTypeOf :: VersionRangeF a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (VersionRangeF a) 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Associated Types

type Rep (VersionRangeF a) 
Instance details

Defined in Distribution.Types.VersionRange.Internal

type Rep (VersionRangeF a) = D1 ('MetaData "VersionRangeF" "Distribution.Types.VersionRange.Internal" "Cabal-syntax-3.16.0.0-inplace" 'False) (((C1 ('MetaCons "ThisVersionF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "LaterVersionF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) :+: (C1 ('MetaCons "OrLaterVersionF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "EarlierVersionF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)))) :+: ((C1 ('MetaCons "OrEarlierVersionF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "MajorBoundVersionF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) :+: (C1 ('MetaCons "UnionVersionRangesF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "IntersectVersionRangesF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))))
Read a => Read (VersionRangeF a) 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Show a => Show (VersionRangeF a) 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Eq a => Eq (VersionRangeF a) 
Instance details

Defined in Distribution.Types.VersionRange.Internal

type Rep (VersionRangeF a) 
Instance details

Defined in Distribution.Types.VersionRange.Internal

type Rep (VersionRangeF a) = D1 ('MetaData "VersionRangeF" "Distribution.Types.VersionRange.Internal" "Cabal-syntax-3.16.0.0-inplace" 'False) (((C1 ('MetaCons "ThisVersionF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "LaterVersionF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) :+: (C1 ('MetaCons "OrLaterVersionF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "EarlierVersionF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)))) :+: ((C1 ('MetaCons "OrEarlierVersionF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "MajorBoundVersionF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) :+: (C1 ('MetaCons "UnionVersionRangesF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "IntersectVersionRangesF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))))

data VersionRange #

Instances

Instances details
Parsec VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Methods

parsec :: CabalParsing m => m VersionRange

Pretty VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Methods

pretty :: VersionRange -> Doc

prettyVersioned :: CabalSpecVersion -> VersionRange -> Doc

Structured VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Methods

structure :: Proxy VersionRange -> Structure

structureHash' :: Tagged VersionRange MD5

Binary VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

NFData VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Methods

rnf :: VersionRange -> () #

Data VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Methods

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

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

toConstr :: VersionRange -> Constr #

dataTypeOf :: VersionRange -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Associated Types

type Rep VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

type Rep VersionRange = D1 ('MetaData "VersionRange" "Distribution.Types.VersionRange.Internal" "Cabal-syntax-3.16.0.0-inplace" 'False) (((C1 ('MetaCons "ThisVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "LaterVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) :+: (C1 ('MetaCons "OrLaterVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "EarlierVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)))) :+: ((C1 ('MetaCons "OrEarlierVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "MajorBoundVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) :+: (C1 ('MetaCons "UnionVersionRanges" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionRange) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionRange)) :+: C1 ('MetaCons "IntersectVersionRanges" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionRange) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionRange)))))
Read VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Show VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Eq VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Ord VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

Newtype (CompilerFlavor, VersionRange) TestedWith 
Instance details

Defined in Distribution.FieldGrammar.Newtypes

Methods

pack :: (CompilerFlavor, VersionRange) -> TestedWith

unpack :: TestedWith -> (CompilerFlavor, VersionRange)

type Rep VersionRange 
Instance details

Defined in Distribution.Types.VersionRange.Internal

type Rep VersionRange = D1 ('MetaData "VersionRange" "Distribution.Types.VersionRange.Internal" "Cabal-syntax-3.16.0.0-inplace" 'False) (((C1 ('MetaCons "ThisVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "LaterVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) :+: (C1 ('MetaCons "OrLaterVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "EarlierVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)))) :+: ((C1 ('MetaCons "OrEarlierVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "MajorBoundVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) :+: (C1 ('MetaCons "UnionVersionRanges" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionRange) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionRange)) :+: C1 ('MetaCons "IntersectVersionRanges" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionRange) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VersionRange)))))

data Bound #

Instances

Instances details
Show Bound 
Instance details

Defined in Distribution.Types.VersionInterval

Methods

showsPrec :: Int -> Bound -> ShowS #

show :: Bound -> String #

showList :: [Bound] -> ShowS #

Eq Bound 
Instance details

Defined in Distribution.Types.VersionInterval

Methods

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

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

data LowerBound #

Constructors

LowerBound !Version !Bound 

Instances

Instances details
Show LowerBound 
Instance details

Defined in Distribution.Types.VersionInterval

Eq LowerBound 
Instance details

Defined in Distribution.Types.VersionInterval

data UpperBound #

Instances

Instances details
Show UpperBound 
Instance details

Defined in Distribution.Types.VersionInterval

Eq UpperBound 
Instance details

Defined in Distribution.Types.VersionInterval

foldVersionRange :: a -> (Version -> a) -> (Version -> a) -> (Version -> a) -> (a -> a -> a) -> (a -> a -> a) -> VersionRange -> a #

data License #

Instances

Instances details
Parsec License 
Instance details

Defined in Distribution.License

Methods

parsec :: CabalParsing m => m License

Pretty License 
Instance details

Defined in Distribution.License

Methods

pretty :: License -> Doc

prettyVersioned :: CabalSpecVersion -> License -> Doc

Structured License 
Instance details

Defined in Distribution.License

Methods

structure :: Proxy License -> Structure

structureHash' :: Tagged License MD5

Binary License 
Instance details

Defined in Distribution.License

Methods

put :: License -> Put #

get :: Get License #

putList :: [License] -> Put #

NFData License 
Instance details

Defined in Distribution.License

Methods

rnf :: License -> () #

Data License 
Instance details

Defined in Distribution.License

Methods

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

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

toConstr :: License -> Constr #

dataTypeOf :: License -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic License 
Instance details

Defined in Distribution.License

Associated Types

type Rep License 
Instance details

Defined in Distribution.License

type Rep License = D1 ('MetaData "License" "Distribution.License" "Cabal-syntax-3.16.0.0-inplace" 'False) (((C1 ('MetaCons "GPL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version))) :+: (C1 ('MetaCons "AGPL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version))) :+: C1 ('MetaCons "LGPL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version))))) :+: ((C1 ('MetaCons "BSD2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BSD3" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BSD4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MIT" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "ISC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MPL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) :+: (C1 ('MetaCons "Apache" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version))) :+: C1 ('MetaCons "PublicDomain" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "AllRightsReserved" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnspecifiedLicense" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OtherLicense" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnknownLicense" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))

Methods

from :: License -> Rep License x #

to :: Rep License x -> License #

Read License 
Instance details

Defined in Distribution.License

Show License 
Instance details

Defined in Distribution.License

Eq License 
Instance details

Defined in Distribution.License

Methods

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

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

Ord License 
Instance details

Defined in Distribution.License

Newtype (Either License License) SpecLicense 
Instance details

Defined in Distribution.FieldGrammar.Newtypes

Methods

pack :: Either License License -> SpecLicense

unpack :: SpecLicense -> Either License License

Newtype (Either License License) SpecLicenseLenient 
Instance details

Defined in Distribution.Types.InstalledPackageInfo.FieldGrammar

Methods

pack :: Either License License -> SpecLicenseLenient

unpack :: SpecLicenseLenient -> Either License License

type Rep License 
Instance details

Defined in Distribution.License

type Rep License = D1 ('MetaData "License" "Distribution.License" "Cabal-syntax-3.16.0.0-inplace" 'False) (((C1 ('MetaCons "GPL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version))) :+: (C1 ('MetaCons "AGPL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version))) :+: C1 ('MetaCons "LGPL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version))))) :+: ((C1 ('MetaCons "BSD2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BSD3" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BSD4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MIT" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "ISC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MPL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) :+: (C1 ('MetaCons "Apache" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Version))) :+: C1 ('MetaCons "PublicDomain" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "AllRightsReserved" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnspecifiedLicense" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OtherLicense" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnknownLicense" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))

licenseFromSPDX :: License -> License #

licenseToSPDX :: License -> License #

data KnownExtension #

Constructors

OverlappingInstances 
UndecidableInstances 
IncoherentInstances 
DoRec 
RecursiveDo 
ParallelListComp 
MultiParamTypeClasses 
MonomorphismRestriction 
DeepSubsumption 
FunctionalDependencies 
Rank2Types 
RankNTypes 
PolymorphicComponents 
ExistentialQuantification 
ScopedTypeVariables 
PatternSignatures 
ImplicitParams 
FlexibleContexts 
FlexibleInstances 
EmptyDataDecls 
CPP 
KindSignatures 
BangPatterns 
TypeSynonymInstances 
TemplateHaskell 
ForeignFunctionInterface 
Arrows 
Generics 
ImplicitPrelude 
NamedFieldPuns 
PatternGuards 
GeneralizedNewtypeDeriving 
GeneralisedNewtypeDeriving 
ExtensibleRecords 
RestrictedTypeSynonyms 
HereDocuments 
MagicHash 
TypeFamilies 
StandaloneDeriving 
UnicodeSyntax 
UnliftedFFITypes 
InterruptibleFFI 
CApiFFI 
LiberalTypeSynonyms 
TypeOperators 
RecordWildCards 
RecordPuns 
DisambiguateRecordFields 
TraditionalRecordSyntax 
OverloadedStrings 
GADTs 
GADTSyntax 
MonoPatBinds 
RelaxedPolyRec 
ExtendedDefaultRules 
NamedDefaults 
UnboxedTuples 
DeriveDataTypeable 
DeriveGeneric 
DefaultSignatures 
InstanceSigs 
ConstrainedClassMethods 
PackageImports 
ImpredicativeTypes 
NewQualifiedOperators 
PostfixOperators 
QuasiQuotes 
TransformListComp 
MonadComprehensions 
ViewPatterns 
XmlSyntax 
RegularPatterns 
TupleSections 
GHCForeignImportPrim 
NPlusKPatterns 
DoAndIfThenElse 
MultiWayIf 
LambdaCase 
RebindableSyntax 
ExplicitForAll 
DatatypeContexts 
MonoLocalBinds 
DeriveFunctor 
DeriveTraversable 
DeriveFoldable 
NondecreasingIndentation 
SafeImports 
Safe 
Trustworthy 
Unsafe 
ConstraintKinds 
PolyKinds 
DataKinds 
TypeData 
ParallelArrays 
RoleAnnotations 
OverloadedLists 
EmptyCase 
AutoDeriveTypeable 
NegativeLiterals 
BinaryLiterals 
NumDecimals 
NullaryTypeClasses 
ExplicitNamespaces 
AllowAmbiguousTypes 
JavaScriptFFI 
PatternSynonyms 
PartialTypeSignatures 
NamedWildCards 
DeriveAnyClass 
DeriveLift 
StaticPointers 
StrictData 
Strict 
ApplicativeDo 
DuplicateRecordFields 
TypeApplications 
TypeInType 
UndecidableSuperClasses 
MonadFailDesugaring 
TemplateHaskellQuotes 
OverloadedLabels 
TypeFamilyDependencies 
DerivingStrategies 
DerivingVia 
UnboxedSums 
HexFloatLiterals 
BlockArguments 
NumericUnderscores 
QuantifiedConstraints 
StarIsType 
EmptyDataDeriving 
CUSKs 
ImportQualifiedPost 
StandaloneKindSignatures 
UnliftedNewtypes 
LexicalNegation 
QualifiedDo 
LinearTypes 
RequiredTypeArguments 
FieldSelectors 
OverloadedRecordDot 
OverloadedRecordUpdate 
UnliftedDatatypes 
ExtendedLiterals 
AlternativeLayoutRule 
AlternativeLayoutRuleTransitional 
RelaxedLayout 
TypeAbstractions 
ListTuplePuns 
MultilineStrings 
OrPatterns 

Instances

Instances details
Pretty KnownExtension 
Instance details

Defined in Language.Haskell.Extension

Methods

pretty :: KnownExtension -> Doc

prettyVersioned :: CabalSpecVersion -> KnownExtension -> Doc

Structured KnownExtension 
Instance details

Defined in Language.Haskell.Extension

Methods

structure :: Proxy KnownExtension -> Structure

structureHash' :: Tagged KnownExtension MD5

Binary KnownExtension 
Instance details

Defined in Language.Haskell.Extension

NFData KnownExtension 
Instance details

Defined in Language.Haskell.Extension

Methods

rnf :: KnownExtension -> () #

Data KnownExtension 
Instance details

Defined in Language.Haskell.Extension

Methods

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

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

toConstr :: KnownExtension -> Constr #

dataTypeOf :: KnownExtension -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded KnownExtension 
Instance details

Defined in Language.Haskell.Extension

Enum KnownExtension 
Instance details

Defined in Language.Haskell.Extension

Generic KnownExtension 
Instance details

Defined in Language.Haskell.Extension

Associated Types

type Rep KnownExtension 
Instance details

Defined in Language.Haskell.Extension

type Rep KnownExtension = D1 ('MetaData "KnownExtension" "Language.Haskell.Extension" "Cabal-syntax-3.16.0.0-inplace" 'False) (((((((C1 ('MetaCons "OverlappingInstances" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UndecidableInstances" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "IncoherentInstances" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DoRec" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "RecursiveDo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ParallelListComp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MultiParamTypeClasses" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MonomorphismRestriction" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeepSubsumption" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "FunctionalDependencies" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Rank2Types" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RankNTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PolymorphicComponents" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExistentialQuantification" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ScopedTypeVariables" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PatternSignatures" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ImplicitParams" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FlexibleContexts" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FlexibleInstances" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "EmptyDataDecls" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CPP" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KindSignatures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BangPatterns" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TypeSynonymInstances" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TemplateHaskell" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ForeignFunctionInterface" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Arrows" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Generics" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "ImplicitPrelude" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NamedFieldPuns" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PatternGuards" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GeneralizedNewtypeDeriving" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GeneralisedNewtypeDeriving" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ExtensibleRecords" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RestrictedTypeSynonyms" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HereDocuments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MagicHash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeFamilies" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "StandaloneDeriving" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnicodeSyntax" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnliftedFFITypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InterruptibleFFI" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CApiFFI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LiberalTypeSynonyms" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TypeOperators" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RecordWildCards" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RecordPuns" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "DisambiguateRecordFields" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TraditionalRecordSyntax" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OverloadedStrings" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GADTs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GADTSyntax" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "MonoPatBinds" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RelaxedPolyRec" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ExtendedDefaultRules" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NamedDefaults" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnboxedTuples" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "DeriveDataTypeable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveGeneric" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DefaultSignatures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InstanceSigs" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ConstrainedClassMethods" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PackageImports" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ImpredicativeTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NewQualifiedOperators" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PostfixOperators" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "QuasiQuotes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TransformListComp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MonadComprehensions" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ViewPatterns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "XmlSyntax" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "RegularPatterns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TupleSections" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GHCForeignImportPrim" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NPlusKPatterns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DoAndIfThenElse" 'PrefixI 'False) (U1 :: Type -> Type)))))))) :+: ((((((C1 ('MetaCons "MultiWayIf" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LambdaCase" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RebindableSyntax" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExplicitForAll" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DatatypeContexts" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MonoLocalBinds" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DeriveFunctor" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DeriveTraversable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveFoldable" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "NondecreasingIndentation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SafeImports" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Safe" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Trustworthy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unsafe" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ConstraintKinds" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PolyKinds" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DataKinds" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TypeData" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ParallelArrays" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "RoleAnnotations" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverloadedLists" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EmptyCase" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AutoDeriveTypeable" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NegativeLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BinaryLiterals" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NumDecimals" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NullaryTypeClasses" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExplicitNamespaces" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "AllowAmbiguousTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JavaScriptFFI" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PatternSynonyms" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PartialTypeSignatures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NamedWildCards" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "DeriveAnyClass" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveLift" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StaticPointers" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StrictData" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Strict" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "ApplicativeDo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DuplicateRecordFields" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TypeApplications" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeInType" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "UndecidableSuperClasses" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MonadFailDesugaring" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TemplateHaskellQuotes" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OverloadedLabels" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeFamilyDependencies" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "DerivingStrategies" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DerivingVia" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnboxedSums" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HexFloatLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockArguments" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "NumericUnderscores" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QuantifiedConstraints" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StarIsType" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EmptyDataDeriving" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CUSKs" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "ImportQualifiedPost" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StandaloneKindSignatures" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnliftedNewtypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LexicalNegation" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "QualifiedDo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LinearTypes" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RequiredTypeArguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FieldSelectors" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverloadedRecordDot" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "OverloadedRecordUpdate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnliftedDatatypes" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ExtendedLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AlternativeLayoutRule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlternativeLayoutRuleTransitional" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "RelaxedLayout" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeAbstractions" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ListTuplePuns" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MultilineStrings" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OrPatterns" 'PrefixI 'False) (U1 :: Type -> Type)))))))))
Read KnownExtension 
Instance details

Defined in Language.Haskell.Extension

Show KnownExtension 
Instance details

Defined in Language.Haskell.Extension

Eq KnownExtension 
Instance details

Defined in Language.Haskell.Extension

Ord KnownExtension 
Instance details

Defined in Language.Haskell.Extension

type Rep KnownExtension 
Instance details

Defined in Language.Haskell.Extension

type Rep KnownExtension = D1 ('MetaData "KnownExtension" "Language.Haskell.Extension" "Cabal-syntax-3.16.0.0-inplace" 'False) (((((((C1 ('MetaCons "OverlappingInstances" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UndecidableInstances" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "IncoherentInstances" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DoRec" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "RecursiveDo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ParallelListComp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MultiParamTypeClasses" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MonomorphismRestriction" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeepSubsumption" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "FunctionalDependencies" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Rank2Types" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RankNTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PolymorphicComponents" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExistentialQuantification" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ScopedTypeVariables" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PatternSignatures" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ImplicitParams" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FlexibleContexts" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FlexibleInstances" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "EmptyDataDecls" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CPP" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KindSignatures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BangPatterns" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TypeSynonymInstances" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TemplateHaskell" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ForeignFunctionInterface" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Arrows" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Generics" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "ImplicitPrelude" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NamedFieldPuns" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PatternGuards" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GeneralizedNewtypeDeriving" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GeneralisedNewtypeDeriving" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ExtensibleRecords" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RestrictedTypeSynonyms" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HereDocuments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MagicHash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeFamilies" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "StandaloneDeriving" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnicodeSyntax" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnliftedFFITypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InterruptibleFFI" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CApiFFI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LiberalTypeSynonyms" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TypeOperators" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RecordWildCards" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RecordPuns" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "DisambiguateRecordFields" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TraditionalRecordSyntax" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OverloadedStrings" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GADTs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GADTSyntax" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "MonoPatBinds" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RelaxedPolyRec" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ExtendedDefaultRules" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NamedDefaults" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnboxedTuples" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "DeriveDataTypeable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveGeneric" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DefaultSignatures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InstanceSigs" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ConstrainedClassMethods" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PackageImports" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ImpredicativeTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NewQualifiedOperators" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PostfixOperators" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "QuasiQuotes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TransformListComp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MonadComprehensions" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ViewPatterns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "XmlSyntax" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "RegularPatterns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TupleSections" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GHCForeignImportPrim" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NPlusKPatterns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DoAndIfThenElse" 'PrefixI 'False) (U1 :: Type -> Type)))))))) :+: ((((((C1 ('MetaCons "MultiWayIf" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LambdaCase" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RebindableSyntax" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExplicitForAll" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DatatypeContexts" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MonoLocalBinds" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DeriveFunctor" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DeriveTraversable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveFoldable" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "NondecreasingIndentation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SafeImports" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Safe" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Trustworthy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unsafe" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ConstraintKinds" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PolyKinds" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DataKinds" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TypeData" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ParallelArrays" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "RoleAnnotations" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverloadedLists" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EmptyCase" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AutoDeriveTypeable" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NegativeLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BinaryLiterals" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NumDecimals" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NullaryTypeClasses" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExplicitNamespaces" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "AllowAmbiguousTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JavaScriptFFI" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PatternSynonyms" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PartialTypeSignatures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NamedWildCards" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "DeriveAnyClass" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveLift" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StaticPointers" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StrictData" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Strict" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "ApplicativeDo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DuplicateRecordFields" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TypeApplications" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeInType" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "UndecidableSuperClasses" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MonadFailDesugaring" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TemplateHaskellQuotes" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OverloadedLabels" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeFamilyDependencies" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "DerivingStrategies" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DerivingVia" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnboxedSums" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HexFloatLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockArguments" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "NumericUnderscores" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QuantifiedConstraints" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StarIsType" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EmptyDataDeriving" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CUSKs" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "ImportQualifiedPost" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StandaloneKindSignatures" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnliftedNewtypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LexicalNegation" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "QualifiedDo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LinearTypes" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RequiredTypeArguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FieldSelectors" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverloadedRecordDot" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "OverloadedRecordUpdate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnliftedDatatypes" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ExtendedLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AlternativeLayoutRule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlternativeLayoutRuleTransitional" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "RelaxedLayout" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeAbstractions" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ListTuplePuns" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MultilineStrings" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OrPatterns" 'PrefixI 'False) (U1 :: Type -> Type)))))))))

data Extension #

Instances

Instances details
Parsec Extension 
Instance details

Defined in Language.Haskell.Extension

Methods

parsec :: CabalParsing m => m Extension

Pretty Extension 
Instance details

Defined in Language.Haskell.Extension

Methods

pretty :: Extension -> Doc

prettyVersioned :: CabalSpecVersion -> Extension -> Doc

Structured Extension 
Instance details

Defined in Language.Haskell.Extension

Methods

structure :: Proxy Extension -> Structure

structureHash' :: Tagged Extension MD5

Binary Extension 
Instance details

Defined in Language.Haskell.Extension

NFData Extension 
Instance details

Defined in Language.Haskell.Extension

Methods

rnf :: Extension -> () #

Data Extension 
Instance details

Defined in Language.Haskell.Extension

Methods

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

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

toConstr :: Extension -> Constr #

dataTypeOf :: Extension -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Extension 
Instance details

Defined in Language.Haskell.Extension

Associated Types

type Rep Extension 
Instance details

Defined in Language.Haskell.Extension

type Rep Extension = D1 ('MetaData "Extension" "Language.Haskell.Extension" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "EnableExtension" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KnownExtension)) :+: (C1 ('MetaCons "DisableExtension" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KnownExtension)) :+: C1 ('MetaCons "UnknownExtension" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))
Read Extension 
Instance details

Defined in Language.Haskell.Extension

Show Extension 
Instance details

Defined in Language.Haskell.Extension

Eq Extension 
Instance details

Defined in Language.Haskell.Extension

Ord Extension 
Instance details

Defined in Language.Haskell.Extension

type Rep Extension 
Instance details

Defined in Language.Haskell.Extension

type Rep Extension = D1 ('MetaData "Extension" "Language.Haskell.Extension" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "EnableExtension" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KnownExtension)) :+: (C1 ('MetaCons "DisableExtension" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KnownExtension)) :+: C1 ('MetaCons "UnknownExtension" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))

data Language #

Instances

Instances details
Parsec Language 
Instance details

Defined in Language.Haskell.Extension

Methods

parsec :: CabalParsing m => m Language

Pretty Language 
Instance details

Defined in Language.Haskell.Extension

Methods

pretty :: Language -> Doc

prettyVersioned :: CabalSpecVersion -> Language -> Doc

Structured Language 
Instance details

Defined in Language.Haskell.Extension

Methods

structure :: Proxy Language -> Structure

structureHash' :: Tagged Language MD5

Binary Language 
Instance details

Defined in Language.Haskell.Extension

Methods

put :: Language -> Put #

get :: Get Language #

putList :: [Language] -> Put #

NFData Language 
Instance details

Defined in Language.Haskell.Extension

Methods

rnf :: Language -> () #

Data Language 
Instance details

Defined in Language.Haskell.Extension

Methods

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

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

toConstr :: Language -> Constr #

dataTypeOf :: Language -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Language 
Instance details

Defined in Language.Haskell.Extension

Associated Types

type Rep Language 
Instance details

Defined in Language.Haskell.Extension

type Rep Language = D1 ('MetaData "Language" "Language.Haskell.Extension" "Cabal-syntax-3.16.0.0-inplace" 'False) ((C1 ('MetaCons "Haskell98" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Haskell2010" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GHC2021" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GHC2024" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnknownLanguage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))

Methods

from :: Language -> Rep Language x #

to :: Rep Language x -> Language #

Read Language 
Instance details

Defined in Language.Haskell.Extension

Show Language 
Instance details

Defined in Language.Haskell.Extension

Eq Language 
Instance details

Defined in Language.Haskell.Extension

Ord Language 
Instance details

Defined in Language.Haskell.Extension

type Rep Language 
Instance details

Defined in Language.Haskell.Extension

type Rep Language = D1 ('MetaData "Language" "Language.Haskell.Extension" "Cabal-syntax-3.16.0.0-inplace" 'False) ((C1 ('MetaCons "Haskell98" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Haskell2010" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GHC2021" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GHC2024" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnknownLanguage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))

Simple interface

defaultMain :: IO () Source #

A simple implementation of main for a Cabal setup script. It reads the package description file using IO, and performs the action specified on the command line.

defaultMainNoRead :: GenericPackageDescription -> IO () Source #

Like defaultMain, but accepts the package description as input rather than using IO to read it.

defaultMainArgs :: [String] -> IO () Source #

A version of defaultMain that is passed the command line arguments, rather than getting them from the environment.

Customization

data UserHooks Source #

Hooks allow authors to add specific functionality before and after a command is run, and also to specify additional preprocessors.

  • WARNING: The hooks interface is under rather constant flux as we try to understand users needs. Setup files that depend on this interface may break in future releases.

Constructors

UserHooks 

Fields

type Args = [String] Source #

defaultMainWithHooks :: UserHooks -> IO () Source #

A customizable version of defaultMain.

defaultMainWithHooksArgs :: UserHooks -> [String] -> IO () Source #

A customizable version of defaultMain that also takes the command line arguments.

defaultMainWithHooksNoRead :: UserHooks -> GenericPackageDescription -> IO () Source #

A customizable version of defaultMainNoRead.

defaultMainWithHooksNoReadArgs :: UserHooks -> GenericPackageDescription -> [String] -> IO () Source #

A customizable version of defaultMainNoRead that also takes the command line arguments.

Since: 2.2.0.0

Standard sets of hooks

simpleUserHooks :: UserHooks Source #

Hooks that correspond to a plain instantiation of the "simple" build system

autoconfUserHooks :: UserHooks Source #

Basic autoconf UserHooks:

  • postConf runs ./configure, if present.
  • the pre-hooks, except for pre-conf, read additional build information from package.buildinfo, if present.

Thus configure can use local system information to generate package.buildinfo and possibly other files.

emptyUserHooks :: UserHooks Source #

Empty UserHooks which do nothing.