futhark-0.7.4: An optimising compiler for a functional, array-oriented language.

Safe HaskellNone
LanguageHaskell2010

Futhark.CodeGen.ImpGen

Contents

Synopsis

Entry Points

Pluggable Compiler

type OpCompiler lore op = Destination -> Op lore -> ImpM lore op () Source #

How to compile an ExpT.

type ExpCompiler lore op = Destination -> Exp lore -> ImpM lore op () Source #

How to compile an Exp.

type CopyCompiler lore op Source #

Arguments

 = PrimType 
-> MemLocation 
-> MemLocation 
-> Count Elements

Number of row elements of the source.

-> ImpM lore op () 

type BodyCompiler lore op = Destination -> Body lore -> ImpM lore op () Source #

How to compile a BodyT.

data Operations lore op Source #

Constructors

Operations 

defaultOperations :: (ExplicitMemorish lore, FreeIn op) => OpCompiler lore op -> Operations lore op Source #

An operations set for which the expression compiler always returns CompileExp.

data Destination Source #

When compiling an expression, this is a description of where the result should end up. The integer is a reference to the construct that gave rise to this destination (for patterns, this will be the tag of the first name in the pattern). This can be used to make the generated code easier to relate to the original code.

Instances
Show Destination Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

data ValueDestination Source #

Constructors

ScalarDestination VName 
ArrayElemDestination VName PrimType Space (Count Bytes) 
MemoryDestination VName 
ArrayDestination (Maybe MemLocation)

The MemLocation is Just if a copy if required. If it is Nothing, then a copy/assignment of a memory block somewhere takes care of this array.

data MemLocation Source #

When an array is declared, this is where it is stored.

Instances
Eq MemLocation Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Show MemLocation Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

newtype ScalarEntry Source #

Constructors

ScalarEntry 

Monadic Compiler Interface

data ImpM lore op a Source #

Instances
MonadState VNameSource (ImpM lore op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

get :: ImpM lore op VNameSource #

put :: VNameSource -> ImpM lore op () #

state :: (VNameSource -> (a, VNameSource)) -> ImpM lore op a #

MonadError InternalError (ImpM lore op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

throwError :: InternalError -> ImpM lore op a #

catchError :: ImpM lore op a -> (InternalError -> ImpM lore op a) -> ImpM lore op a #

HasScope SOACS (ImpM lore op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

lookupType :: VName -> ImpM lore op Type Source #

lookupInfo :: VName -> ImpM lore op (NameInfo SOACS) Source #

askScope :: ImpM lore op (Scope SOACS) Source #

asksScope :: (Scope SOACS -> a) -> ImpM lore op a Source #

MonadWriter (Code op) (ImpM lore op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

writer :: (a, Code op) -> ImpM lore op a #

tell :: Code op -> ImpM lore op () #

listen :: ImpM lore op a -> ImpM lore op (a, Code op) #

pass :: ImpM lore op (a, Code op -> Code op) -> ImpM lore op a #

Monad (ImpM lore op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

(>>=) :: ImpM lore op a -> (a -> ImpM lore op b) -> ImpM lore op b #

(>>) :: ImpM lore op a -> ImpM lore op b -> ImpM lore op b #

return :: a -> ImpM lore op a #

fail :: String -> ImpM lore op a #

Functor (ImpM lore op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

fmap :: (a -> b) -> ImpM lore op a -> ImpM lore op b #

(<$) :: a -> ImpM lore op b -> ImpM lore op a #

MonadFail (ImpM lore op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

fail :: String -> ImpM lore op a #

Applicative (ImpM lore op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

pure :: a -> ImpM lore op a #

(<*>) :: ImpM lore op (a -> b) -> ImpM lore op a -> ImpM lore op b #

liftA2 :: (a -> b -> c) -> ImpM lore op a -> ImpM lore op b -> ImpM lore op c #

(*>) :: ImpM lore op a -> ImpM lore op b -> ImpM lore op b #

(<*) :: ImpM lore op a -> ImpM lore op b -> ImpM lore op a #

MonadFreshNames (ImpM lore op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

MonadReader (Env lore op) (ImpM lore op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

ask :: ImpM lore op (Env lore op) #

local :: (Env lore op -> Env lore op) -> ImpM lore op a -> ImpM lore op a #

reader :: (Env lore op -> a) -> ImpM lore op a #

data Env lore op Source #

Instances
MonadReader (Env lore op) (ImpM lore op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

ask :: ImpM lore op (Env lore op) #

local :: (Env lore op -> Env lore op) -> ImpM lore op a -> ImpM lore op a #

reader :: (Env lore op -> a) -> ImpM lore op a #

subImpM :: Operations lore' op' -> ImpM lore' op' a -> ImpM lore op (a, Code op') Source #

subImpM_ :: Operations lore' op' -> ImpM lore' op' a -> ImpM lore op (Code op') Source #

emit :: Code op -> ImpM lore op () Source #

Emit some generated imperative code.

collect :: ImpM lore op () -> ImpM lore op (Code op) Source #

Execute a code generation action, returning the code that was emitted.

comment :: String -> ImpM lore op () -> ImpM lore op () Source #

Execute a code generation action, wrapping the generated code within a Comment with the given description.

data VarEntry lore Source #

Every non-scalar variable must be associated with an entry.

Constructors

ArrayVar (Maybe (Exp lore)) ArrayEntry 
ScalarVar (Maybe (Exp lore)) ScalarEntry 
MemVar (Maybe (Exp lore)) MemEntry 

Lookups

lookupVar :: VName -> ImpM lore op (VarEntry lore) Source #

Building Blocks

compileAlloc :: Destination -> SubExp -> Space -> ImpM lore op () Source #

compileAlloc dest size space allocates n bytes of memory in space, writing the result to dest, which must be a single MemoryDestination,

declaringLParams :: ExplicitMemorish lore => [LParam lore] -> ImpM lore op a -> ImpM lore op a Source #

declaringFParams :: ExplicitMemorish lore => [FParam lore] -> ImpM lore op a -> ImpM lore op a Source #

declaringVarEntry :: VName -> VarEntry lore -> ImpM lore op a -> ImpM lore op a Source #

declaringScope :: Maybe (Exp lore) -> Scope ExplicitMemory -> ImpM lore op a -> ImpM lore op a Source #

declaringScopes :: [(Maybe (Exp lore), Scope ExplicitMemory)] -> ImpM lore op a -> ImpM lore op a Source #

declaringPrimVar :: VName -> PrimType -> ImpM lore op a -> ImpM lore op a Source #

declaringPrimVars :: [(VName, PrimType)] -> ImpM lore op a -> ImpM lore op a Source #

withPrimVar :: VName -> PrimType -> ImpM lore op a -> ImpM lore op a Source #

everythingVolatile :: ImpM lore op a -> ImpM lore op a Source #

compileBody :: Destination -> Body lore -> ImpM lore op () Source #

compileLoopBody :: (ExplicitMemorish lore, FreeIn op) => [VName] -> Body lore -> ImpM lore op (Code op) Source #

defCompileBody :: (ExplicitMemorish lore, FreeIn op) => Destination -> Body lore -> ImpM lore op () Source #

compileStms :: (ExplicitMemorish lore, FreeIn op) => Names -> [Stm lore] -> ImpM lore op () -> ImpM lore op () Source #

compileExp :: Destination -> Exp lore -> ImpM lore op () Source #

defCompileExp :: (ExplicitMemorish lore, FreeIn op) => Destination -> Exp lore -> ImpM lore op () Source #

funcallTargets :: Destination -> ImpM lore op [VName] Source #

Remove the array targets.

copyDWIM :: VName -> [Exp] -> SubExp -> [Exp] -> ImpM lore op () Source #

Copy from here to there; both destination and source be indexeded. If so, they better be arrays of enough dimensions. This function will generally just Do What I Mean, and Do The Right Thing. Both destination and source must be in scope.

copyDWIMDest :: ValueDestination -> [Exp] -> SubExp -> [Exp] -> ImpM lore op () Source #

Like copyDWIM, but the target is a ValueDestination instead of a variable name.