Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- compileProg :: (Mem rep inner, FreeIn op, MonadFreshNames m) => r -> Operations rep r op -> Space -> Prog rep -> m (Warnings, Definitions op)
- type OpCompiler rep r op = Pat (LetDec rep) -> Op rep -> ImpM rep r op ()
- type ExpCompiler rep r op = Pat (LetDec rep) -> Exp rep -> ImpM rep r op ()
- type CopyCompiler rep r op = PrimType -> MemLoc -> MemLoc -> ImpM rep r op ()
- type StmsCompiler rep r op = Names -> Stms rep -> ImpM rep r op () -> ImpM rep r op ()
- type AllocCompiler rep r op = VName -> Count Bytes (TExp Int64) -> ImpM rep r op ()
- data Operations rep r op = Operations {
- opsExpCompiler :: ExpCompiler rep r op
- opsOpCompiler :: OpCompiler rep r op
- opsStmsCompiler :: StmsCompiler rep r op
- opsCopyCompiler :: CopyCompiler rep r op
- opsAllocCompilers :: Map Space (AllocCompiler rep r op)
- defaultOperations :: (Mem rep inner, FreeIn op) => OpCompiler rep r op -> Operations rep r op
- data MemLoc = MemLoc {
- memLocName :: VName
- memLocShape :: [DimSize]
- memLocLMAD :: LMAD (TExp Int64)
- sliceMemLoc :: MemLoc -> Slice (TExp Int64) -> MemLoc
- newtype MemEntry = MemEntry {}
- newtype ScalarEntry = ScalarEntry {}
- data ImpM rep r op a
- localDefaultSpace :: Space -> ImpM rep r op a -> ImpM rep r op a
- askFunction :: ImpM rep r op (Maybe Name)
- newVNameForFun :: String -> ImpM rep r op VName
- nameForFun :: String -> ImpM rep r op Name
- askEnv :: ImpM rep r op r
- localEnv :: (r -> r) -> ImpM rep r op a -> ImpM rep r op a
- localOps :: Operations rep r op -> ImpM rep r op a -> ImpM rep r op a
- type VTable rep = Map VName (VarEntry rep)
- getVTable :: ImpM rep r op (VTable rep)
- localVTable :: (VTable rep -> VTable rep) -> ImpM rep r op a -> ImpM rep r op a
- subImpM :: r' -> Operations rep r' op' -> ImpM rep r' op' a -> ImpM rep r op (a, Code op')
- subImpM_ :: r' -> Operations rep r' op' -> ImpM rep r' op' a -> ImpM rep r op (Code op')
- emit :: Code op -> ImpM rep r op ()
- emitFunction :: Name -> Function op -> ImpM rep r op ()
- hasFunction :: Name -> ImpM rep r op Bool
- collect :: ImpM rep r op () -> ImpM rep r op (Code op)
- collect' :: ImpM rep r op a -> ImpM rep r op (a, Code op)
- data VarEntry rep
- data ArrayEntry = ArrayEntry {}
- lookupVar :: VName -> ImpM rep r op (VarEntry rep)
- lookupArray :: VName -> ImpM rep r op ArrayEntry
- lookupArraySpace :: VName -> ImpM rep r op Space
- lookupMemory :: VName -> ImpM rep r op MemEntry
- lookupAcc :: VName -> [TExp Int64] -> ImpM rep r op (VName, Space, [VName], [TExp Int64], Maybe (Lambda rep))
- askAttrs :: ImpM rep r op Attrs
- data TV t
- class MkTV t where
- tvSize :: TV t -> DimSize
- tvExp :: TV t -> TExp t
- tvVar :: TV t -> VName
- class ToExp a where
- compileAlloc :: Mem rep inner => Pat (LetDec rep) -> SubExp -> Space -> ImpM rep r op ()
- everythingVolatile :: ImpM rep r op a -> ImpM rep r op a
- compileBody :: Pat (LetDec rep) -> Body rep -> ImpM rep r op ()
- compileBody' :: [Param dec] -> Body rep -> ImpM rep r op ()
- compileLoopBody :: Typed dec => [Param dec] -> Body rep -> ImpM rep r op ()
- defCompileStms :: (Mem rep inner, FreeIn op) => Names -> Stms rep -> ImpM rep r op () -> ImpM rep r op ()
- compileStms :: Names -> Stms rep -> ImpM rep r op () -> ImpM rep r op ()
- compileExp :: Pat (LetDec rep) -> Exp rep -> ImpM rep r op ()
- defCompileExp :: Mem rep inner => Pat (LetDec rep) -> Exp rep -> ImpM rep r op ()
- fullyIndexArray :: VName -> [TExp Int64] -> ImpM rep r op (VName, Space, Count Elements (TExp Int64))
- fullyIndexArray' :: MemLoc -> [TExp Int64] -> ImpM rep r op (VName, Space, Count Elements (TExp Int64))
- copy :: CopyCompiler rep r op
- copyDWIM :: VName -> [DimIndex (TExp Int64)] -> SubExp -> [DimIndex (TExp Int64)] -> ImpM rep r op ()
- copyDWIMFix :: VName -> [TExp Int64] -> SubExp -> [TExp Int64] -> ImpM rep r op ()
- lmadCopy :: CopyCompiler rep r op
- typeSize :: Type -> Count Bytes (TExp Int64)
- inBounds :: Slice (TExp Int64) -> [TExp Int64] -> TExp Bool
- caseMatch :: [SubExp] -> [Maybe PrimValue] -> TExp Bool
- newVName :: MonadFreshNames m => String -> m VName
- dLParams :: Mem rep inner => [LParam rep] -> ImpM rep r op ()
- dFParams :: Mem rep inner => [FParam rep] -> ImpM rep r op ()
- addLoopVar :: VName -> IntType -> ImpM rep r op ()
- dScope :: Mem rep inner => Maybe (Exp rep) -> Scope rep -> ImpM rep r op ()
- dArray :: VName -> PrimType -> ShapeBase SubExp -> VName -> LMAD -> ImpM rep r op ()
- dPrim :: MkTV t => String -> ImpM rep r op (TV t)
- dPrimS :: String -> PrimType -> ImpM rep r op VName
- dPrimSV :: String -> PrimType -> ImpM rep r op (TV t)
- dPrimVol :: String -> PrimType -> TExp t -> ImpM rep r op (TV t)
- dPrim_ :: VName -> PrimType -> ImpM rep r op ()
- dPrimV_ :: VName -> TExp t -> ImpM rep r op ()
- dPrimV :: String -> TExp t -> ImpM rep r op (TV t)
- dPrimVE :: String -> TExp t -> ImpM rep r op (TExp t)
- dIndexSpace :: [(VName, TExp Int64)] -> TExp Int64 -> ImpM rep r op ()
- dIndexSpace' :: String -> [TExp Int64] -> TExp Int64 -> ImpM rep r op [TExp Int64]
- sFor :: String -> TExp t -> (TExp t -> ImpM rep r op ()) -> ImpM rep r op ()
- sWhile :: TExp Bool -> ImpM rep r op () -> ImpM rep r op ()
- sComment :: Text -> ImpM rep r op () -> ImpM rep r op ()
- sIf :: TExp Bool -> ImpM rep r op () -> ImpM rep r op () -> ImpM rep r op ()
- sWhen :: TExp Bool -> ImpM rep r op () -> ImpM rep r op ()
- sUnless :: TExp Bool -> ImpM rep r op () -> ImpM rep r op ()
- sOp :: op -> ImpM rep r op ()
- sDeclareMem :: String -> Space -> ImpM rep r op VName
- sAlloc :: String -> Count Bytes (TExp Int64) -> Space -> ImpM rep r op VName
- sAlloc_ :: VName -> Count Bytes (TExp Int64) -> Space -> ImpM rep r op ()
- sArray :: String -> PrimType -> ShapeBase SubExp -> VName -> LMAD -> ImpM rep r op VName
- sArrayInMem :: String -> PrimType -> ShapeBase SubExp -> VName -> ImpM rep r op VName
- sAllocArray :: String -> PrimType -> ShapeBase SubExp -> Space -> ImpM rep r op VName
- sAllocArrayPerm :: String -> PrimType -> ShapeBase SubExp -> Space -> [Int] -> ImpM rep r op VName
- sStaticArray :: String -> PrimType -> ArrayContents -> ImpM rep r op VName
- sWrite :: VName -> [TExp Int64] -> Exp -> ImpM rep r op ()
- sUpdate :: VName -> Slice (TExp Int64) -> SubExp -> ImpM rep r op ()
- sLoopNest :: Shape -> ([TExp Int64] -> ImpM rep r op ()) -> ImpM rep r op ()
- sLoopSpace :: [TExp t] -> ([TExp t] -> ImpM rep r op ()) -> ImpM rep r op ()
- (<--) :: TV t -> TExp t -> ImpM rep r op ()
- (<~~) :: VName -> Exp -> ImpM rep r op ()
- function :: Name -> [Param] -> [Param] -> ImpM rep r op () -> ImpM rep r op ()
- genConstants :: ImpM rep r op (Names, a) -> ImpM rep r op a
- warn :: Located loc => loc -> [loc] -> Text -> ImpM rep r op ()
- module Language.Futhark.Warnings
Entry Points
compileProg :: (Mem rep inner, FreeIn op, MonadFreshNames m) => r -> Operations rep r op -> Space -> Prog rep -> m (Warnings, Definitions op) Source #
Pluggable Compiler
type OpCompiler rep r op = Pat (LetDec rep) -> Op rep -> ImpM rep r op () Source #
How to compile an Op
.
type ExpCompiler rep r op = Pat (LetDec rep) -> Exp rep -> ImpM rep r op () Source #
How to compile an Exp
.
type StmsCompiler rep r op = Names -> Stms rep -> ImpM rep r op () -> ImpM rep r op () Source #
How to compile some Stms
.
type AllocCompiler rep r op = VName -> Count Bytes (TExp Int64) -> ImpM rep r op () Source #
An alternate way of compiling an allocation.
data Operations rep r op Source #
Operations | |
|
defaultOperations :: (Mem rep inner, FreeIn op) => OpCompiler rep r op -> Operations rep r op Source #
An operations set for which the expression compiler always
returns defCompileExp
.
When an array is declared, this is where it is stored.
MemLoc | |
|
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
HasScope SOACS (ImpM rep r op) Source # | |
Applicative (ImpM rep r op) Source # | |
Defined in Futhark.CodeGen.ImpGen pure :: a -> ImpM rep r op a # (<*>) :: ImpM rep r op (a -> b) -> ImpM rep r op a -> ImpM rep r op b # liftA2 :: (a -> b -> c) -> ImpM rep r op a -> ImpM rep r op b -> ImpM rep r op c # (*>) :: ImpM rep r op a -> ImpM rep r op b -> ImpM rep r op b # (<*) :: ImpM rep r op a -> ImpM rep r op b -> ImpM rep r op a # | |
Functor (ImpM rep r op) Source # | |
Monad (ImpM rep r op) Source # | |
MonadFreshNames (ImpM rep r op) Source # | |
Defined in Futhark.CodeGen.ImpGen getNameSource :: ImpM rep r op VNameSource Source # putNameSource :: VNameSource -> ImpM rep r op () Source # |
newVNameForFun :: String -> ImpM rep r op VName Source #
Generate a VName
, prefixed with askFunction
if it exists.
nameForFun :: String -> ImpM rep r op Name Source #
Generate a Name
, prefixed with askFunction
if it exists.
localVTable :: (VTable rep -> VTable rep) -> ImpM rep r op a -> ImpM rep 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!
emitFunction :: Name -> Function op -> ImpM rep r op () Source #
Emit a function in the generated code.
collect :: ImpM rep r op () -> ImpM rep r op (Code op) Source #
Execute a code generation action, returning the code that was emitted.
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 rep r op ArrayEntry Source #
lookupArraySpace :: VName -> ImpM rep r op Space Source #
In which memory space is this array allocated?
lookupAcc :: VName -> [TExp Int64] -> ImpM rep r op (VName, Space, [VName], [TExp Int64], Maybe (Lambda rep)) Source #
In the case of a histogram-like accumulator, also sets the index parameters.
askAttrs :: ImpM rep r op Attrs Source #
The active attributes, including those for the statement currently being compiled.
Building Blocks
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.
A type class that helps ensuring that the type annotation in a
TV
is correct.
mkTV :: VName -> TV t Source #
Create a typed variable from a name and a dynamic type.
tvType :: TV t -> PrimType Source #
Extract type from a TV
.
Compile things to Exp
.
toExp :: a -> ImpM rep r op Exp Source #
Compile to an Exp
, where the type (which must still be a
primitive) is deduced monadically.
toExp' :: PrimType -> a -> Exp Source #
Compile where we know the type in advance.
compileAlloc :: Mem rep inner => Pat (LetDec rep) -> SubExp -> Space -> ImpM rep r op () Source #
compileAlloc pat size space
allocates n
bytes of memory in
space
, writing the result to pat
, which must contain a single
memory-typed element.
everythingVolatile :: ImpM rep r op a -> ImpM rep r op a Source #
defCompileStms :: (Mem rep inner, FreeIn op) => Names -> Stms rep -> ImpM rep r op () -> ImpM rep r op () Source #
fullyIndexArray :: VName -> [TExp Int64] -> ImpM rep r op (VName, Space, Count Elements (TExp Int64)) Source #
fullyIndexArray' :: MemLoc -> [TExp Int64] -> ImpM rep r op (VName, Space, Count Elements (TExp Int64)) Source #
copy :: CopyCompiler rep r op Source #
copyDWIM :: VName -> [DimIndex (TExp Int64)] -> SubExp -> [DimIndex (TExp Int64)] -> ImpM rep 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.
lmadCopy :: CopyCompiler rep r op Source #
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.
inBounds :: Slice (TExp Int64) -> [TExp Int64] -> TExp Bool Source #
Is this indexing in-bounds for an array of the given shape? This is useful for things like scatter, which ignores out-of-bounds writes.
caseMatch :: [SubExp] -> [Maybe PrimValue] -> TExp Bool Source #
Generate an expression that is true if the subexpressions match the case pasttern.
Constructing code.
newVName :: MonadFreshNames m => String -> m VName Source #
Produce a fresh VName
, using the given base name as a template.
dPrimS :: String -> PrimType -> ImpM rep r op VName Source #
Create variable of some provided dynamic type. You'll need this when you are compiling program code of Haskell-level unknown type. For other things, use other functions.
dPrimSV :: String -> PrimType -> ImpM rep r op (TV t) Source #
Create TV
of some provided dynamic type. No guarantee that the
dynamic type matches the inferred type.
dIndexSpace :: [(VName, TExp Int64)] -> TExp Int64 -> ImpM rep r op () Source #
dIndexSpace f dims i
computes a list of indices into an
array with dimension dims
given the flat index i
. The
resulting list will have the same size as dims
. Intermediate
results are passed to f
.
dIndexSpace' :: String -> [TExp Int64] -> TExp Int64 -> ImpM rep r op [TExp Int64] Source #
Like dIndexSpace
, but invent some new names for the indexes
based on the given template.
sComment :: Text -> ImpM rep r op () -> ImpM rep r op () Source #
Execute a code generation action, wrapping the generated code
within a Comment
with the given description.
sArrayInMem :: String -> PrimType -> ShapeBase SubExp -> VName -> ImpM rep r op VName Source #
Declare an array in row-major order in the given memory block.
sAllocArray :: String -> PrimType -> ShapeBase SubExp -> Space -> ImpM rep r op VName Source #
Uses linear/iota index function.
sAllocArrayPerm :: String -> PrimType -> ShapeBase SubExp -> Space -> [Int] -> ImpM rep r op VName Source #
Like sAllocArray
, but permute the in-memory representation of the indices as specified.
sStaticArray :: String -> PrimType -> ArrayContents -> ImpM rep r op VName Source #
Uses linear/iota index function.
sLoopSpace :: [TExp t] -> ([TExp t] -> ImpM rep r op ()) -> ImpM rep r op () Source #
Create a sequential For
loop covering a space of the given
shape. The function is calling with the indexes for a given
iteration.
function :: Name -> [Param] -> [Param] -> ImpM rep r op () -> ImpM rep r op () Source #
Constructing an ad-hoc function that does not correspond to any of the IR functions in the input program.
genConstants :: ImpM rep r op (Names, a) -> ImpM rep r op a Source #
Generate constants that get put outside of all functions. Will
be executed at program startup. Action must return the names that
should should be made available. This one has real sharp edges. Do
not use inside subImpM
. Do not use any variable from the context.
warn :: Located loc => loc -> [loc] -> Text -> ImpM rep r op () Source #
Emit a warning about something the user should be aware of.
module Language.Futhark.Warnings