Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- compileProg :: (ExplicitMemorish lore, MonadFreshNames m) => Operations lore op -> Space -> [Space] -> Prog lore -> m (Either InternalError (Functions op))
- type OpCompiler lore op = Pattern lore -> Op lore -> ImpM lore op ()
- type ExpCompiler lore op = Pattern lore -> Exp lore -> ImpM lore op ()
- type CopyCompiler lore op = PrimType -> MemLocation -> MemLocation -> Count Elements -> ImpM lore op ()
- type StmsCompiler lore op = Names -> [Stm lore] -> ImpM lore op () -> ImpM lore op ()
- data Operations lore op = Operations {
- opsExpCompiler :: ExpCompiler lore op
- opsOpCompiler :: OpCompiler lore op
- opsStmsCompiler :: StmsCompiler lore op
- opsCopyCompiler :: CopyCompiler lore op
- defaultOperations :: (ExplicitMemorish lore, FreeIn op) => OpCompiler lore op -> Operations lore op
- data ValueDestination
- arrayDestination :: MemLocation -> ValueDestination
- data MemLocation = MemLocation {}
- data MemEntry = MemEntry {}
- newtype ScalarEntry = ScalarEntry {}
- data ImpM lore op a
- data Env lore op
- type VTable lore = Map VName (VarEntry lore)
- getVTable :: ImpM lore op (VTable lore)
- localVTable :: (VTable lore -> VTable lore) -> ImpM lore op a -> ImpM lore op a
- subImpM :: Operations lore' op' -> ImpM lore' op' a -> ImpM lore op (a, Code op')
- subImpM_ :: Operations lore' op' -> ImpM lore' op' a -> ImpM lore op (Code op')
- emit :: Code op -> ImpM lore op ()
- emitFunction :: Name -> Function op -> ImpM lore op ()
- hasFunction :: Name -> ImpM lore op Bool
- collect :: ImpM lore op () -> ImpM lore op (Code op)
- comment :: String -> ImpM lore op () -> ImpM lore op ()
- data VarEntry lore
- data ArrayEntry = ArrayEntry {}
- lookupVar :: VName -> ImpM lore op (VarEntry lore)
- lookupArray :: VName -> ImpM lore op ArrayEntry
- lookupMemory :: VName -> ImpM lore op MemEntry
- compileSubExp :: SubExp -> ImpM lore op Exp
- compileSubExpOfType :: PrimType -> SubExp -> Exp
- compileSubExpTo :: VName -> SubExp -> ImpM lore op ()
- compilePrimExp :: PrimExp VName -> Exp
- compileAlloc :: ExplicitMemorish lore => Pattern lore -> SubExp -> Space -> ImpM lore op ()
- subExpToDimSize :: SubExp -> ImpM lore op DimSize
- everythingVolatile :: ImpM lore op a -> ImpM lore op a
- compileBody :: ExplicitMemorish lore => Pattern lore -> Body lore -> ImpM lore op ()
- compileBody' :: (ExplicitMemorish lore, attr ~ LetAttr lore) => [Param attr] -> Body lore -> ImpM lore op ()
- compileLoopBody :: [VName] -> Body lore -> ImpM lore op ()
- defCompileStms :: (ExplicitMemorish lore, FreeIn op) => Names -> [Stm lore] -> ImpM lore op () -> ImpM lore op ()
- compileStms :: Names -> [Stm lore] -> ImpM lore op () -> ImpM lore op ()
- compileExp :: Pattern lore -> Exp lore -> ImpM lore op ()
- defCompileExp :: ExplicitMemorish lore => Pattern lore -> Exp lore -> ImpM lore op ()
- offsetArray :: MemLocation -> Exp -> MemLocation
- strideArray :: MemLocation -> Exp -> MemLocation
- fullyIndexArray :: VName -> [Exp] -> ImpM lore op (VName, Space, Count Bytes)
- fullyIndexArray' :: MemLocation -> [Exp] -> PrimType -> ImpM lore op (VName, Space, Count Bytes)
- varIndex :: VName -> Exp
- dimSizeToExp :: DimSize -> Count Elements
- dimSizeToSubExp :: Size -> SubExp
- copy :: CopyCompiler lore op
- copyDWIM :: VName -> [Exp] -> SubExp -> [Exp] -> ImpM lore op ()
- copyDWIMDest :: ValueDestination -> [Exp] -> SubExp -> [Exp] -> ImpM lore op ()
- copyElementWise :: CopyCompiler lore op
- dLParams :: ExplicitMemorish lore => [LParam lore] -> ImpM lore op ()
- dFParams :: ExplicitMemorish lore => [FParam lore] -> ImpM lore op ()
- dScope :: Maybe (Exp lore) -> Scope ExplicitMemory -> ImpM lore op ()
- dScopes :: [(Maybe (Exp lore), Scope ExplicitMemory)] -> ImpM lore op ()
- dArray :: VName -> PrimType -> ShapeBase SubExp -> MemBind -> ImpM lore op ()
- dPrim :: String -> PrimType -> ImpM lore op VName
- dPrim_ :: VName -> PrimType -> ImpM lore op ()
- dPrimV :: String -> Exp -> ImpM lore op VName
- sFor :: VName -> IntType -> Exp -> ImpM lore op () -> ImpM lore op ()
- sWhile :: Exp -> ImpM lore op () -> ImpM lore op ()
- sComment :: String -> ImpM lore op () -> ImpM lore op ()
- sIf :: Exp -> ImpM lore op () -> ImpM lore op () -> ImpM lore op ()
- sWhen :: Exp -> ImpM lore op () -> ImpM lore op ()
- sUnless :: Exp -> ImpM lore op () -> ImpM lore op ()
- sOp :: op -> ImpM lore op ()
- sAlloc :: String -> Count Bytes -> Space -> ImpM lore op VName
- sArray :: String -> PrimType -> ShapeBase SubExp -> MemBind -> ImpM lore op VName
- sAllocArray :: String -> PrimType -> ShapeBase SubExp -> Space -> ImpM lore op VName
- sStaticArray :: String -> Space -> PrimType -> [PrimValue] -> ImpM lore op VName
- sWrite :: VName -> [Exp] -> PrimExp ExpLeaf -> ImpM lore op ()
- (<--) :: VName -> Exp -> ImpM lore op ()
Entry Points
compileProg :: (ExplicitMemorish lore, MonadFreshNames m) => Operations lore op -> Space -> [Space] -> Prog lore -> m (Either InternalError (Functions op)) Source #
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 #
= 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 #
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 ValueDestination Source #
Instances
Show ValueDestination Source # | |
Defined in Futhark.CodeGen.ImpGen showsPrec :: Int -> ValueDestination -> ShowS # show :: ValueDestination -> String # showList :: [ValueDestination] -> ShowS # |
data MemLocation Source #
When an array is dared, this is where it is stored.
Instances
Eq MemLocation Source # | |
Defined in Futhark.CodeGen.ImpGen (==) :: MemLocation -> MemLocation -> Bool # (/=) :: MemLocation -> MemLocation -> Bool # | |
Show MemLocation Source # | |
Defined in Futhark.CodeGen.ImpGen showsPrec :: Int -> MemLocation -> ShowS # show :: MemLocation -> String # showList :: [MemLocation] -> ShowS # |
newtype ScalarEntry Source #
Instances
Show ScalarEntry Source # | |
Defined in Futhark.CodeGen.ImpGen showsPrec :: Int -> ScalarEntry -> ShowS # show :: ScalarEntry -> String # showList :: [ScalarEntry] -> ShowS # |
Monadic Compiler Interface
Instances
MonadError InternalError (ImpM lore op) Source # | |
Defined in Futhark.CodeGen.ImpGen 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 # | |
MonadWriter (Code op) (ImpM lore op) Source # | |
Monad (ImpM lore op) Source # | |
Functor (ImpM lore op) Source # | |
MonadFail (ImpM lore op) Source # | |
Defined in Futhark.CodeGen.ImpGen | |
Applicative (ImpM lore op) Source # | |
Defined in Futhark.CodeGen.ImpGen | |
MonadFreshNames (ImpM lore op) Source # | |
Defined in Futhark.CodeGen.ImpGen getNameSource :: ImpM lore op VNameSource Source # putNameSource :: VNameSource -> ImpM lore op () Source # | |
MonadReader (Env lore op) (ImpM lore op) Source # | |
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!
emitFunction :: Name -> Function op -> ImpM lore op () Source #
Emit a function in the generated 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.
Every non-scalar variable must be associated with an entry.
data ArrayEntry Source #
Instances
Show ArrayEntry Source # | |
Defined in Futhark.CodeGen.ImpGen showsPrec :: Int -> ArrayEntry -> ShowS # show :: ArrayEntry -> String # showList :: [ArrayEntry] -> ShowS # |
Lookups
lookupArray :: VName -> ImpM lore op ArrayEntry Source #
Building Blocks
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 #
defCompileStms :: (ExplicitMemorish lore, FreeIn op) => Names -> [Stm lore] -> ImpM lore op () -> ImpM lore op () Source #
defCompileExp :: ExplicitMemorish lore => Pattern lore -> Exp lore -> ImpM lore op () Source #
offsetArray :: MemLocation -> Exp -> MemLocation Source #
strideArray :: MemLocation -> Exp -> MemLocation Source #
fullyIndexArray' :: MemLocation -> [Exp] -> PrimType -> ImpM lore op (VName, Space, Count Bytes) Source #
dimSizeToSubExp :: Size -> SubExp Source #
copy :: CopyCompiler 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.
copyElementWise :: CopyCompiler lore op Source #
Constructing code.
sAllocArray :: String -> PrimType -> ShapeBase SubExp -> Space -> ImpM lore op VName Source #
Uses linear/iota index function.