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

Futhark.CodeGen.ImpGen

Synopsis

Entry Points

compileProg :: (Mem lore, FreeIn op, MonadFreshNames m) => r -> Operations lore r op -> Space -> Prog lore -> m (Warnings, 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 -> Slice (TExp Int64) -> MemLocation -> Slice (TExp Int64) -> 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 (TExp Int64) -> ImpM lore r op () Source #

An alternate way of compiling an allocation.

data Operations lore r op Source #

Constructors

Operations 

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

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

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 #

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 #

newVNameForFun :: String -> ImpM lore r op VName Source #

Generate a VName, prefixed with askFunction if it exists.

nameForFun :: String -> ImpM lore r op Name Source #

Generate a Name, prefixed with askFunction if it exists.

askEnv :: ImpM lore r op r Source #

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

localOps :: Operations lore r op -> 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
Decorations 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

data TV t Source #

A typed variable, which we can turn into a typed expression, or use as the target for an assignment. This is used to aid in type safety when doing code generation, by keeping the types straight. It is still easy to cheat when you need to.

mkTV :: VName -> PrimType -> TV t Source #

Create a typed variable from a name and a dynamic type. Note that there is no guarantee that the dynamic type corresponds to the inferred static type, but the latter will at least have to be used consistently.

tvSize :: TV t -> DimSize Source #

Convert a typed variable to a size (a SubExp).

tvExp :: TV t -> TExp t Source #

Convert a typed variable to a similarly typed expression.

tvVar :: TV t -> VName Source #

Extract the underlying variable name from a typed variable.

class ToExp a where Source #

Compile things to Exp.

Minimal complete definition

toExp, toExp'

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.

toInt64Exp :: a -> TExp Int64 Source #

toBoolExp :: a -> TExp Bool Source #

compileAlloc :: Mem 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 :: Mem lore => Pattern lore -> Body lore -> ImpM lore r op () Source #

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

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

defCompileStms :: (Mem 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 :: Mem lore => Pattern lore -> Exp lore -> ImpM lore r op () Source #

copy :: CopyCompiler lore r op Source #

copyDWIM :: VName -> [DimIndex (TExp Int64)] -> SubExp -> [DimIndex (TExp Int64)] -> 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 -> [TExp Int64] -> SubExp -> [TExp Int64] -> ImpM lore r op () Source #

As copyDWIM, but implicitly DimFixes the indexes.

typeSize :: Type -> Count Bytes (TExp Int64) Source #

The number of bytes needed to represent the array in a straightforward contiguous format, as an Int64 expression.

isMapTransposeCopy :: PrimType -> MemLocation -> Slice (TExp Int64) -> MemLocation -> Slice (TExp Int64) -> Maybe (TExp Int64, TExp Int64, TExp Int64, TExp Int64, TExp Int64) Source #

Is this copy really a mapping with transpose?

Constructing code.

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

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

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

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

dPrim :: String -> PrimType -> ImpM lore r op (TV t) Source #

The return type is polymorphic, so there is no guarantee it actually matches the PrimType, but at least we have to use it consistently.

dPrimVol :: String -> PrimType -> TExp t -> ImpM lore r op (TV t) Source #

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

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

dPrimV :: String -> TExp t -> ImpM lore r op (TV t) Source #

dPrimVE :: String -> TExp t -> ImpM lore r op (TExp t) Source #

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

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

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

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

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

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

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

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

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

Declare an array in row-major order in the given memory block.

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 -> [TExp Int64] -> Exp -> ImpM lore r op () Source #

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

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

(<--) :: TV t -> TExp t -> ImpM lore r op () infixl 3 Source #

Typed assignment.

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

Untyped assignment.

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

Constructing an ad-hoc function that does not correspond to any of the IR functions in the input program.

warn :: Located loc => loc -> [loc] -> String -> ImpM lore r op () Source #

Emit a warning about something the user should be aware of.