Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Futhark.IR.SegOp
Description
Segmented operations. These correspond to perfect map
nests on
top of something, except that the map
s are conceptually only
over iota
s (so there will be explicit indexing inside them).
Synopsis
- data SegOp lvl rep
- = SegMap lvl SegSpace [Type] (KernelBody rep)
- | SegRed lvl SegSpace [Type] (KernelBody rep) [SegBinOp rep]
- | SegScan lvl SegSpace [Type] (KernelBody rep) [SegBinOp rep]
- | SegHist lvl SegSpace [Type] (KernelBody rep) [HistOp rep]
- segLevel :: SegOp lvl rep -> lvl
- segBody :: SegOp lvl rep -> KernelBody rep
- segSpace :: SegOp lvl rep -> SegSpace
- typeCheckSegOp :: Checkable rep => (lvl -> TypeM rep ()) -> SegOp lvl (Aliases rep) -> TypeM rep ()
- data SegSpace = SegSpace {
- segFlat :: VName
- unSegSpace :: [(VName, SubExp)]
- scopeOfSegSpace :: SegSpace -> Scope rep
- segSpaceDims :: SegSpace -> [SubExp]
- data HistOp rep = HistOp {
- histShape :: Shape
- histRaceFactor :: SubExp
- histDest :: [VName]
- histNeutral :: [SubExp]
- histOpShape :: Shape
- histOp :: Lambda rep
- histType :: HistOp rep -> [Type]
- splitHistResults :: [HistOp rep] -> [SubExp] -> [([SubExp], [SubExp])]
- data SegBinOp rep = SegBinOp {
- segBinOpComm :: Commutativity
- segBinOpLambda :: Lambda rep
- segBinOpNeutral :: [SubExp]
- segBinOpShape :: Shape
- segBinOpResults :: [SegBinOp rep] -> Int
- segBinOpChunks :: [SegBinOp rep] -> [a] -> [[a]]
- data KernelBody rep = KernelBody {
- kernelBodyDec :: BodyDec rep
- kernelBodyStms :: Stms rep
- kernelBodyResult :: [KernelResult]
- aliasAnalyseKernelBody :: AliasableRep rep => AliasTable -> KernelBody rep -> KernelBody (Aliases rep)
- consumedInKernelBody :: Aliased rep => KernelBody rep -> Names
- data ResultManifest
- data KernelResult
- kernelResultCerts :: KernelResult -> Certs
- kernelResultSubExp :: KernelResult -> SubExp
- data SegOpMapper lvl frep trep m = SegOpMapper {
- mapOnSegOpSubExp :: SubExp -> m SubExp
- mapOnSegOpLambda :: Lambda frep -> m (Lambda trep)
- mapOnSegOpBody :: KernelBody frep -> m (KernelBody trep)
- mapOnSegOpVName :: VName -> m VName
- mapOnSegOpLevel :: lvl -> m lvl
- identitySegOpMapper :: Monad m => SegOpMapper lvl rep rep m
- mapSegOpM :: Monad m => SegOpMapper lvl frep trep m -> SegOp lvl frep -> m (SegOp lvl trep)
- traverseSegOpStms :: Monad m => OpStmsTraverser m (SegOp lvl rep) rep
- simplifySegOp :: (SimplifiableRep rep, BodyDec rep ~ (), Simplifiable lvl) => SegOp lvl (Wise rep) -> SimpleM rep (SegOp lvl (Wise rep), Stms (Wise rep))
- class HasSegOp rep where
- type SegOpLevel rep
- asSegOp :: Op rep -> Maybe (SegOp (SegOpLevel rep) rep)
- segOp :: SegOp (SegOpLevel rep) rep -> Op rep
- segOpRules :: (HasSegOp rep, BuilderOps rep, Buildable rep, Aliased rep) => RuleBook rep
- segOpReturns :: (Mem rep inner, Monad m, HasScope rep m) => SegOp lvl rep -> m [ExpReturns]
Documentation
A SegOp
is semantically a perfectly nested stack of maps, on
top of some bottommost computation (scalar computation, reduction,
scan, or histogram). The SegSpace
encodes the original map
structure.
All SegOp
s are parameterised by the representation of their body,
as well as a *level*. The *level* is a representation-specific bit
of information. For example, in GPU backends, it is used to
indicate whether the SegOp
is expected to run at the thread-level
or the block-level.
The type list is usually the type of the element returned by a
single thread. The result of the SegOp is then an array of that
type, with the shape of the SegSpace
prepended. One exception is
for WriteReturns
, where the type annotation is the full type of
the result.
Constructors
SegMap lvl SegSpace [Type] (KernelBody rep) | |
SegRed lvl SegSpace [Type] (KernelBody rep) [SegBinOp rep] | The KernelSpace must always have at least two dimensions, implying that the result of a SegRed is always an array. |
SegScan lvl SegSpace [Type] (KernelBody rep) [SegBinOp rep] | |
SegHist lvl SegSpace [Type] (KernelBody rep) [HistOp rep] |
Instances
typeCheckSegOp :: Checkable rep => (lvl -> TypeM rep ()) -> SegOp lvl (Aliases rep) -> TypeM rep () Source #
Type check a SegOp
, given a checker for its level.
Index space of a SegOp
.
Constructors
SegSpace | |
Fields
|
scopeOfSegSpace :: SegSpace -> Scope rep Source #
Details
An operator for SegHist
.
Constructors
HistOp | |
Fields
|
Instances
RepTypes rep => Show (HistOp rep) Source # | |
RepTypes rep => Eq (HistOp rep) Source # | |
RepTypes rep => Ord (HistOp rep) Source # | |
splitHistResults :: [HistOp rep] -> [SubExp] -> [([SubExp], [SubExp])] Source #
Split reduction results returned by a KernelBody
into those
that correspond to indexes for the HistOp
s, and those that
correspond to value.
Constructors
SegBinOp | |
Fields
|
Instances
RepTypes rep => Show (SegBinOp rep) Source # | |
RepTypes rep => Eq (SegBinOp rep) Source # | |
RepTypes rep => Ord (SegBinOp rep) Source # | |
Defined in Futhark.IR.SegOp | |
PrettyRep rep => Pretty (SegBinOp rep) Source # | |
Defined in Futhark.IR.SegOp |
segBinOpResults :: [SegBinOp rep] -> Int Source #
How many reduction results are produced by these SegBinOp
s?
segBinOpChunks :: [SegBinOp rep] -> [a] -> [[a]] Source #
Split some list into chunks equal to the number of values
returned by each SegBinOp
data KernelBody rep Source #
The body of a SegOp
.
Constructors
KernelBody | |
Fields
|
Instances
aliasAnalyseKernelBody :: AliasableRep rep => AliasTable -> KernelBody rep -> KernelBody (Aliases rep) Source #
Perform alias analysis on a KernelBody
.
consumedInKernelBody :: Aliased rep => KernelBody rep -> Names Source #
The variables consumed in the kernel body.
data ResultManifest Source #
Metadata about whether there is a subtle point to this
KernelResult
. This is used to protect things like tiling, which
might otherwise be removed by the simplifier because they're
semantically redundant. This has no semantic effect and can be
ignored at code generation.
Constructors
ResultNoSimplify | Don't simplify this one! |
ResultMaySimplify | Go nuts. |
ResultPrivate | The results produced are only used within the same physical thread later on, and can thus be kept in registers. |
Instances
Show ResultManifest Source # | |
Defined in Futhark.IR.SegOp Methods showsPrec :: Int -> ResultManifest -> ShowS # show :: ResultManifest -> String # showList :: [ResultManifest] -> ShowS # | |
Eq ResultManifest Source # | |
Defined in Futhark.IR.SegOp Methods (==) :: ResultManifest -> ResultManifest -> Bool # (/=) :: ResultManifest -> ResultManifest -> Bool # | |
Ord ResultManifest Source # | |
Defined in Futhark.IR.SegOp Methods compare :: ResultManifest -> ResultManifest -> Ordering # (<) :: ResultManifest -> ResultManifest -> Bool # (<=) :: ResultManifest -> ResultManifest -> Bool # (>) :: ResultManifest -> ResultManifest -> Bool # (>=) :: ResultManifest -> ResultManifest -> Bool # max :: ResultManifest -> ResultManifest -> ResultManifest # min :: ResultManifest -> ResultManifest -> ResultManifest # |
data KernelResult Source #
A KernelBody
does not return an ordinary Result
. Instead, it
returns a list of these.
Constructors
Returns ResultManifest Certs SubExp | Each "worker" in the kernel returns this.
Whether this is a result-per-thread or a
result-per-block depends on where the |
WriteReturns Certs VName [(Slice SubExp, SubExp)] | |
TileReturns Certs [(SubExp, SubExp)] VName | |
RegTileReturns Certs [(SubExp, SubExp, SubExp)] VName |
Instances
kernelResultCerts :: KernelResult -> Certs Source #
Get the certs for this KernelResult
.
kernelResultSubExp :: KernelResult -> SubExp Source #
Get the root SubExp
corresponding values for a KernelResult
.
Generic traversal
data SegOpMapper lvl frep trep m Source #
Constructors
SegOpMapper | |
Fields
|
identitySegOpMapper :: Monad m => SegOpMapper lvl rep rep m Source #
A mapper that simply returns the SegOp
verbatim.
mapSegOpM :: Monad m => SegOpMapper lvl frep trep m -> SegOp lvl frep -> m (SegOp lvl trep) Source #
Apply a SegOpMapper
to the given SegOp
.
traverseSegOpStms :: Monad m => OpStmsTraverser m (SegOp lvl rep) rep Source #
A helper for defining TraverseOpStms
.
Simplification
simplifySegOp :: (SimplifiableRep rep, BodyDec rep ~ (), Simplifiable lvl) => SegOp lvl (Wise rep) -> SimpleM rep (SegOp lvl (Wise rep), Stms (Wise rep)) Source #
Simplify the given SegOp
.
class HasSegOp rep where Source #
Does this rep contain SegOp
s in its Op
s? A rep must be an
instance of this class for the simplification rules to work.
Associated Types
type SegOpLevel rep Source #
segOpRules :: (HasSegOp rep, BuilderOps rep, Buildable rep, Aliased rep) => RuleBook rep Source #
Simplification rules for simplifying SegOp
s.
Memory
segOpReturns :: (Mem rep inner, Monad m, HasScope rep m) => SegOp lvl rep -> m [ExpReturns] Source #
Like segOpType
, but for memory representations.