Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Kernel lore
- = Kernel KernelDebugHints KernelSpace [Type] (KernelBody lore)
- | SegMap KernelSpace [Type] (KernelBody lore)
- | SegRed KernelSpace [SegRedOp lore] [Type] (KernelBody lore)
- | SegScan KernelSpace (Lambda lore) [SubExp] [Type] (KernelBody lore)
- | SegGenRed KernelSpace [GenReduceOp lore] [Type] (KernelBody lore)
- kernelType :: Kernel lore -> [Type]
- kernelSpace :: Kernel lore -> KernelSpace
- data KernelDebugHints = KernelDebugHints {
- kernelName :: String
- kernelHints :: [(String, SubExp)]
- 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 KernelSpace = KernelSpace {}
- spaceDimensions :: KernelSpace -> [(VName, SubExp)]
- data SpaceStructure
- = FlatThreadSpace [(VName, SubExp)]
- | NestedThreadSpace [(VName, SubExp, VName, SubExp)]
- scopeOfKernelSpace :: KernelSpace -> Scope lore
- data KernelResult
- kernelResultSubExp :: KernelResult -> SubExp
- type KernelPath = [(Name, Bool)]
- chunkedKernelNonconcatOutputs :: Lambda lore -> Int
- typeCheckKernel :: Checkable lore => Kernel (Aliases lore) -> TypeM lore ()
- data KernelMapper flore tlore m = KernelMapper {
- mapOnKernelSubExp :: SubExp -> m SubExp
- mapOnKernelLambda :: Lambda flore -> m (Lambda tlore)
- mapOnKernelBody :: Body flore -> m (Body tlore)
- mapOnKernelVName :: VName -> m VName
- mapOnKernelLParam :: LParam flore -> m (LParam tlore)
- mapOnKernelKernelBody :: KernelBody flore -> m (KernelBody tlore)
- identityKernelMapper :: Monad m => KernelMapper lore lore m
- mapKernelM :: (Applicative m, Monad m) => KernelMapper flore tlore m -> Kernel flore -> m (Kernel tlore)
- data KernelWalker lore m = KernelWalker {
- walkOnKernelSubExp :: SubExp -> m ()
- walkOnKernelLambda :: Lambda lore -> m ()
- walkOnKernelBody :: Body lore -> m ()
- walkOnKernelVName :: VName -> m ()
- walkOnKernelLParam :: LParam lore -> m ()
- walkOnKernelKernelBody :: KernelBody lore -> m ()
- identityKernelWalker :: Monad m => KernelWalker lore m
- walkKernelM :: Monad m => KernelWalker lore m -> Kernel lore -> m ()
- data HostOp lore inner
- typeCheckHostOp :: Checkable lore => (inner -> TypeM lore ()) -> HostOp (Aliases lore) inner -> TypeM lore ()
Documentation
Kernel KernelDebugHints KernelSpace [Type] (KernelBody lore) | |
SegMap KernelSpace [Type] (KernelBody lore) | |
SegRed KernelSpace [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 KernelSpace (Lambda lore) [SubExp] [Type] (KernelBody lore) | |
SegGenRed KernelSpace [GenReduceOp lore] [Type] (KernelBody lore) |
Instances
kernelType :: Kernel lore -> [Type] Source #
kernelSpace :: Kernel lore -> KernelSpace Source #
data KernelDebugHints Source #
Some information about what goes into a kernel, and where it came from. Has no semantic meaning; only used for debugging generated code.
KernelDebugHints | |
|
Instances
Eq KernelDebugHints Source # | |
Defined in Futhark.Representation.Kernels.Kernel (==) :: KernelDebugHints -> KernelDebugHints -> Bool # (/=) :: KernelDebugHints -> KernelDebugHints -> Bool # | |
Ord KernelDebugHints Source # | |
Defined in Futhark.Representation.Kernels.Kernel compare :: KernelDebugHints -> KernelDebugHints -> Ordering # (<) :: KernelDebugHints -> KernelDebugHints -> Bool # (<=) :: KernelDebugHints -> KernelDebugHints -> Bool # (>) :: KernelDebugHints -> KernelDebugHints -> Bool # (>=) :: KernelDebugHints -> KernelDebugHints -> Bool # max :: KernelDebugHints -> KernelDebugHints -> KernelDebugHints # min :: KernelDebugHints -> KernelDebugHints -> KernelDebugHints # | |
Show KernelDebugHints Source # | |
Defined in Futhark.Representation.Kernels.Kernel showsPrec :: Int -> KernelDebugHints -> ShowS # show :: KernelDebugHints -> String # showList :: [KernelDebugHints] -> ShowS # |
data GenReduceOp lore Source #
GenReduceOp | |
|
Instances
Annotations lore => Eq (GenReduceOp lore) Source # | |
Defined in Futhark.Representation.Kernels.Kernel (==) :: GenReduceOp lore -> GenReduceOp lore -> Bool # (/=) :: GenReduceOp lore -> GenReduceOp lore -> Bool # | |
Annotations lore => Ord (GenReduceOp lore) Source # | |
Defined in Futhark.Representation.Kernels.Kernel 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 showsPrec :: Int -> GenReduceOp lore -> ShowS # show :: GenReduceOp lore -> String # showList :: [GenReduceOp lore] -> ShowS # |
SegRedOp | |
|
Instances
Annotations lore => Eq (SegRedOp lore) Source # | |
Annotations lore => Ord (SegRedOp lore) Source # | |
Defined in Futhark.Representation.Kernels.Kernel 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 SegRedOp
s?
data KernelBody lore Source #
The body of a Kernel
.
KernelBody | |
|
Instances
data KernelSpace Source #
first three bound in the kernel, the rest are params to kernel
Instances
spaceDimensions :: KernelSpace -> [(VName, SubExp)] Source #
Global thread IDs and their upper bound.
data SpaceStructure Source #
Indices computed for each thread (or group) inside the kernel. This is an arbitrary-dimensional space that is generated from the flat GPU thread space.
FlatThreadSpace [(VName, SubExp)] | |
NestedThreadSpace [(VName, SubExp, VName, SubExp)] |
Instances
scopeOfKernelSpace :: KernelSpace -> Scope lore Source #
data KernelResult Source #
ThreadsReturn SubExp | Each thread in the kernel space (which must be non-empty) returns this. |
GroupsReturn SubExp | Each group returns this. |
WriteReturn [SubExp] VName [([SubExp], SubExp)] | |
ConcatReturns SplitOrdering SubExp SubExp (Maybe SubExp) VName |
Instances
type KernelPath = [(Name, Bool)] Source #
An indication of which comparisons have been performed to get to this point, as well as the result of each comparison.
chunkedKernelNonconcatOutputs :: Lambda lore -> Int Source #
Generic traversal
data KernelMapper flore tlore m Source #
KernelMapper | |
|
identityKernelMapper :: Monad m => KernelMapper lore lore m Source #
A mapper that simply returns the Kernel
verbatim.
mapKernelM :: (Applicative m, Monad m) => KernelMapper flore tlore m -> Kernel flore -> m (Kernel tlore) Source #
Map a monadic action across the immediate children of a Kernel. The mapping does not descend recursively into subexpressions and is done left-to-right.
data KernelWalker lore m Source #
KernelWalker | |
|
identityKernelWalker :: Monad m => KernelWalker lore m Source #
A no-op traversal.
walkKernelM :: Monad m => KernelWalker lore m -> Kernel lore -> m () Source #
As mapKernelM
, but ignoring the results.
Host operations
data HostOp lore inner Source #
A host-level operation; parameterised by what else it can do.
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. |
HostOp inner | The arbitrary operation. |