Cabal-2.2.0.1: A framework for packaging Haskell software

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

Distribution.Simple.Compiler

Contents

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 Compiler #

Constructors

Compiler 

Fields

Instances
Eq Compiler # 
Instance details
Read Compiler # 
Instance details
Show Compiler # 
Instance details
Generic Compiler # 
Instance details

Associated Types

type Rep Compiler :: * -> * #

Methods

from :: Compiler -> Rep Compiler x #

to :: Rep Compiler x -> Compiler #

Binary Compiler # 
Instance details

Methods

put :: Compiler -> Put #

get :: Get Compiler #

putList :: [Compiler] -> Put #

type Rep Compiler # 
Instance details

compilerCompatFlavor :: CompilerFlavor -> Compiler -> Bool #

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 #

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

data PackageDB #

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 isloated environments of packages, for example to build a collection of related packages without installing them globally.

Instances
Eq PackageDB # 
Instance details
Ord PackageDB # 
Instance details
Read PackageDB # 
Instance details
Show PackageDB # 
Instance details
Generic PackageDB # 
Instance details

Associated Types

type Rep PackageDB :: * -> * #

Binary PackageDB # 
Instance details
type Rep PackageDB # 
Instance details
type Rep PackageDB = D1 (MetaData "PackageDB" "Distribution.Simple.Compiler" "Cabal-2.2.0.1-JS0vobxWxH7sbYKd0omMO" False) (C1 (MetaCons "GlobalPackageDB" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "UserPackageDB" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "SpecificPackageDB" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath))))

type PackageDBStack = [PackageDB] #

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.

registrationPackageDB :: PackageDBStack -> PackageDB #

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

Support for optimisation levels

data OptimisationLevel #

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
Bounded OptimisationLevel # 
Instance details
Enum OptimisationLevel # 
Instance details
Eq OptimisationLevel # 
Instance details
Read OptimisationLevel # 
Instance details
Show OptimisationLevel # 
Instance details
Generic OptimisationLevel # 
Instance details

Associated Types

type Rep OptimisationLevel :: * -> * #

Binary OptimisationLevel # 
Instance details
type Rep OptimisationLevel # 
Instance details
type Rep OptimisationLevel = D1 (MetaData "OptimisationLevel" "Distribution.Simple.Compiler" "Cabal-2.2.0.1-JS0vobxWxH7sbYKd0omMO" False) (C1 (MetaCons "NoOptimisation" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "NormalOptimisation" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MaximumOptimisation" PrefixI False) (U1 :: * -> *)))

Support for debug info levels

data DebugInfoLevel #

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
Bounded DebugInfoLevel # 
Instance details
Enum DebugInfoLevel # 
Instance details
Eq DebugInfoLevel # 
Instance details
Read DebugInfoLevel # 
Instance details
Show DebugInfoLevel # 
Instance details
Generic DebugInfoLevel # 
Instance details

Associated Types

type Rep DebugInfoLevel :: * -> * #

Binary DebugInfoLevel # 
Instance details
type Rep DebugInfoLevel # 
Instance details
type Rep DebugInfoLevel = D1 (MetaData "DebugInfoLevel" "Distribution.Simple.Compiler" "Cabal-2.2.0.1-JS0vobxWxH7sbYKd0omMO" False) ((C1 (MetaCons "NoDebugInfo" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MinimalDebugInfo" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "NormalDebugInfo" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MaximalDebugInfo" PrefixI False) (U1 :: * -> *)))

Support for language extensions

type Flag = String #

extensionsToFlags :: Compiler -> [Extension] -> [Flag] #

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

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

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

parmakeSupported :: Compiler -> Bool #

Does this compiler support parallel --make mode?

reexportedModulesSupported :: Compiler -> Bool #

Does this compiler support reexported-modules?

renamingPackageFlagsSupported :: Compiler -> Bool #

Does this compiler support thinning/renaming on package flags?

unifiedIPIDRequired :: Compiler -> Bool #

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

packageKeySupported :: Compiler -> Bool #

Does this compiler support package keys?

unitIdSupported :: Compiler -> Bool #

Does this compiler support unit IDs?

coverageSupported :: Compiler -> Bool #

Does this compiler support Haskell program coverage?

profilingSupported :: Compiler -> Bool #

Does this compiler support profiling?

backpackSupported :: Compiler -> Bool #

Does this compiler support Backpack?

arResponseFilesSupported :: Compiler -> Bool #

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

libraryDynDirSupported :: Compiler -> Bool #

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

Support for profiling detail levels

data ProfDetailLevel #

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
Eq ProfDetailLevel # 
Instance details
Read ProfDetailLevel # 
Instance details
Show ProfDetailLevel # 
Instance details
Generic ProfDetailLevel # 
Instance details

Associated Types

type Rep ProfDetailLevel :: * -> * #

Binary ProfDetailLevel # 
Instance details
type Rep ProfDetailLevel # 
Instance details
type Rep ProfDetailLevel = D1 (MetaData "ProfDetailLevel" "Distribution.Simple.Compiler" "Cabal-2.2.0.1-JS0vobxWxH7sbYKd0omMO" False) ((C1 (MetaCons "ProfDetailNone" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "ProfDetailDefault" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ProfDetailExportedFunctions" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "ProfDetailToplevelFunctions" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "ProfDetailAllFunctions" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ProfDetailOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))