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

Distribution.Simple.Compiler

Description

This should be a much more sophisticated abstraction than it is. Currently it's just a bit of data about the compiler, like its flavour and name and version. The reason it's just data is because currently it has to be in Read and Show so it can be saved along with the LocalBuildInfo. The only interesting bit of info it contains is a mapping between language extensions and compiler command line flags. This module also defines a PackageDB type which is used to refer to package databases. Most compilers only know about a single global package collection but GHC has a global and per-user one and it lets you create arbitrary other package databases. We do not yet fully support this latter feature.

Synopsis

Haskell implementations

data CompilerFlavor #

Instances

Instances details
Parsec CompilerFlavor 
Instance details

Defined in Distribution.Compiler

Methods

parsec :: CabalParsing m => m CompilerFlavor

Pretty CompilerFlavor 
Instance details

Defined in Distribution.Compiler

Methods

pretty :: CompilerFlavor -> Doc

prettyVersioned :: CabalSpecVersion -> CompilerFlavor -> Doc

Structured CompilerFlavor 
Instance details

Defined in Distribution.Compiler

Methods

structure :: Proxy CompilerFlavor -> Structure

structureHash' :: Tagged CompilerFlavor MD5

Binary CompilerFlavor 
Instance details

Defined in Distribution.Compiler

NFData CompilerFlavor 
Instance details

Defined in Distribution.Compiler

Methods

rnf :: CompilerFlavor -> () #

Data CompilerFlavor 
Instance details

Defined in Distribution.Compiler

Methods

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

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

toConstr :: CompilerFlavor -> Constr #

dataTypeOf :: CompilerFlavor -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic CompilerFlavor 
Instance details

Defined in Distribution.Compiler

Associated Types

type Rep CompilerFlavor 
Instance details

Defined in Distribution.Compiler

type Rep CompilerFlavor = D1 ('MetaData "CompilerFlavor" "Distribution.Compiler" "Cabal-syntax-3.16.0.0-inplace" 'False) (((C1 ('MetaCons "GHC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GHCJS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NHC" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "YHC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Hugs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HBC" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Helium" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "JHC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LHC" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "UHC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Eta" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MHS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OtherCompiler" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))
Read CompilerFlavor 
Instance details

Defined in Distribution.Compiler

Show CompilerFlavor 
Instance details

Defined in Distribution.Compiler

Eq CompilerFlavor 
Instance details

Defined in Distribution.Compiler

Ord CompilerFlavor 
Instance details

Defined in Distribution.Compiler

Newtype (CompilerFlavor, VersionRange) TestedWith 
Instance details

Defined in Distribution.FieldGrammar.Newtypes

Methods

pack :: (CompilerFlavor, VersionRange) -> TestedWith

unpack :: TestedWith -> (CompilerFlavor, VersionRange)

type Rep CompilerFlavor 
Instance details

Defined in Distribution.Compiler

type Rep CompilerFlavor = D1 ('MetaData "CompilerFlavor" "Distribution.Compiler" "Cabal-syntax-3.16.0.0-inplace" 'False) (((C1 ('MetaCons "GHC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GHCJS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NHC" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "YHC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Hugs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HBC" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Helium" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "JHC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LHC" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "UHC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Eta" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MHS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OtherCompiler" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))

data AbiTag #

Constructors

NoAbiTag 
AbiTag String 

Instances

Instances details
Parsec AbiTag 
Instance details

Defined in Distribution.Compiler

Methods

parsec :: CabalParsing m => m AbiTag

Pretty AbiTag 
Instance details

Defined in Distribution.Compiler

Methods

pretty :: AbiTag -> Doc

prettyVersioned :: CabalSpecVersion -> AbiTag -> Doc

Structured AbiTag 
Instance details

Defined in Distribution.Compiler

Methods

structure :: Proxy AbiTag -> Structure

structureHash' :: Tagged AbiTag MD5

Binary AbiTag 
Instance details

Defined in Distribution.Compiler

Methods

put :: AbiTag -> Put #

get :: Get AbiTag #

putList :: [AbiTag] -> Put #

Generic AbiTag 
Instance details

Defined in Distribution.Compiler

Associated Types

type Rep AbiTag 
Instance details

Defined in Distribution.Compiler

type Rep AbiTag = D1 ('MetaData "AbiTag" "Distribution.Compiler" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "NoAbiTag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AbiTag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

Methods

from :: AbiTag -> Rep AbiTag x #

to :: Rep AbiTag x -> AbiTag #

Read AbiTag 
Instance details

Defined in Distribution.Compiler

Show AbiTag 
Instance details

Defined in Distribution.Compiler

Eq AbiTag 
Instance details

Defined in Distribution.Compiler

Methods

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

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

type Rep AbiTag 
Instance details

Defined in Distribution.Compiler

type Rep AbiTag = D1 ('MetaData "AbiTag" "Distribution.Compiler" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "NoAbiTag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AbiTag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data CompilerInfo #

Instances

Instances details
Binary CompilerInfo 
Instance details

Defined in Distribution.Compiler

Generic CompilerInfo 
Instance details

Defined in Distribution.Compiler

Associated Types

type Rep CompilerInfo 
Instance details

Defined in Distribution.Compiler

type Rep CompilerInfo = D1 ('MetaData "CompilerInfo" "Distribution.Compiler" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "CompilerInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "compilerInfoId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CompilerId) :*: S1 ('MetaSel ('Just "compilerInfoAbiTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AbiTag)) :*: (S1 ('MetaSel ('Just "compilerInfoCompat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [CompilerId])) :*: (S1 ('MetaSel ('Just "compilerInfoLanguages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Language])) :*: S1 ('MetaSel ('Just "compilerInfoExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Extension]))))))
Read CompilerInfo 
Instance details

Defined in Distribution.Compiler

Show CompilerInfo 
Instance details

Defined in Distribution.Compiler

type Rep CompilerInfo 
Instance details

Defined in Distribution.Compiler

type Rep CompilerInfo = D1 ('MetaData "CompilerInfo" "Distribution.Compiler" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "CompilerInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "compilerInfoId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CompilerId) :*: S1 ('MetaSel ('Just "compilerInfoAbiTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AbiTag)) :*: (S1 ('MetaSel ('Just "compilerInfoCompat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [CompilerId])) :*: (S1 ('MetaSel ('Just "compilerInfoLanguages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Language])) :*: S1 ('MetaSel ('Just "compilerInfoExtensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Extension]))))))

data CompilerId #

Instances

Instances details
Parsec CompilerId 
Instance details

Defined in Distribution.Compiler

Methods

parsec :: CabalParsing m => m CompilerId

Pretty CompilerId 
Instance details

Defined in Distribution.Compiler

Methods

pretty :: CompilerId -> Doc

prettyVersioned :: CabalSpecVersion -> CompilerId -> Doc

Structured CompilerId 
Instance details

Defined in Distribution.Compiler

Methods

structure :: Proxy CompilerId -> Structure

structureHash' :: Tagged CompilerId MD5

Binary CompilerId 
Instance details

Defined in Distribution.Compiler

NFData CompilerId 
Instance details

Defined in Distribution.Compiler

Methods

rnf :: CompilerId -> () #

Generic CompilerId 
Instance details

Defined in Distribution.Compiler

Associated Types

type Rep CompilerId 
Instance details

Defined in Distribution.Compiler

type Rep CompilerId = D1 ('MetaData "CompilerId" "Distribution.Compiler" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "CompilerId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CompilerFlavor) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)))
Read CompilerId 
Instance details

Defined in Distribution.Compiler

Show CompilerId 
Instance details

Defined in Distribution.Compiler

Eq CompilerId 
Instance details

Defined in Distribution.Compiler

Ord CompilerId 
Instance details

Defined in Distribution.Compiler

type Rep CompilerId 
Instance details

Defined in Distribution.Compiler

type Rep CompilerId = D1 ('MetaData "CompilerId" "Distribution.Compiler" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "CompilerId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CompilerFlavor) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)))

data PerCompilerFlavor v #

Constructors

PerCompilerFlavor v v 

Instances

Instances details
Functor PerCompilerFlavor 
Instance details

Defined in Distribution.Compiler

Foldable PerCompilerFlavor 
Instance details

Defined in Distribution.Compiler

Methods

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

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

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

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

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

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

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

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

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

toList :: PerCompilerFlavor a -> [a] #

null :: PerCompilerFlavor a -> Bool #

length :: PerCompilerFlavor a -> Int #

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

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

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

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

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

Traversable PerCompilerFlavor 
Instance details

Defined in Distribution.Compiler

Methods

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

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

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

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

Structured a => Structured (PerCompilerFlavor a) 
Instance details

Defined in Distribution.Compiler

Methods

structure :: Proxy (PerCompilerFlavor a) -> Structure

structureHash' :: Tagged (PerCompilerFlavor a) MD5

Binary a => Binary (PerCompilerFlavor a) 
Instance details

Defined in Distribution.Compiler

NFData a => NFData (PerCompilerFlavor a) 
Instance details

Defined in Distribution.Compiler

Methods

rnf :: PerCompilerFlavor a -> () #

(Semigroup a, Monoid a) => Monoid (PerCompilerFlavor a) 
Instance details

Defined in Distribution.Compiler

Semigroup a => Semigroup (PerCompilerFlavor a) 
Instance details

Defined in Distribution.Compiler

Data v => Data (PerCompilerFlavor v) 
Instance details

Defined in Distribution.Compiler

Methods

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

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

toConstr :: PerCompilerFlavor v -> Constr #

dataTypeOf :: PerCompilerFlavor v -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (PerCompilerFlavor v) 
Instance details

Defined in Distribution.Compiler

Associated Types

type Rep (PerCompilerFlavor v) 
Instance details

Defined in Distribution.Compiler

type Rep (PerCompilerFlavor v) = D1 ('MetaData "PerCompilerFlavor" "Distribution.Compiler" "Cabal-syntax-3.16.0.0-inplace" 'False) (C1 ('MetaCons "PerCompilerFlavor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 v) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 v)))
Read v => Read (PerCompilerFlavor v) 
Instance details

Defined in Distribution.Compiler

Show v => Show (PerCompilerFlavor v) 
Instance details

Defined in Distribution.Compiler

Eq v => Eq (PerCompilerFlavor v) 
Instance details

Defined in Distribution.Compiler

Ord v => Ord (PerCompilerFlavor v) 
Instance details

Defined in Distribution.Compiler

type Rep (PerCompilerFlavor v) 
Instance details

Defined in Distribution.Compiler

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

data Compiler Source #

Constructors

Compiler 

Fields

Instances

Instances details
Structured Compiler Source # 
Instance details

Defined in Distribution.Simple.Compiler

Methods

structure :: Proxy Compiler -> Structure

structureHash' :: Tagged Compiler MD5

Binary Compiler Source # 
Instance details

Defined in Distribution.Simple.Compiler

Methods

put :: Compiler -> Put #

get :: Get Compiler #

putList :: [Compiler] -> Put #

Generic Compiler Source # 
Instance details

Defined in Distribution.Simple.Compiler

Associated Types

type Rep Compiler 
Instance details

Defined in Distribution.Simple.Compiler

Methods

from :: Compiler -> Rep Compiler x #

to :: Rep Compiler x -> Compiler #

Read Compiler Source # 
Instance details

Defined in Distribution.Simple.Compiler

Show Compiler Source # 
Instance details

Defined in Distribution.Simple.Compiler

Eq Compiler Source # 
Instance details

Defined in Distribution.Simple.Compiler

type Rep Compiler Source # 
Instance details

Defined in Distribution.Simple.Compiler

compilerCompatFlavor :: CompilerFlavor -> Compiler -> Bool Source #

Is this compiler compatible with the compiler flavour we're interested in?

For example this checks if the compiler is actually GHC or is another compiler that claims to be compatible with some version of GHC, e.g. GHCJS.

if compilerCompatFlavor GHC compiler then ... else ...

compilerCompatVersion :: CompilerFlavor -> Compiler -> Maybe Version Source #

Is this compiler compatible with the compiler flavour we're interested in, and if so what version does it claim to be compatible with.

For example this checks if the compiler is actually GHC-7.x or is another compiler that claims to be compatible with some GHC-7.x version.

case compilerCompatVersion GHC compiler of
  Just (Version (7:_)) -> ...
  _                    -> ...

Support for package databases

type PackageDB = PackageDBX (SymbolicPath Pkg ('Dir PkgDB)) Source #

type PackageDBStack = PackageDBStackX (SymbolicPath Pkg ('Dir PkgDB)) Source #

data PackageDBX fp Source #

Some compilers have a notion of a database of available packages. For some there is just one global db of packages, other compilers support a per-user or an arbitrary db specified at some location in the file system. This can be used to build isolated environments of packages, for example to build a collection of related packages without installing them globally.

Abstracted over

Constructors

GlobalPackageDB 
UserPackageDB 
SpecificPackageDB fp

NB: the path might be relative or it might be absolute

Instances

Instances details
Functor PackageDBX Source # 
Instance details

Defined in Distribution.Simple.Compiler

Methods

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

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

Foldable PackageDBX Source # 
Instance details

Defined in Distribution.Simple.Compiler

Methods

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

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

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

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

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

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

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

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

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

toList :: PackageDBX a -> [a] #

null :: PackageDBX a -> Bool #

length :: PackageDBX a -> Int #

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

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

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

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

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

Traversable PackageDBX Source # 
Instance details

Defined in Distribution.Simple.Compiler

Methods

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

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

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

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

Structured fp => Structured (PackageDBX fp) Source # 
Instance details

Defined in Distribution.Simple.Compiler

Methods

structure :: Proxy (PackageDBX fp) -> Structure

structureHash' :: Tagged (PackageDBX fp) MD5

Binary fp => Binary (PackageDBX fp) Source # 
Instance details

Defined in Distribution.Simple.Compiler

Methods

put :: PackageDBX fp -> Put #

get :: Get (PackageDBX fp) #

putList :: [PackageDBX fp] -> Put #

Generic (PackageDBX fp) Source # 
Instance details

Defined in Distribution.Simple.Compiler

Associated Types

type Rep (PackageDBX fp) 
Instance details

Defined in Distribution.Simple.Compiler

type Rep (PackageDBX fp) = D1 ('MetaData "PackageDBX" "Distribution.Simple.Compiler" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "GlobalPackageDB" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UserPackageDB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SpecificPackageDB" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 fp))))

Methods

from :: PackageDBX fp -> Rep (PackageDBX fp) x #

to :: Rep (PackageDBX fp) x -> PackageDBX fp #

Read fp => Read (PackageDBX fp) Source # 
Instance details

Defined in Distribution.Simple.Compiler

Show fp => Show (PackageDBX fp) Source # 
Instance details

Defined in Distribution.Simple.Compiler

Methods

showsPrec :: Int -> PackageDBX fp -> ShowS #

show :: PackageDBX fp -> String #

showList :: [PackageDBX fp] -> ShowS #

Eq fp => Eq (PackageDBX fp) Source # 
Instance details

Defined in Distribution.Simple.Compiler

Methods

(==) :: PackageDBX fp -> PackageDBX fp -> Bool #

(/=) :: PackageDBX fp -> PackageDBX fp -> Bool #

Ord fp => Ord (PackageDBX fp) Source # 
Instance details

Defined in Distribution.Simple.Compiler

Methods

compare :: PackageDBX fp -> PackageDBX fp -> Ordering #

(<) :: PackageDBX fp -> PackageDBX fp -> Bool #

(<=) :: PackageDBX fp -> PackageDBX fp -> Bool #

(>) :: PackageDBX fp -> PackageDBX fp -> Bool #

(>=) :: PackageDBX fp -> PackageDBX fp -> Bool #

max :: PackageDBX fp -> PackageDBX fp -> PackageDBX fp #

min :: PackageDBX fp -> PackageDBX fp -> PackageDBX fp #

type Rep (PackageDBX fp) Source # 
Instance details

Defined in Distribution.Simple.Compiler

type Rep (PackageDBX fp) = D1 ('MetaData "PackageDBX" "Distribution.Simple.Compiler" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "GlobalPackageDB" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UserPackageDB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SpecificPackageDB" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 fp))))

type PackageDBStackX from = [PackageDBX from] Source #

We typically get packages from several databases, and stack them together. This type lets us be explicit about that stacking. For example typical stacks include:

[GlobalPackageDB]
[GlobalPackageDB, UserPackageDB]
[GlobalPackageDB, SpecificPackageDB "package.conf.inplace"]

Note that the GlobalPackageDB is invariably at the bottom since it contains the rts, base and other special compiler-specific packages.

We are not restricted to using just the above combinations. In particular we can use several custom package dbs and the user package db together.

When it comes to writing, the top most (last) package is used.

type PackageDBS from = PackageDBX (SymbolicPath from ('Dir PkgDB)) Source #

type PackageDBStackS from = PackageDBStackX (SymbolicPath from ('Dir PkgDB)) Source #

registrationPackageDB :: PackageDBStackX from -> PackageDBX from Source #

Return the package that we should register into. This is the package db at the top of the stack.

absolutePackageDBPaths :: Maybe (SymbolicPath CWD ('Dir Pkg)) -> PackageDBStack -> IO PackageDBStack Source #

Make package paths absolute

absolutePackageDBPath :: Maybe (SymbolicPath CWD ('Dir Pkg)) -> PackageDB -> IO PackageDB Source #

interpretPackageDB :: Maybe (SymbolicPath CWD ('Dir Pkg)) -> PackageDB -> PackageDBCWD Source #

interpretPackageDBStack :: Maybe (SymbolicPath CWD ('Dir Pkg)) -> PackageDBStack -> PackageDBStackCWD Source #

coercePackageDB :: PackageDBCWD -> PackageDBX (SymbolicPath CWD ('Dir PkgDB)) Source #

Transform a package db using a FilePath into one using symbolic paths.

coercePackageDBStack :: [PackageDBCWD] -> [PackageDBX (SymbolicPath CWD ('Dir PkgDB))] Source #

Support for optimisation levels

data OptimisationLevel Source #

Some compilers support optimising. Some have different levels. For compilers that do not the level is just capped to the level they do support.

Instances

Instances details
Structured OptimisationLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Binary OptimisationLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Bounded OptimisationLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Enum OptimisationLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Generic OptimisationLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Associated Types

type Rep OptimisationLevel 
Instance details

Defined in Distribution.Simple.Compiler

type Rep OptimisationLevel = D1 ('MetaData "OptimisationLevel" "Distribution.Simple.Compiler" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "NoOptimisation" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NormalOptimisation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MaximumOptimisation" 'PrefixI 'False) (U1 :: Type -> Type)))
Read OptimisationLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Show OptimisationLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Eq OptimisationLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

type Rep OptimisationLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

type Rep OptimisationLevel = D1 ('MetaData "OptimisationLevel" "Distribution.Simple.Compiler" "Cabal-3.16.0.0-inplace" 'False) (C1 ('MetaCons "NoOptimisation" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NormalOptimisation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MaximumOptimisation" 'PrefixI 'False) (U1 :: Type -> Type)))

Support for debug info levels

data DebugInfoLevel Source #

Some compilers support emitting debug info. Some have different levels. For compilers that do not the level is just capped to the level they do support.

Instances

Instances details
Structured DebugInfoLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Methods

structure :: Proxy DebugInfoLevel -> Structure

structureHash' :: Tagged DebugInfoLevel MD5

Binary DebugInfoLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Bounded DebugInfoLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Enum DebugInfoLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Generic DebugInfoLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Associated Types

type Rep DebugInfoLevel 
Instance details

Defined in Distribution.Simple.Compiler

type Rep DebugInfoLevel = D1 ('MetaData "DebugInfoLevel" "Distribution.Simple.Compiler" "Cabal-3.16.0.0-inplace" 'False) ((C1 ('MetaCons "NoDebugInfo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MinimalDebugInfo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NormalDebugInfo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MaximalDebugInfo" 'PrefixI 'False) (U1 :: Type -> Type)))
Read DebugInfoLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Show DebugInfoLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Eq DebugInfoLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

type Rep DebugInfoLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

type Rep DebugInfoLevel = D1 ('MetaData "DebugInfoLevel" "Distribution.Simple.Compiler" "Cabal-3.16.0.0-inplace" 'False) ((C1 ('MetaCons "NoDebugInfo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MinimalDebugInfo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NormalDebugInfo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MaximalDebugInfo" 'PrefixI 'False) (U1 :: Type -> Type)))

Support for language extensions

extensionsToFlags :: Compiler -> [Extension] -> [CompilerFlag] Source #

For the given compiler, return the flags for the supported extensions.

unsupportedExtensions :: Compiler -> [Extension] -> [Extension] Source #

For the given compiler, return the extensions it does not support.

parmakeSupported :: Compiler -> Bool Source #

Does this compiler support parallel --make mode?

reexportedModulesSupported :: Compiler -> Bool Source #

Does this compiler support reexported-modules?

renamingPackageFlagsSupported :: Compiler -> Bool Source #

Does this compiler support thinning/renaming on package flags?

unifiedIPIDRequired :: Compiler -> Bool Source #

Does this compiler have unified IPIDs (so no package keys)

packageKeySupported :: Compiler -> Bool Source #

Does this compiler support package keys?

unitIdSupported :: Compiler -> Bool Source #

Does this compiler support unit IDs?

coverageSupported :: Compiler -> Bool Source #

Does this compiler support Haskell program coverage?

profilingSupported :: Compiler -> Bool Source #

Does this compiler support profiling?

profilingDynamicSupported :: Compiler -> Maybe Bool Source #

Is the compiler distributed with profiling dynamic libraries

profilingDynamicSupportedOrUnknown :: Compiler -> Bool Source #

Either profiling dynamic is definitely supported or we don't know (so assume it is)

profilingVanillaSupported :: Compiler -> Maybe Bool Source #

Is the compiler distributed with profiling libraries

profilingVanillaSupportedOrUnknown :: Compiler -> Bool Source #

Either profiling is definitely supported or we don't know (so assume it is)

dynamicSupported :: Compiler -> Maybe Bool Source #

Is the compiler distributed with dynamic libraries

backpackSupported :: Compiler -> Bool Source #

Does this compiler support Backpack?

arResponseFilesSupported :: Compiler -> Bool Source #

Does this compiler's "ar" command supports response file arguments (i.e. @file-style arguments).

arDashLSupported :: Compiler -> Bool Source #

Does this compiler's "ar" command support llvm-ar's -L flag, which compels the archiver to add an input archive's members rather than adding the archive itself.

libraryDynDirSupported :: Compiler -> Bool Source #

Does this compiler support a package database entry with: "dynamic-library-dirs"?

libraryVisibilitySupported :: Compiler -> Bool Source #

Does this compiler support a package database entry with: "visibility"?

jsemSupported :: Compiler -> Bool Source #

Does this compiler support the -jsem option?

reexportedAsSupported :: Compiler -> Bool Source #

Does the compiler support the -reexported-modules "A as B" syntax

Support for profiling detail levels

data ProfDetailLevel Source #

Some compilers (notably GHC) support profiling and can instrument programs so the system can account costs to different functions. There are different levels of detail that can be used for this accounting. For compilers that do not support this notion or the particular detail levels, this is either ignored or just capped to some similar level they do support.

Instances

Instances details
Structured ProfDetailLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Methods

structure :: Proxy ProfDetailLevel -> Structure

structureHash' :: Tagged ProfDetailLevel MD5

Binary ProfDetailLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Generic ProfDetailLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Associated Types

type Rep ProfDetailLevel 
Instance details

Defined in Distribution.Simple.Compiler

type Rep ProfDetailLevel = D1 ('MetaData "ProfDetailLevel" "Distribution.Simple.Compiler" "Cabal-3.16.0.0-inplace" 'False) ((C1 ('MetaCons "ProfDetailNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ProfDetailDefault" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ProfDetailExportedFunctions" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ProfDetailToplevelFunctions" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ProfDetailAllFunctions" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ProfDetailTopLate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ProfDetailOther" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))
Read ProfDetailLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Show ProfDetailLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

Eq ProfDetailLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

type Rep ProfDetailLevel Source # 
Instance details

Defined in Distribution.Simple.Compiler

type Rep ProfDetailLevel = D1 ('MetaData "ProfDetailLevel" "Distribution.Simple.Compiler" "Cabal-3.16.0.0-inplace" 'False) ((C1 ('MetaCons "ProfDetailNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ProfDetailDefault" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ProfDetailExportedFunctions" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ProfDetailToplevelFunctions" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ProfDetailAllFunctions" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ProfDetailTopLate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ProfDetailOther" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))