| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Futhark.Representation.Kernels.Kernel
Synopsis
- data GenReduceOp lore = GenReduceOp {
- genReduceWidth :: SubExp
- genReduceDest :: [VName]
- genReduceNeutral :: [SubExp]
- genReduceShape :: Shape
- genReduceOp :: LambdaT lore
- data SegRedOp lore = SegRedOp {
- segRedComm :: Commutativity
- segRedLambda :: Lambda lore
- segRedNeutral :: [SubExp]
- segRedShape :: Shape
- segRedResults :: [SegRedOp lore] -> Int
- data KernelBody lore = KernelBody {
- kernelBodyLore :: BodyAttr lore
- kernelBodyStms :: Stms lore
- kernelBodyResult :: [KernelResult]
- data KernelResult
- = Returns SubExp
- | WriteReturns [SubExp] VName [([SubExp], SubExp)]
- | ConcatReturns SplitOrdering SubExp SubExp VName
- | TileReturns [(SubExp, SubExp)] VName
- kernelResultSubExp :: KernelResult -> SubExp
- data SplitOrdering
- data SegOp lore
- = SegMap SegLevel SegSpace [Type] (KernelBody lore)
- | SegRed SegLevel SegSpace [SegRedOp lore] [Type] (KernelBody lore)
- | SegScan SegLevel SegSpace (Lambda lore) [SubExp] [Type] (KernelBody lore)
- | SegGenRed SegLevel SegSpace [GenReduceOp lore] [Type] (KernelBody lore)
- data SegLevel
- = SegThread { }
- | SegGroup { }
- | SegThreadScalar { }
- data SegVirt
- segLevel :: SegOp lore -> SegLevel
- segSpace :: SegOp lore -> SegSpace
- typeCheckSegOp :: Checkable lore => Maybe SegLevel -> SegOp (Aliases lore) -> TypeM lore ()
- data SegSpace = SegSpace {
- segFlat :: VName
- unSegSpace :: [(VName, SubExp)]
- scopeOfSegSpace :: SegSpace -> Scope lore
- segSpaceDims :: SegSpace -> [SubExp]
- data SegOpMapper flore tlore m = SegOpMapper {
- mapOnSegOpSubExp :: SubExp -> m SubExp
- mapOnSegOpLambda :: Lambda flore -> m (Lambda tlore)
- mapOnSegOpBody :: KernelBody flore -> m (KernelBody tlore)
- mapOnSegOpVName :: VName -> m VName
- identitySegOpMapper :: Monad m => SegOpMapper lore lore m
- mapSegOpM :: (Applicative m, Monad m) => SegOpMapper flore tlore m -> SegOp flore -> m (SegOp tlore)
- data SegOpWalker lore m = SegOpWalker {
- walkOnSegOpSubExp :: SubExp -> m ()
- walkOnSegOpLambda :: Lambda lore -> m ()
- walkOnSegOpBody :: KernelBody lore -> m ()
- walkOnSegOpVName :: VName -> m ()
- identitySegOpWalker :: Monad m => SegOpWalker lore m
- walkSegOpM :: Monad m => SegOpWalker lore m -> SegOp lore -> m ()
- data HostOp lore op
- typeCheckHostOp :: Checkable lore => (SegLevel -> OpWithAliases (Op lore) -> TypeM lore ()) -> Maybe SegLevel -> (op -> TypeM lore ()) -> HostOp (Aliases lore) op -> TypeM lore ()
- module Futhark.Representation.Kernels.Sizes
Documentation
data GenReduceOp lore Source #
Constructors
| GenReduceOp | |
Fields
| |
Instances
| Annotations lore => Eq (GenReduceOp lore) Source # | |
Defined in Futhark.Representation.Kernels.Kernel Methods (==) :: GenReduceOp lore -> GenReduceOp lore -> Bool # (/=) :: GenReduceOp lore -> GenReduceOp lore -> Bool # | |
| Annotations lore => Ord (GenReduceOp lore) Source # | |
Defined in Futhark.Representation.Kernels.Kernel Methods compare :: GenReduceOp lore -> GenReduceOp lore -> Ordering # (<) :: GenReduceOp lore -> GenReduceOp lore -> Bool # (<=) :: GenReduceOp lore -> GenReduceOp lore -> Bool # (>) :: GenReduceOp lore -> GenReduceOp lore -> Bool # (>=) :: GenReduceOp lore -> GenReduceOp lore -> Bool # max :: GenReduceOp lore -> GenReduceOp lore -> GenReduceOp lore # min :: GenReduceOp lore -> GenReduceOp lore -> GenReduceOp lore # | |
| Annotations lore => Show (GenReduceOp lore) Source # | |
Defined in Futhark.Representation.Kernels.Kernel Methods showsPrec :: Int -> GenReduceOp lore -> ShowS # show :: GenReduceOp lore -> String # showList :: [GenReduceOp lore] -> ShowS # | |
Constructors
| SegRedOp | |
Fields
| |
Instances
| Annotations lore => Eq (SegRedOp lore) Source # | |
| Annotations lore => Ord (SegRedOp lore) Source # | |
Defined in Futhark.Representation.Kernels.Kernel Methods compare :: SegRedOp lore -> SegRedOp lore -> Ordering # (<) :: SegRedOp lore -> SegRedOp lore -> Bool # (<=) :: SegRedOp lore -> SegRedOp lore -> Bool # (>) :: SegRedOp lore -> SegRedOp lore -> Bool # (>=) :: SegRedOp lore -> SegRedOp lore -> Bool # | |
| Annotations lore => Show (SegRedOp lore) Source # | |
segRedResults :: [SegRedOp lore] -> Int Source #
How many reduction results are produced by these SegRedOps?
data KernelBody lore Source #
The body of a Kernel.
Constructors
| KernelBody | |
Fields
| |
Instances
data KernelResult Source #
Constructors
| Returns SubExp | Each "worker" in the kernel returns this.
Whether this is a result-per-thread or a
result-per-group depends on the |
| WriteReturns [SubExp] VName [([SubExp], SubExp)] | |
| ConcatReturns SplitOrdering SubExp SubExp VName | |
| TileReturns [(SubExp, SubExp)] VName |
Instances
data SplitOrdering Source #
How an array is split into chunks.
Constructors
| SplitContiguous | |
| SplitStrided SubExp |
Instances
Segmented operations
Constructors
| SegMap SegLevel SegSpace [Type] (KernelBody lore) | |
| SegRed SegLevel SegSpace [SegRedOp lore] [Type] (KernelBody lore) | The KernelSpace must always have at least two dimensions, implying that the result of a SegRed is always an array. |
| SegScan SegLevel SegSpace (Lambda lore) [SubExp] [Type] (KernelBody lore) | |
| SegGenRed SegLevel SegSpace [GenReduceOp lore] [Type] (KernelBody lore) |
Instances
At which level the *body* of a SegOp executes.
Constructors
| SegThread | |
Fields | |
| SegGroup | |
Fields | |
| SegThreadScalar | Like |
Fields | |
Do we need group-virtualisation when generating code for the
segmented operation? In most cases, we do, but for some simple
kernels, we compute the full number of groups in advance, and then
virtualisation is an unnecessary (but generally very small)
overhead. This only really matters for fairly trivial but very
wide map kernels where each thread performs constant-time work on
scalars.
typeCheckSegOp :: Checkable lore => Maybe SegLevel -> SegOp (Aliases lore) -> TypeM lore () Source #
Index space of a SegOp.
Constructors
| SegSpace | |
Fields
| |
scopeOfSegSpace :: SegSpace -> Scope lore Source #
segSpaceDims :: SegSpace -> [SubExp] Source #
Generic traversal
data SegOpMapper flore tlore m Source #
Constructors
| SegOpMapper | |
Fields
| |
identitySegOpMapper :: Monad m => SegOpMapper lore lore m Source #
A mapper that simply returns the SegOp verbatim.
mapSegOpM :: (Applicative m, Monad m) => SegOpMapper flore tlore m -> SegOp flore -> m (SegOp tlore) Source #
data SegOpWalker lore m Source #
Constructors
| SegOpWalker | |
Fields
| |
identitySegOpWalker :: Monad m => SegOpWalker lore m Source #
A no-op traversal.
walkSegOpM :: Monad m => SegOpWalker lore m -> SegOp lore -> m () Source #
As mapSegOpM, but ignoring the results.
Host operations
A host-level operation; parameterised by what else it can do.
Constructors
| SplitSpace SplitOrdering SubExp SubExp SubExp |
Computes how to divide array elements to threads in a kernel. Returns the number of elements in the chunk that the current thread should take.
If the order If the order |
| GetSize Name SizeClass | Produce some runtime-configurable size. |
| GetSizeMax SizeClass | The maximum size of some class. |
| CmpSizeLe Name SizeClass SubExp | Compare size (likely a threshold) with some Int32 value. |
| SegOp (SegOp lore) | A segmented operation. |
| OtherOp op |
Instances
typeCheckHostOp :: Checkable lore => (SegLevel -> OpWithAliases (Op lore) -> TypeM lore ()) -> Maybe SegLevel -> (op -> TypeM lore ()) -> HostOp (Aliases lore) op -> TypeM lore () Source #