futhark-0.15.5: An optimising compiler for a functional, array-oriented language.
Safe HaskellNone
LanguageHaskell2010

Futhark.CodeGen.ImpGen

Synopsis

Entry Points

compileProg :: (ExplicitMemorish lore, FreeIn op, MonadFreshNames m) => r -> Operations lore r op -> Space -> Prog lore -> m (Definitions op) Source #

Pluggable Compiler

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

How to compile an Op.

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

How to compile an Exp.

type CopyCompiler lore r op = PrimType -> MemLocation -> MemLocation -> ImpM lore r op () Source #

type StmsCompiler lore r op = Names -> Stms lore -> ImpM lore r op () -> ImpM lore r op () Source #

How to compile some Stms.

type AllocCompiler lore r op = VName -> Count Bytes Exp -> ImpM lore r op () Source #

An alternate way of compiling an allocation.

data Operations lore r op Source #

Constructors

Operations 

defaultOperations :: (ExplicitMemorish lore, FreeIn op) => OpCompiler lore r op -> Operations lore r 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

Instances details
Eq MemLocation Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Show MemLocation Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

newtype MemEntry Source #

Constructors

MemEntry 

Fields

Instances

Instances details
Show MemEntry Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

newtype ScalarEntry Source #

Constructors

ScalarEntry 

Instances

Instances details
Show ScalarEntry Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Monadic Compiler Interface

data ImpM lore r op a Source #

Instances

Instances details
HasScope SOACS (ImpM lore r op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

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

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

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

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

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

Defined in Futhark.CodeGen.ImpGen

Methods

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

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

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

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

Monad (ImpM lore r op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

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

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

return :: a -> ImpM lore r op a #

Functor (ImpM lore r op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

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

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

Applicative (ImpM lore r op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

pure :: a -> ImpM lore r op a #

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

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

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

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

MonadFreshNames (ImpM lore r op) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

getNameSource :: ImpM lore r op VNameSource Source #

putNameSource :: VNameSource -> ImpM lore r op () Source #

localDefaultSpace :: Space -> ImpM lore r op a -> ImpM lore r op a Source #

askEnv :: ImpM lore r op r Source #

localEnv :: (r -> r) -> ImpM lore r op a -> ImpM lore r op a Source #

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

The symbol table used during compilation.

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

Get the current symbol table.

localVTable :: (VTable lore -> VTable lore) -> ImpM lore r op a -> ImpM lore r 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 :: r' -> Operations lore r' op' -> ImpM lore r' op' a -> ImpM lore r op (a, Code op') Source #

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

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

Emit some generated imperative code.

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

Emit a function in the generated code.

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

Check if a function of a given name exists.

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

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

collect' :: ImpM lore r op a -> ImpM lore r op (a, Code op) Source #

comment :: String -> ImpM lore r op () -> ImpM lore r 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

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

data ArrayEntry Source #

Instances

Instances details
Show ArrayEntry Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Lookups

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

Building Blocks

class ToExp a where Source #

Compile things to Exp.

Methods

toExp :: a -> ImpM lore r op Exp Source #

Compile to an Exp, where the type (must must still be a primitive) is deduced monadically.

toExp' :: PrimType -> a -> Exp Source #

Compile where we know the type in advance.

Instances

Instances details
ToExp SubExp Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

toExp :: SubExp -> ImpM lore r op Exp Source #

toExp' :: PrimType -> SubExp -> Exp Source #

ToExp (PrimExp VName) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

compileAlloc :: ExplicitMemorish lore => Pattern lore -> SubExp -> Space -> ImpM lore r 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 r op a -> ImpM lore r op a Source #

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

compileBody' :: [Param attr] -> Body lore -> ImpM lore r op () Source #

compileLoopBody :: Typed attr => [Param attr] -> Body lore -> ImpM lore r op () Source #

defCompileStms :: (ExplicitMemorish lore, FreeIn op) => Names -> Stms lore -> ImpM lore r op () -> ImpM lore r op () Source #

compileStms :: Names -> Stms lore -> ImpM lore r op () -> ImpM lore r op () Source #

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

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

copy :: CopyCompiler lore r op Source #

copyDWIM :: VName -> [DimIndex Exp] -> SubExp -> [DimIndex Exp] -> ImpM lore r 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.

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

As copyDWIM, but implicitly DimFixes the indexes.

typeSize :: Type -> Count Bytes Exp Source #

The number of bytes needed to represent the array in a straightforward contiguous format.

Constructing code.

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

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

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

dArray :: VName -> PrimType -> ShapeBase SubExp -> MemBind -> ImpM lore r op () Source #

dPrim :: String -> PrimType -> ImpM lore r op VName Source #

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

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

dPrimV_ :: VName -> Exp -> ImpM lore r op () Source #

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

dPrimVE :: String -> Exp -> ImpM lore r op Exp Source #

sFor :: String -> Exp -> (Exp -> ImpM lore r op ()) -> ImpM lore r op () Source #

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

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

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

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

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

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

sAlloc :: String -> Count Bytes Exp -> Space -> ImpM lore r op VName Source #

sAlloc_ :: VName -> Count Bytes Exp -> Space -> ImpM lore r op () Source #

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

Uses linear/iota index function.

sAllocArrayPerm :: String -> PrimType -> ShapeBase SubExp -> Space -> [Int] -> ImpM lore r op VName Source #

Like sAllocArray, but permute the in-memory representation of the indices as specified.

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

Uses linear/iota index function.

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

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

sLoopNest :: Shape -> ([Exp] -> ImpM lore r op ()) -> ImpM lore r op () Source #

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

ASsignment.

function :: [Param] -> [Param] -> ImpM lore r op () -> ImpM lore r op (Function op) Source #

Constructing a non-entry point function.