Copyright | Isaac Jones 2003-2004 |
---|---|
License | BSD3 |
Maintainer | cabal-devel@haskell.org |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Distribution.Compiler
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
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
- data CompilerFlavor
- buildCompilerId :: CompilerId
- buildCompilerFlavor :: CompilerFlavor
- defaultCompilerFlavor :: Maybe CompilerFlavor
- classifyCompilerFlavor :: String -> CompilerFlavor
- knownCompilerFlavors :: [CompilerFlavor]
- data PerCompilerFlavor v = PerCompilerFlavor v v
- perCompilerFlavorToList :: PerCompilerFlavor v -> [(CompilerFlavor, v)]
- data CompilerId = CompilerId CompilerFlavor Version
- data CompilerInfo = CompilerInfo {}
- unknownCompilerInfo :: CompilerId -> AbiTag -> CompilerInfo
- data AbiTag
- abiTagString :: AbiTag -> String
Compiler flavor
data CompilerFlavor Source #
Constructors
GHC | |
GHCJS | |
NHC | |
YHC | |
Hugs | |
HBC | |
Helium | |
JHC | |
LHC | |
UHC | |
Eta | |
HaskellSuite String | |
OtherCompiler String |
Instances
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.
Per compiler flavor
data PerCompilerFlavor v Source #
PerCompilerFlavor
carries only info per GHC and GHCJS
Cabal parses only ghc-options
and ghcjs-options
, others are omitted.
Constructors
PerCompilerFlavor v v |
Instances
Functor PerCompilerFlavor Source # | |||||
Defined in Distribution.Compiler Methods fmap :: (a -> b) -> PerCompilerFlavor a -> PerCompilerFlavor b # (<$) :: a -> PerCompilerFlavor b -> PerCompilerFlavor a # | |||||
Foldable PerCompilerFlavor Source # | |||||
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 Source # | |||||
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) Source # | |||||
Defined in Distribution.Compiler Methods structure :: Proxy (PerCompilerFlavor a) -> Structure Source # structureHash' :: Tagged (PerCompilerFlavor a) MD5 | |||||
Binary a => Binary (PerCompilerFlavor a) Source # | |||||
Defined in Distribution.Compiler Methods put :: PerCompilerFlavor a -> Put Source # get :: Get (PerCompilerFlavor a) Source # putList :: [PerCompilerFlavor a] -> Put Source # | |||||
NFData a => NFData (PerCompilerFlavor a) Source # | |||||
Defined in Distribution.Compiler Methods rnf :: PerCompilerFlavor a -> () Source # | |||||
(Semigroup a, Monoid a) => Monoid (PerCompilerFlavor a) Source # | |||||
Defined in Distribution.Compiler Methods mempty :: PerCompilerFlavor a # mappend :: PerCompilerFlavor a -> PerCompilerFlavor a -> PerCompilerFlavor a # mconcat :: [PerCompilerFlavor a] -> PerCompilerFlavor a # | |||||
Semigroup a => Semigroup (PerCompilerFlavor a) Source # | |||||
Defined in Distribution.Compiler Methods (<>) :: PerCompilerFlavor a -> PerCompilerFlavor a -> PerCompilerFlavor a # sconcat :: NonEmpty (PerCompilerFlavor a) -> PerCompilerFlavor a # stimes :: Integral b => b -> PerCompilerFlavor a -> PerCompilerFlavor a # | |||||
Data v => Data (PerCompilerFlavor v) Source # | |||||
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) Source # | |||||
Defined in Distribution.Compiler Associated Types
Methods from :: PerCompilerFlavor v -> Rep (PerCompilerFlavor v) x # to :: Rep (PerCompilerFlavor v) x -> PerCompilerFlavor v # | |||||
Read v => Read (PerCompilerFlavor v) Source # | |||||
Defined in Distribution.Compiler Methods readsPrec :: Int -> ReadS (PerCompilerFlavor v) # readList :: ReadS [PerCompilerFlavor v] # readPrec :: ReadPrec (PerCompilerFlavor v) # readListPrec :: ReadPrec [PerCompilerFlavor v] # | |||||
Show v => Show (PerCompilerFlavor v) Source # | |||||
Defined in Distribution.Compiler Methods showsPrec :: Int -> PerCompilerFlavor v -> ShowS # show :: PerCompilerFlavor v -> String # showList :: [PerCompilerFlavor v] -> ShowS # | |||||
Eq v => Eq (PerCompilerFlavor v) Source # | |||||
Defined in Distribution.Compiler Methods (==) :: PerCompilerFlavor v -> PerCompilerFlavor v -> Bool # (/=) :: PerCompilerFlavor v -> PerCompilerFlavor v -> Bool # | |||||
Ord v => Ord (PerCompilerFlavor v) Source # | |||||
Defined in Distribution.Compiler Methods compare :: PerCompilerFlavor v -> PerCompilerFlavor v -> Ordering # (<) :: PerCompilerFlavor v -> PerCompilerFlavor v -> Bool # (<=) :: PerCompilerFlavor v -> PerCompilerFlavor v -> Bool # (>) :: PerCompilerFlavor v -> PerCompilerFlavor v -> Bool # (>=) :: PerCompilerFlavor v -> PerCompilerFlavor v -> Bool # max :: PerCompilerFlavor v -> PerCompilerFlavor v -> PerCompilerFlavor v # min :: PerCompilerFlavor v -> PerCompilerFlavor v -> PerCompilerFlavor v # | |||||
type Rep (PerCompilerFlavor v) Source # | |||||
Defined in Distribution.Compiler type Rep (PerCompilerFlavor v) = D1 ('MetaData "PerCompilerFlavor" "Distribution.Compiler" "Cabal-syntax-3.12.0.0-29a8" '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))) |
perCompilerFlavorToList :: PerCompilerFlavor v -> [(CompilerFlavor, v)] Source #
Compiler id
data CompilerId Source #
Constructors
CompilerId CompilerFlavor Version |
Instances
Parsec CompilerId Source # | |||||
Defined in Distribution.Compiler Methods parsec :: CabalParsing m => m CompilerId Source # | |||||
Pretty CompilerId Source # | |||||
Defined in Distribution.Compiler Methods pretty :: CompilerId -> Doc Source # prettyVersioned :: CabalSpecVersion -> CompilerId -> Doc Source # | |||||
Structured CompilerId Source # | |||||
Defined in Distribution.Compiler | |||||
Binary CompilerId Source # | |||||
Defined in Distribution.Compiler Methods put :: CompilerId -> Put Source # get :: Get CompilerId Source # putList :: [CompilerId] -> Put Source # | |||||
NFData CompilerId Source # | |||||
Defined in Distribution.Compiler Methods rnf :: CompilerId -> () Source # | |||||
Generic CompilerId Source # | |||||
Defined in Distribution.Compiler Associated Types
| |||||
Read CompilerId Source # | |||||
Defined in Distribution.Compiler Methods readsPrec :: Int -> ReadS CompilerId # readList :: ReadS [CompilerId] # readPrec :: ReadPrec CompilerId # readListPrec :: ReadPrec [CompilerId] # | |||||
Show CompilerId Source # | |||||
Defined in Distribution.Compiler Methods showsPrec :: Int -> CompilerId -> ShowS # show :: CompilerId -> String # showList :: [CompilerId] -> ShowS # | |||||
Eq CompilerId Source # | |||||
Defined in Distribution.Compiler | |||||
Ord CompilerId Source # | |||||
Defined in Distribution.Compiler Methods compare :: CompilerId -> CompilerId -> Ordering # (<) :: CompilerId -> CompilerId -> Bool # (<=) :: CompilerId -> CompilerId -> Bool # (>) :: CompilerId -> CompilerId -> Bool # (>=) :: CompilerId -> CompilerId -> Bool # max :: CompilerId -> CompilerId -> CompilerId # min :: CompilerId -> CompilerId -> CompilerId # | |||||
type Rep CompilerId Source # | |||||
Defined in Distribution.Compiler type Rep CompilerId = D1 ('MetaData "CompilerId" "Distribution.Compiler" "Cabal-syntax-3.12.0.0-29a8" '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))) |
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
Binary CompilerInfo Source # | |||||
Defined in Distribution.Compiler Methods put :: CompilerInfo -> Put Source # get :: Get CompilerInfo Source # putList :: [CompilerInfo] -> Put Source # | |||||
Generic CompilerInfo Source # | |||||
Defined in Distribution.Compiler Associated Types
| |||||
Read CompilerInfo Source # | |||||
Defined in Distribution.Compiler Methods readsPrec :: Int -> ReadS CompilerInfo # readList :: ReadS [CompilerInfo] # | |||||
Show CompilerInfo Source # | |||||
Defined in Distribution.Compiler Methods showsPrec :: Int -> CompilerInfo -> ShowS # show :: CompilerInfo -> String # showList :: [CompilerInfo] -> ShowS # | |||||
type Rep CompilerInfo Source # | |||||
Defined in Distribution.Compiler type Rep CompilerInfo = D1 ('MetaData "CompilerInfo" "Distribution.Compiler" "Cabal-syntax-3.12.0.0-29a8" '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])))))) |
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.
Instances
Parsec AbiTag Source # | |||||
Defined in Distribution.Compiler Methods parsec :: CabalParsing m => m AbiTag Source # | |||||
Pretty AbiTag Source # | |||||
Defined in Distribution.Compiler | |||||
Structured AbiTag Source # | |||||
Defined in Distribution.Compiler | |||||
Binary AbiTag Source # | |||||
Generic AbiTag Source # | |||||
Defined in Distribution.Compiler Associated Types
| |||||
Read AbiTag Source # | |||||
Show AbiTag Source # | |||||
Eq AbiTag Source # | |||||
type Rep AbiTag Source # | |||||
Defined in Distribution.Compiler type Rep AbiTag = D1 ('MetaData "AbiTag" "Distribution.Compiler" "Cabal-syntax-3.12.0.0-29a8" 'False) (C1 ('MetaCons "NoAbiTag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AbiTag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) |
abiTagString :: AbiTag -> String Source #