futhark-0.10.1: 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 = Pattern lore -> Op lore -> ImpM lore op () Source #

How to compile an ExpT.

type ExpCompiler lore op = Pattern lore -> 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 StmsCompiler lore op = Names -> [Stm lore] -> ImpM lore op () -> ImpM lore op () Source #

How to compile some Stms.

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 MemLocation Source #

When an array is dared, 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

data MemEntry Source #

Constructors

MemEntry 
Instances
Show MemEntry Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

newtype ScalarEntry Source #

Constructors

ScalarEntry 
Instances
Show ScalarEntry Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Monadic Compiler Interface

data ImpM lore op a Source #

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

type VTable lore = Map VName (VarEntry lore) Source #

The symbol table used during compilation.

getVTable :: ImpM lore op (VTable lore) Source #

Get the current symbol table.

localVTable :: (VTable lore -> VTable lore) -> ImpM lore op a -> ImpM lore op a Source #

Run an action with a modified symbol table. All changes to the symbol table will be reverted once the action is done!

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.

emitFunction :: Name -> Function op -> ImpM lore op () Source #

Emit a function in the generated code.

hasFunction :: Name -> ImpM lore op Bool Source #

Check if a function of a given name exists.

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 
Instances
Annotations lore => Show (VarEntry lore) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

showsPrec :: Int -> VarEntry lore -> ShowS #

show :: VarEntry lore -> String #

showList :: [VarEntry lore] -> ShowS #

Lookups

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

Building Blocks

compileSubExpTo :: VName -> SubExp -> ImpM lore op () Source #

compileAlloc :: ExplicitMemorish lore => Pattern lore -> SubExp -> Space -> ImpM lore op () Source #

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

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

compileBody :: ExplicitMemorish lore => Pattern lore -> Body lore -> ImpM lore op () Source #

compileBody' :: (ExplicitMemorish lore, attr ~ LetAttr lore) => [Param attr] -> Body lore -> ImpM lore op () Source #

compileLoopBody :: [VName] -> Body lore -> ImpM lore op () Source #

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

compileStms :: Names -> [Stm lore] -> ImpM lore op () -> ImpM lore op () Source #

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

defCompileExp :: ExplicitMemorish lore => Pattern lore -> Exp lore -> ImpM lore op () Source #

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.

Constructing code.

dLParams :: ExplicitMemorish lore => [LParam lore] -> ImpM lore op () Source #

dFParams :: ExplicitMemorish lore => [FParam lore] -> ImpM lore op () Source #

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

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

dPrim_ :: VName -> PrimType -> ImpM lore op () Source #

dPrimV :: String -> Exp -> ImpM lore op VName Source #

sFor :: VName -> IntType -> Exp -> ImpM lore op () -> ImpM lore op () Source #

sWhile :: Exp -> ImpM lore op () -> ImpM lore op () Source #

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

sIf :: Exp -> ImpM lore op () -> ImpM lore op () -> ImpM lore op () Source #

sWhen :: Exp -> ImpM lore op () -> ImpM lore op () Source #

sUnless :: Exp -> ImpM lore op () -> ImpM lore op () Source #

sOp :: op -> ImpM lore op () Source #

sAlloc_ :: VName -> MemSize -> Space -> ImpM lore op () Source #

sAllocArray :: String -> PrimType -> ShapeBase SubExp -> Space -> ImpM lore op VName Source #

Uses linear/iota index function.

sStaticArray :: String -> Space -> PrimType -> ArrayContents -> ImpM lore op VName Source #

Uses linear/iota index function.

sWrite :: VName -> [Exp] -> PrimExp ExpLeaf -> ImpM lore op () Source #

sUpdate :: VName -> Slice Exp -> SubExp -> ImpM lore op () Source #

(<--) :: VName -> Exp -> ImpM lore op () infixl 3 Source #

ASsignment.