Cabal-2.0.1.1: A framework for packaging Haskell software

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

Distribution.Compiler

Contents

Description

This has an enumeration of the various compilers that Cabal knows about. It also specifies the default compiler. Sadly you'll often see code that does case analysis on this compiler flavour enumeration like:

case compilerFlavor comp of
  GHC -> GHC.getInstalledPackages verbosity packageDb progdb
  JHC -> JHC.getInstalledPackages verbosity packageDb progdb

Obviously it would be better to use the proper Compiler abstraction because that would keep all the compiler-specific code together. Unfortunately we cannot make this change yet without breaking the UserHooks api, which would break all custom Setup.hs files, so for the moment we just have to live with this deficiency. If you're interested, see ticket #57.

Synopsis

Compiler flavor

data CompilerFlavor Source #

Instances
Eq CompilerFlavor Source # 
Instance details
Data CompilerFlavor Source # 
Instance details

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 :: (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 #

Ord CompilerFlavor Source # 
Instance details
Read CompilerFlavor Source # 
Instance details
Show CompilerFlavor Source # 
Instance details
Generic CompilerFlavor Source # 
Instance details

Associated Types

type Rep CompilerFlavor :: * -> * #

Binary CompilerFlavor Source # 
Instance details
Text CompilerFlavor Source # 
Instance details
type Rep CompilerFlavor Source # 
Instance details
type Rep CompilerFlavor = D1 * (MetaData "CompilerFlavor" "Distribution.Compiler" "Cabal-2.0.1.1-99tbaCBn5in8ykZQ2Yxqis" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "GHC" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "GHCJS" PrefixI False) (U1 *)) (C1 * (MetaCons "NHC" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "YHC" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Hugs" PrefixI False) (U1 *)) (C1 * (MetaCons "HBC" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "Helium" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "JHC" PrefixI False) (U1 *)) (C1 * (MetaCons "LHC" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "UHC" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "HaskellSuite" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) (C1 * (MetaCons "OtherCompiler" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))))))

defaultCompilerFlavor :: Maybe CompilerFlavor Source #

The default compiler flavour to pick when compiling stuff. This defaults to the compiler used to build the Cabal lib.

However if it's not a recognised compiler then it's Nothing and the user will have to specify which compiler they want.

parseCompilerFlavorCompat :: ReadP r CompilerFlavor Source #

Like classifyCompilerFlavor but compatible with the old ReadS parser.

It is compatible in the sense that it accepts only the same strings, eg GHC but not "ghc". However other strings get mapped to OtherCompiler. The point of this is that we do not allow extra valid values that would upset older Cabal versions that had a stricter parser however we cope with new values more gracefully so that we'll be able to introduce new value in future without breaking things so much.

Compiler id

data CompilerId Source #

Instances
Eq CompilerId Source # 
Instance details
Ord CompilerId Source # 
Instance details
Read CompilerId Source # 
Instance details
Show CompilerId Source # 
Instance details
Generic CompilerId Source # 
Instance details

Associated Types

type Rep CompilerId :: * -> * #

Binary CompilerId Source # 
Instance details
Text CompilerId Source # 
Instance details
type Rep CompilerId Source # 
Instance details

Compiler info

data CompilerInfo Source #

Compiler information used for resolving configurations. Some fields can be set to Nothing to indicate that the information is unknown.

Constructors

CompilerInfo 

Fields

Instances
Read CompilerInfo Source # 
Instance details
Show CompilerInfo Source # 
Instance details
Generic CompilerInfo Source # 
Instance details

Associated Types

type Rep CompilerInfo :: * -> * #

Binary CompilerInfo Source # 
Instance details
type Rep CompilerInfo Source # 
Instance details
type Rep CompilerInfo = D1 * (MetaData "CompilerInfo" "Distribution.Compiler" "Cabal-2.0.1.1-99tbaCBn5in8ykZQ2Yxqis" False) (C1 * (MetaCons "CompilerInfo" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "compilerInfoId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CompilerId)) (S1 * (MetaSel (Just Symbol "compilerInfoAbiTag") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * AbiTag))) ((:*:) * (S1 * (MetaSel (Just Symbol "compilerInfoCompat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe [CompilerId]))) ((:*:) * (S1 * (MetaSel (Just Symbol "compilerInfoLanguages") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe [Language]))) (S1 * (MetaSel (Just Symbol "compilerInfoExtensions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe [Extension])))))))

unknownCompilerInfo :: CompilerId -> AbiTag -> CompilerInfo Source #

Make a CompilerInfo of which only the known information is its CompilerId, its AbiTag and that it does not claim to be compatible with other compiler id's.

data AbiTag Source #

Constructors

NoAbiTag 
AbiTag String 
Instances
Eq AbiTag Source # 
Instance details

Methods

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

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

Read AbiTag Source # 
Instance details
Show AbiTag Source # 
Instance details
Generic AbiTag Source # 
Instance details

Associated Types

type Rep AbiTag :: * -> * #

Methods

from :: AbiTag -> Rep AbiTag x #

to :: Rep AbiTag x -> AbiTag #

Binary AbiTag Source # 
Instance details

Methods

put :: AbiTag -> Put #

get :: Get AbiTag #

putList :: [AbiTag] -> Put #

Text AbiTag Source # 
Instance details
type Rep AbiTag Source # 
Instance details
type Rep AbiTag = D1 * (MetaData "AbiTag" "Distribution.Compiler" "Cabal-2.0.1.1-99tbaCBn5in8ykZQ2Yxqis" False) ((:+:) * (C1 * (MetaCons "NoAbiTag" PrefixI False) (U1 *)) (C1 * (MetaCons "AbiTag" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))))