futhark-0.25.23: An optimising compiler for a functional, array-oriented language.
Safe HaskellSafe-Inferred
LanguageGHC2021

Futhark.CodeGen.ImpCode.GPU

Description

Variation of Futhark.CodeGen.ImpCode that contains the notion of a kernel invocation.

Synopsis

Documentation

type Program = Definitions HostOp Source #

A program that calls kernels.

type HostCode = Code HostOp Source #

Host-level code that can call kernels.

type KernelCode = Code KernelOp Source #

Code inside a kernel.

type KernelConstExp = PrimExp KernelConst Source #

An expression whose variables are kernel constants.

data HostOp Source #

An operation that runs on the host (CPU).

Instances

Instances details
Show HostOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

FreeIn HostOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

Methods

freeIn' :: HostOp -> FV Source #

Pretty HostOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

Methods

pretty :: HostOp -> Doc ann #

prettyList :: [HostOp] -> Doc ann #

data KernelOp Source #

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 ErrorSyncs if any of them do. A failing assertion will jump to the next following ErrorSync, so make sure it's not inside control flow or similar.

Instances

Instances details
Show KernelOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

FreeIn KernelOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

Methods

freeIn' :: KernelOp -> FV Source #

Pretty KernelOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

Methods

pretty :: KernelOp -> Doc ann #

prettyList :: [KernelOp] -> Doc ann #

data Fence Source #

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 

Instances

Instances details
Show Fence Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

Methods

showsPrec :: Int -> Fence -> ShowS #

show :: Fence -> String #

showList :: [Fence] -> ShowS #

Eq Fence Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

Methods

(==) :: Fence -> Fence -> Bool #

(/=) :: Fence -> Fence -> Bool #

Ord Fence Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

Methods

compare :: Fence -> Fence -> Ordering #

(<) :: Fence -> Fence -> Bool #

(<=) :: Fence -> Fence -> Bool #

(>) :: Fence -> Fence -> Bool #

(>=) :: Fence -> Fence -> Bool #

max :: Fence -> Fence -> Fence #

min :: Fence -> Fence -> Fence #

data AtomicOp Source #

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.

Instances

Instances details
Show AtomicOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

FreeIn AtomicOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

Methods

freeIn' :: AtomicOp -> FV Source #

type BlockDim = Either Exp KernelConstExp Source #

The size of one dimension of a block.

data Kernel Source #

A generic kernel containing arbitrary kernel code.

Constructors

Kernel 

Fields

  • kernelBody :: Code KernelOp
     
  • kernelUses :: [KernelUse]

    The host variables referenced by the kernel.

  • kernelNumBlocks :: [Exp]
     
  • kernelBlockSize :: [BlockDim]
     
  • kernelName :: Name

    A short descriptive and _unique_ name - should be alphanumeric and without spaces.

  • kernelFailureTolerant :: Bool

    If true, this kernel does not need to check whether we are in a failing state, as it can cope. Intuitively, it means that the kernel does not depend on any non-scalar parameters to make control flow decisions. Replication, transpose, and copy kernels are examples of this.

  • kernelCheckSharedMemory :: Bool

    If true, multi-versioning branches will consider this kernel when considering the shared memory requirements. Set this to false for kernels that do their own checking.

Instances

Instances details
Show Kernel Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

FreeIn Kernel Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

Methods

freeIn' :: Kernel -> FV Source #

Pretty Kernel Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.GPU

Methods

pretty :: Kernel -> Doc ann #

prettyList :: [Kernel] -> Doc ann #

data KernelUse Source #

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.