Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Futhark.CodeGen.ImpCode.GPU
Description
Variation of Futhark.CodeGen.ImpCode that contains the notion of a kernel invocation.
Synopsis
- type Program = Definitions HostOp
- type HostCode = Code HostOp
- type KernelCode = Code KernelOp
- data KernelConst
- type KernelConstExp = PrimExp KernelConst
- data HostOp
- data KernelOp
- data Fence
- data AtomicOp
- = AtomicAdd IntType VName VName (Count Elements (TExp Int64)) Exp
- | AtomicFAdd FloatType VName VName (Count Elements (TExp Int64)) Exp
- | AtomicSMax IntType VName VName (Count Elements (TExp Int64)) Exp
- | AtomicSMin IntType VName VName (Count Elements (TExp Int64)) Exp
- | AtomicUMax IntType VName VName (Count Elements (TExp Int64)) Exp
- | AtomicUMin IntType VName VName (Count Elements (TExp Int64)) Exp
- | AtomicAnd IntType VName VName (Count Elements (TExp Int64)) Exp
- | AtomicOr IntType VName VName (Count Elements (TExp Int64)) Exp
- | AtomicXor IntType VName VName (Count Elements (TExp Int64)) Exp
- | AtomicCmpXchg PrimType VName VName (Count Elements (TExp Int64)) Exp Exp
- | AtomicXchg PrimType VName VName (Count Elements (TExp Int64)) Exp
- | AtomicWrite PrimType VName (Count Elements (TExp Int64)) Exp
- type BlockDim = Either Exp KernelConstExp
- data Kernel = Kernel {}
- data KernelUse
- module Futhark.CodeGen.ImpCode
- module Futhark.IR.GPU.Sizes
Documentation
type Program = Definitions HostOp Source #
A program that calls kernels.
type KernelCode = Code KernelOp Source #
Code inside a kernel.
data KernelConst Source #
A run-time constant related to kernels.
Constructors
SizeConst Name SizeClass | |
SizeMaxConst SizeClass |
Instances
Show KernelConst Source # | |
Defined in Futhark.CodeGen.ImpCode.GPU Methods showsPrec :: Int -> KernelConst -> ShowS # show :: KernelConst -> String # showList :: [KernelConst] -> ShowS # | |
FreeIn KernelConst Source # | |
Defined in Futhark.CodeGen.ImpCode.GPU Methods freeIn' :: KernelConst -> FV Source # | |
Eq KernelConst Source # | |
Defined in Futhark.CodeGen.ImpCode.GPU | |
Ord KernelConst Source # | |
Defined in Futhark.CodeGen.ImpCode.GPU Methods compare :: KernelConst -> KernelConst -> Ordering # (<) :: KernelConst -> KernelConst -> Bool # (<=) :: KernelConst -> KernelConst -> Bool # (>) :: KernelConst -> KernelConst -> Bool # (>=) :: KernelConst -> KernelConst -> Bool # max :: KernelConst -> KernelConst -> KernelConst # min :: KernelConst -> KernelConst -> KernelConst # | |
Pretty KernelConst Source # | |
Defined in Futhark.CodeGen.ImpCode.GPU |
type KernelConstExp = PrimExp KernelConst Source #
An expression whose variables are kernel constants.
An operation that runs on the host (CPU).
Constructors
CallKernel Kernel | |
GetSize VName Name SizeClass | |
CmpSizeLe VName Name SizeClass Exp | |
GetSizeMax VName SizeClass |
An operation that occurs within a kernel body.
Constructors
GetBlockId VName Int | |
GetLocalId VName Int | |
GetLocalSize VName Int | |
GetLockstepWidth VName | |
Atomic Space AtomicOp | |
Barrier Fence | |
MemFence Fence | |
SharedAlloc VName (Count Bytes (TExp Int64)) | |
ErrorSync Fence | Perform a barrier and also check whether any
threads have failed an assertion. Make sure all
threads would reach all |
When we do a barrier or fence, is it at the local or global
level? By the Ord
instance, global is greater than local.
Constructors
FenceLocal | |
FenceGlobal |
Atomic operations return the value stored before the update. This
old value is stored in the first VName
(except for
AtomicWrite
). The second VName
is the memory block to update.
The Exp
is the new value.
Constructors
AtomicAdd IntType VName VName (Count Elements (TExp Int64)) Exp | |
AtomicFAdd FloatType VName VName (Count Elements (TExp Int64)) Exp | |
AtomicSMax IntType VName VName (Count Elements (TExp Int64)) Exp | |
AtomicSMin IntType VName VName (Count Elements (TExp Int64)) Exp | |
AtomicUMax IntType VName VName (Count Elements (TExp Int64)) Exp | |
AtomicUMin IntType VName VName (Count Elements (TExp Int64)) Exp | |
AtomicAnd IntType VName VName (Count Elements (TExp Int64)) Exp | |
AtomicOr IntType VName VName (Count Elements (TExp Int64)) Exp | |
AtomicXor IntType VName VName (Count Elements (TExp Int64)) Exp | |
AtomicCmpXchg PrimType VName VName (Count Elements (TExp Int64)) Exp Exp | |
AtomicXchg PrimType VName VName (Count Elements (TExp Int64)) Exp | |
AtomicWrite PrimType VName (Count Elements (TExp Int64)) Exp | Corresponds to a write followed by a memory fence. The old value is not read. |
A generic kernel containing arbitrary kernel code.
Constructors
Kernel | |
Fields
|
Information about a host-level variable that is used inside this kernel. When generating the actual kernel code, this is used to deduce which parameters are needed.
Instances
Show KernelUse Source # | |
Eq KernelUse Source # | |
Ord KernelUse Source # | |
Pretty KernelUse Source # | |
Defined in Futhark.CodeGen.ImpCode.GPU |
module Futhark.CodeGen.ImpCode
module Futhark.IR.GPU.Sizes