ghc-7.0.3: The GHC API

Vectorise.Builtins

Contents

Description

Builtin types and functions used by the vectoriser. The source program uses functions from GHC.PArr, which the vectoriser rewrites to use equivalent vectorised versions in the DPH backend packages.

The Builtins structure holds the name of all the things in the DPH packages we will need. We can get specific things using the selectors, which print a civilized panic message if the specified thing cannot be found.

Synopsis

Builtins

data Builtins Source

Holds the names of the builtin types and functions used by the vectoriser.

Constructors

Builtins 

Fields

dphModules :: Modules
 
parrayTyCon :: TyCon

PArray

parrayDataCon :: DataCon

PArray

pdataTyCon :: TyCon

PData

paTyCon :: TyCon

PA

paDataCon :: DataCon

PA

preprTyCon :: TyCon

PRepr

prTyCon :: TyCon

PR

prDataCon :: DataCon

PR

replicatePDVar :: Var

replicatePD

emptyPDVar :: Var

emptyPD

packByTagPDVar :: Var

packByTagPD

combinePDVars :: Array Int Var

combinePD

scalarClass :: Class

Scalar

closureTyCon :: TyCon

:->

closureVar :: Var

closure

applyVar :: Var

$:

liftedClosureVar :: Var

liftedClosure

liftedApplyVar :: Var

liftedApply

closureCtrFuns :: Array Int Var

closure1 .. closure2

voidTyCon :: TyCon

Void

wrapTyCon :: TyCon

Wrap

sumTyCons :: Array Int TyCon

Sum2 .. Sum3

voidVar :: Var

void

pvoidVar :: Var

pvoid

fromVoidVar :: Var

fromVoid

punitVar :: Var

punit

selTys :: Array Int Type

Sel2

selReplicates :: Array Int CoreExpr

replicate2

selPicks :: Array Int CoreExpr

pick2

selTagss :: Array Int CoreExpr

tagsSel2

selEls :: Array (Int, Int) CoreExpr

elementsSel2_0 .. elementsSel_2_1

scalarZips :: Array Int Var

map, zipWith, zipWith3

liftingContext :: Var

lc

indexBuiltinSource

Arguments

:: (Ix i, Outputable i) 
=> String

Name of the selector we've used, for panic messages.

-> (Builtins -> Array i a)

Field selector for the Builtins.

-> i

Index into the array.

-> Builtins 
-> a 

Get an element from one of the arrays of contained by a Builtins. If the indexed thing is not in the array then panic.

Wrapped selectors

Initialisation

initBuiltinsSource

Arguments

:: PackageId

package id the builtins are in, eg dph-common

-> DsM Builtins 

Create the initial map of builtin types and functions.

initBuiltinVars :: Builtins -> DsM [(Var, Var)]Source

Get the mapping of names in the Prelude to names in the DPH library.

initBuiltinTyCons :: Builtins -> DsM [(Name, TyCon)]Source

Get a list of names to TyCons in the mock prelude.

initBuiltinDataCons :: Builtins -> [(Name, DataCon)]Source

Get a list of names to DataCons in the mock prelude.

initBuiltinPAs :: Builtins -> (InstEnv, InstEnv) -> DsM [(Name, Var)]Source

Get the names of all buildin instance functions for the PA class.

initBuiltinPRs :: Builtins -> (InstEnv, InstEnv) -> DsM [(Name, Var)]Source

Get the names of all builtin instance functions for the PR class.

initBuiltinBoxedTyCons :: Builtins -> DsM [(Name, TyCon)]Source

Get a list of boxed TyCons in the mock prelude. This is Int only.

initBuiltinScalars :: Builtins -> DsM [Var]Source

Get a list of all scalar functions in the mock prelude.

Lookup

primMethod :: TyCon -> String -> Builtins -> DsM (Maybe Var)Source

Lookup a method function given its name and instance type.

primPArray :: TyCon -> Builtins -> DsM (Maybe TyCon)Source

Lookup the representation type we use for PArrays that contain a given element type.