Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
Synopsis
- compileProg :: (Mem lore, FreeIn op, MonadFreshNames m) => r -> Operations lore r op -> Space -> Prog lore -> m (Warnings, Definitions op)
- type OpCompiler lore r op = Pattern lore -> Op lore -> ImpM lore r op ()
- type ExpCompiler lore r op = Pattern lore -> Exp lore -> ImpM lore r op ()
- type CopyCompiler lore r op = PrimType -> MemLocation -> Slice Exp -> MemLocation -> Slice Exp -> ImpM lore r op ()
- type StmsCompiler lore r op = Names -> Stms lore -> ImpM lore r op () -> ImpM lore r op ()
- type AllocCompiler lore r op = VName -> Count Bytes Exp -> ImpM lore r op ()
- data Operations lore r op = Operations {
- opsExpCompiler :: ExpCompiler lore r op
- opsOpCompiler :: OpCompiler lore r op
- opsStmsCompiler :: StmsCompiler lore r op
- opsCopyCompiler :: CopyCompiler lore r op
- opsAllocCompilers :: Map Space (AllocCompiler lore r op)
- defaultOperations :: (Mem lore, FreeIn op) => OpCompiler lore r op -> Operations lore r op
- data MemLocation = MemLocation {}
- newtype MemEntry = MemEntry {}
- newtype ScalarEntry = ScalarEntry {}
- data ImpM lore r op a
- localDefaultSpace :: Space -> ImpM lore r op a -> ImpM lore r op a
- askFunction :: ImpM lore r op (Maybe Name)
- newVNameForFun :: String -> ImpM lore r op VName
- nameForFun :: String -> ImpM lore r op Name
- askEnv :: ImpM lore r op r
- localEnv :: (r -> r) -> ImpM lore r op a -> ImpM lore r op a
- localOps :: Operations lore r op -> ImpM lore r op a -> ImpM lore r op a
- type VTable lore = Map VName (VarEntry lore)
- getVTable :: ImpM lore r op (VTable lore)
- localVTable :: (VTable lore -> VTable lore) -> ImpM lore r op a -> ImpM lore r op a
- subImpM :: r' -> Operations lore r' op' -> ImpM lore r' op' a -> ImpM lore r op (a, Code op')
- subImpM_ :: r' -> Operations lore r' op' -> ImpM lore r' op' a -> ImpM lore r op (Code op')
- emit :: Code op -> ImpM lore r op ()
- emitFunction :: Name -> Function op -> ImpM lore r op ()
- hasFunction :: Name -> ImpM lore r op Bool
- collect :: ImpM lore r op () -> ImpM lore r op (Code op)
- collect' :: ImpM lore r op a -> ImpM lore r op (a, Code op)
- comment :: String -> ImpM lore r op () -> ImpM lore r op ()
- data VarEntry lore
- data ArrayEntry = ArrayEntry {}
- lookupVar :: VName -> ImpM lore r op (VarEntry lore)
- lookupArray :: VName -> ImpM lore r op ArrayEntry
- lookupMemory :: VName -> ImpM lore r op MemEntry
- class ToExp a where
- compileAlloc :: Mem lore => Pattern lore -> SubExp -> Space -> ImpM lore r op ()
- everythingVolatile :: ImpM lore r op a -> ImpM lore r op a
- compileBody :: Mem lore => Pattern lore -> Body lore -> ImpM lore r op ()
- compileBody' :: [Param dec] -> Body lore -> ImpM lore r op ()
- compileLoopBody :: Typed dec => [Param dec] -> Body lore -> ImpM lore r op ()
- defCompileStms :: (Mem lore, FreeIn op) => Names -> Stms lore -> ImpM lore r op () -> ImpM lore r op ()
- compileStms :: Names -> Stms lore -> ImpM lore r op () -> ImpM lore r op ()
- compileExp :: Pattern lore -> Exp lore -> ImpM lore r op ()
- defCompileExp :: Mem lore => Pattern lore -> Exp lore -> ImpM lore r op ()
- fullyIndexArray :: VName -> [Exp] -> ImpM lore r op (VName, Space, Count Elements Exp)
- fullyIndexArray' :: MemLocation -> [Exp] -> ImpM lore r op (VName, Space, Count Elements Exp)
- copy :: CopyCompiler lore r op
- copyDWIM :: VName -> [DimIndex Exp] -> SubExp -> [DimIndex Exp] -> ImpM lore r op ()
- copyDWIMFix :: VName -> [Exp] -> SubExp -> [Exp] -> ImpM lore r op ()
- copyElementWise :: CopyCompiler lore r op
- typeSize :: Type -> Count Bytes Exp
- dLParams :: Mem lore => [LParam lore] -> ImpM lore r op ()
- dFParams :: Mem lore => [FParam lore] -> ImpM lore r op ()
- dScope :: Mem lore => Maybe (Exp lore) -> Scope lore -> ImpM lore r op ()
- dArray :: VName -> PrimType -> ShapeBase SubExp -> MemBind -> ImpM lore r op ()
- dPrim :: String -> PrimType -> ImpM lore r op VName
- dPrimVol_ :: VName -> PrimType -> ImpM lore r op ()
- dPrim_ :: VName -> PrimType -> ImpM lore r op ()
- dPrimV_ :: VName -> Exp -> ImpM lore r op ()
- dPrimV :: String -> Exp -> ImpM lore r op VName
- dPrimVE :: String -> Exp -> ImpM lore r op Exp
- sFor :: String -> Exp -> (Exp -> ImpM lore r op ()) -> ImpM lore r op ()
- sWhile :: Exp -> ImpM lore r op () -> ImpM lore r op ()
- sComment :: String -> ImpM lore r op () -> ImpM lore r op ()
- sIf :: Exp -> ImpM lore r op () -> ImpM lore r op () -> ImpM lore r op ()
- sWhen :: Exp -> ImpM lore r op () -> ImpM lore r op ()
- sUnless :: Exp -> ImpM lore r op () -> ImpM lore r op ()
- sOp :: op -> ImpM lore r op ()
- sDeclareMem :: String -> Space -> ImpM lore r op VName
- sAlloc :: String -> Count Bytes Exp -> Space -> ImpM lore r op VName
- sAlloc_ :: VName -> Count Bytes Exp -> Space -> ImpM lore r op ()
- sArray :: String -> PrimType -> ShapeBase SubExp -> MemBind -> ImpM lore r op VName
- sArrayInMem :: String -> PrimType -> ShapeBase SubExp -> VName -> ImpM lore r op VName
- sAllocArray :: String -> PrimType -> ShapeBase SubExp -> Space -> ImpM lore r op VName
- sAllocArrayPerm :: String -> PrimType -> ShapeBase SubExp -> Space -> [Int] -> ImpM lore r op VName
- sStaticArray :: String -> Space -> PrimType -> ArrayContents -> ImpM lore r op VName
- sWrite :: VName -> [Exp] -> PrimExp ExpLeaf -> ImpM lore r op ()
- sUpdate :: VName -> Slice Exp -> SubExp -> ImpM lore r op ()
- sLoopNest :: Shape -> ([Exp] -> ImpM lore r op ()) -> ImpM lore r op ()
- (<--) :: VName -> Exp -> ImpM lore r op ()
- function :: Name -> [Param] -> [Param] -> ImpM lore r op () -> ImpM lore r op ()
- warn :: Located loc => loc -> [loc] -> String -> ImpM lore r op ()
- module Language.Futhark.Warnings
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 Exp -> MemLocation -> Slice Exp -> 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 #
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
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
data ImpM lore r op a Source #
Instances
HasScope SOACS (ImpM lore r op) Source # | |
Monad (ImpM lore r op) Source # | |
Functor (ImpM lore r op) Source # | |
Applicative (ImpM lore r op) Source # | |
Defined in Futhark.CodeGen.ImpGen 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 # | |
Defined in Futhark.CodeGen.ImpGen getNameSource :: ImpM lore r op VNameSource Source # putNameSource :: VNameSource -> ImpM lore r op () 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.
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 #
emitFunction :: Name -> Function op -> ImpM lore r op () Source #
Emit a function in the generated code.
collect :: ImpM lore r op () -> ImpM lore r op (Code op) Source #
Execute a code generation action, returning the code that was emitted.
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.
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 r op ArrayEntry Source #
Building Blocks
Compile things to Exp
.
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.
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 #
defCompileStms :: (Mem lore, FreeIn op) => Names -> Stms lore -> ImpM lore r op () -> ImpM lore r op () Source #
fullyIndexArray' :: MemLocation -> [Exp] -> ImpM lore r op (VName, Space, Count Elements Exp) 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.
copyElementWise :: CopyCompiler lore r op Source #
typeSize :: Type -> Count Bytes Exp Source #
The number of bytes needed to represent the array in a
straightforward contiguous format, as an Int64
expression.
Constructing code.
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.
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.
module Language.Futhark.Warnings