Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Futhark.IR.GPU.Op
Synopsis
- data SizeOp
- data HostOp op rep
- traverseHostOpStms :: Monad m => OpStmsTraverser m (op rep) rep -> OpStmsTraverser m (HostOp op rep) rep
- typeCheckHostOp :: Checkable rep => (SegLevel -> Op (Aliases rep) -> TypeM rep ()) -> Maybe SegLevel -> (op (Aliases rep) -> TypeM rep ()) -> HostOp op (Aliases rep) -> TypeM rep ()
- data SegLevel
- segVirt :: SegLevel -> SegVirt
- data SegVirt
- newtype SegSeqDims = SegSeqDims {
- segSeqDims :: [Int]
- data KernelGrid = KernelGrid {}
- module Futhark.IR.GPU.Sizes
- module Futhark.IR.SegOp
Size operations
A simple size-level query or computation.
Constructors
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 integer value. |
CalcNumBlocks SubExp Name SubExp |
|
Host operations
A host-level operation; parameterised by what else it can do.
Constructors
SegOp (SegOp SegLevel rep) | A segmented operation. |
SizeOp SizeOp | |
OtherOp (op rep) | |
GPUBody [Type] (Body rep) | Code to run sequentially on the GPU, in a single thread. |
Instances
traverseHostOpStms :: Monad m => OpStmsTraverser m (op rep) rep -> OpStmsTraverser m (HostOp op rep) rep Source #
A helper for defining TraverseOpStms
.
typeCheckHostOp :: Checkable rep => (SegLevel -> Op (Aliases rep) -> TypeM rep ()) -> Maybe SegLevel -> (op (Aliases rep) -> TypeM rep ()) -> HostOp op (Aliases rep) -> TypeM rep () Source #
SegOp refinements
At which level the *body* of a SegOp
executes.
Constructors
SegThread SegVirt (Maybe KernelGrid) | |
SegBlock SegVirt (Maybe KernelGrid) | |
SegThreadInBlock SegVirt |
Instances
Show SegLevel Source # | |
FreeIn SegLevel Source # | |
Simplifiable SegLevel Source # | |
Defined in Futhark.IR.GPU.Op | |
Rename SegLevel Source # | |
Substitute SegLevel Source # | |
Defined in Futhark.IR.GPU.Op | |
Eq SegLevel Source # | |
Ord SegLevel Source # | |
Defined in Futhark.IR.GPU.Op | |
Pretty SegLevel Source # | |
Defined in Futhark.IR.GPU.Op |
Do we need block-virtualisation when generating code for the
segmented operation? In most cases, we do, but for some simple
kernels, we compute the full number of blocks 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.
Constructors
SegVirt | |
SegNoVirt | |
SegNoVirtFull SegSeqDims | Not only do we not need virtualisation, but we _guarantee_ that all physical threads participate in the work. This can save some checks in code generation. |
newtype SegSeqDims Source #
These dimensions (indexed from 0, outermost) of the corresponding
SegSpace
should not be parallelised, but instead iterated
sequentially. For example, with a SegSeqDims
of [0]
and a
SegSpace
with dimensions [n][m]
, there will be an outer loop
with n
iterations, while the m
dimension will be parallelised.
Semantically, this has no effect, but it may allow reductions in
memory usage or other low-level optimisations. Operationally, the
guarantee is that for a SegSeqDims of e.g. [i,j,k]
, threads
running at any given moment will always have the same indexes along
the dimensions specified by [i,j,k]
.
At the moment, this is only supported for SegNoVirtFull
intra-block parallelism in GPU code, as we have not yet found it
useful anywhere else.
Constructors
SegSeqDims | |
Fields
|
Instances
Show SegSeqDims Source # | |
Defined in Futhark.IR.GPU.Op Methods showsPrec :: Int -> SegSeqDims -> ShowS # show :: SegSeqDims -> String # showList :: [SegSeqDims] -> ShowS # | |
Eq SegSeqDims Source # | |
Defined in Futhark.IR.GPU.Op | |
Ord SegSeqDims Source # | |
Defined in Futhark.IR.GPU.Op Methods compare :: SegSeqDims -> SegSeqDims -> Ordering # (<) :: SegSeqDims -> SegSeqDims -> Bool # (<=) :: SegSeqDims -> SegSeqDims -> Bool # (>) :: SegSeqDims -> SegSeqDims -> Bool # (>=) :: SegSeqDims -> SegSeqDims -> Bool # max :: SegSeqDims -> SegSeqDims -> SegSeqDims # min :: SegSeqDims -> SegSeqDims -> SegSeqDims # |
data KernelGrid Source #
The actual, physical grid dimensions used for the GPU kernel
running this HostOp
.
Constructors
KernelGrid | |
Fields |
Instances
Reexports
module Futhark.IR.GPU.Sizes
module Futhark.IR.SegOp