futhark-0.10.2: An optimising compiler for a functional, array-oriented language.

Safe HaskellNone
LanguageHaskell2010

Futhark.Representation.Kernels.KernelExp

Description

A representation of nested-parallel in-kernel per-workgroup expressions.

Synopsis

Documentation

data KernelExp lore Source #

Constructors

SplitSpace SplitOrdering SubExp SubExp SubExp

SplitSpace o w i elems_per_thread.

Computes how to divide array elements to threads in a kernel. Returns the number of elements in the chunk that the current thread should take.

w is the length of the outer dimension in the array. i is the current thread index. Each thread takes at most elems_per_thread elements.

If the order o is SplitContiguous, thread with index i should receive elements i*elems_per_tread, i*elems_per_thread + 1, ..., i*elems_per_thread + (elems_per_thread-1).

If the order o is SplitStrided stride, the thread will receive elements i, i+stride, i+2*stride, ..., i+(elems_per_thread-1)*stride.

Combine CombineSpace [Type] [(VName, SubExp)] (Body lore)

Combine cspace ts aspace body will combine values from threads to a single (multidimensional) array. If we define (is, ws) = unzip cspace, then ws is defined the same accross all threads. The cspace defines the shape of the resulting array, and the identifiers used to identify each individual element. Only threads for which all ((i,w) -> i < w) aspace is true will provide a value (of type ts), which is generated by body.

The result of a combine is always stored in local memory (OpenCL terminology)

The same thread may be assigned to multiple elements of Combine, if the size of the CombineSpace exceeds the group size.

GroupReduce SubExp (Lambda lore) [(SubExp, VName)]

GroupReduce w lam input (with (nes, arrs) = unzip input), will perform a reduction of the arrays arrs using the associative reduction operator lam and the neutral elements nes.

The arrays arrs must all have outer dimension w, which must not be larger than the group size.

Currently a GroupReduce consumes the input arrays, as it uses them for scratch space to store temporary results

All threads in a group must participate in a GroupReduce (due to barriers)

The length of the arrays w can be smaller than the number of elements in a group (neutral element will be filled in), but w can never be larger than the group size.

GroupScan SubExp (Lambda lore) [(SubExp, VName)]

Same restrictions as with GroupReduce.

GroupStream SubExp SubExp (GroupStreamLambda lore) [SubExp] [VName] 
GroupGenReduce [SubExp] [VName] (LambdaT lore) [SubExp] [SubExp] VName

GroupGenReduce length destarrays op bucket values arrays

Barrier [SubExp]

HACK: Semantically identity, but inserts a barrier afterwards. This reflects a weakness in our kernel representation.

Instances
Annotations lore => Eq (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Methods

(==) :: KernelExp lore -> KernelExp lore -> Bool #

(/=) :: KernelExp lore -> KernelExp lore -> Bool #

Annotations lore => Ord (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Methods

compare :: KernelExp lore -> KernelExp lore -> Ordering #

(<) :: KernelExp lore -> KernelExp lore -> Bool #

(<=) :: KernelExp lore -> KernelExp lore -> Bool #

(>) :: KernelExp lore -> KernelExp lore -> Bool #

(>=) :: KernelExp lore -> KernelExp lore -> Bool #

max :: KernelExp lore -> KernelExp lore -> KernelExp lore #

min :: KernelExp lore -> KernelExp lore -> KernelExp lore #

Annotations lore => Show (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Methods

showsPrec :: Int -> KernelExp lore -> ShowS #

show :: KernelExp lore -> String #

showList :: [KernelExp lore] -> ShowS #

PrettyLore lore => Pretty (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Methods

ppr :: KernelExp lore -> Doc #

pprPrec :: Int -> KernelExp lore -> Doc #

pprList :: [KernelExp lore] -> Doc #

Attributes lore => FreeIn (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Methods

freeIn :: KernelExp lore -> Names Source #

Attributes lore => TypedOp (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Methods

opType :: HasScope t m => KernelExp lore -> m [ExtType] Source #

Attributes lore => Substitute (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Renameable lore => Rename (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Methods

rename :: KernelExp lore -> RenameM (KernelExp lore) Source #

Attributes lore => IsOp (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Methods

safeOp :: KernelExp lore -> Bool Source #

cheapOp :: KernelExp lore -> Bool Source #

(Attributes lore, Attributes (Aliases lore), CanBeAliased (Op lore)) => CanBeAliased (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Associated Types

type OpWithAliases (KernelExp lore) :: Type Source #

(Attributes lore, Aliased lore) => AliasedOp (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Aliased lore => UsageInOp (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

OpMetrics (Op lore) => OpMetrics (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Methods

opMetrics :: KernelExp lore -> MetricsM () Source #

(Attributes lore, Attributes (Ranges lore), CanBeRanged (Op lore)) => CanBeRanged (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Associated Types

type OpWithRanges (KernelExp lore) :: Type Source #

Ranged inner => RangedOp (KernelExp inner) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Methods

opRanges :: KernelExp inner -> [Range] Source #

(Attributes lore, CanBeWise (Op lore)) => CanBeWise (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Associated Types

type OpWithWisdom (KernelExp lore) :: Type Source #

IndexOp (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Methods

indexOp :: (Attributes lore0, IndexOp (Op lore0)) => SymbolTable lore0 -> Int -> KernelExp lore -> [PrimExp VName] -> Maybe (PrimExp VName, Certificates) Source #

(Attributes lore, Aliased lore, CSEInOp (Op lore)) => CSEInOp (KernelExp lore) Source # 
Instance details

Defined in Futhark.Optimise.CSE

Methods

cseInOp :: KernelExp lore -> CSEM lore0 (KernelExp lore)

type OpWithAliases (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

type OpWithRanges (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

type OpWithRanges (KernelExp lore) = KernelExp (Ranges lore)
type OpWithWisdom (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

type OpWithWisdom (KernelExp lore) = KernelExp (Wise lore)

data GroupStreamLambda lore Source #

Instances
Scoped lore (GroupStreamLambda lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Methods

scopeOf :: GroupStreamLambda lore -> Scope lore Source #

Annotations lore => Eq (GroupStreamLambda lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Annotations lore => Ord (GroupStreamLambda lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Annotations lore => Show (GroupStreamLambda lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

PrettyLore lore => Pretty (GroupStreamLambda lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Attributes lore => FreeIn (GroupStreamLambda lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Attributes lore => Substitute (GroupStreamLambda lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Renameable lore => Rename (GroupStreamLambda lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

data SplitOrdering Source #

How an array is split into chunks.

Instances
Eq SplitOrdering Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Ord SplitOrdering Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Show SplitOrdering Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

FreeIn SplitOrdering Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Substitute SplitOrdering Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Rename SplitOrdering Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Simplifiable SplitOrdering Source # 
Instance details

Defined in Futhark.Representation.Kernels.Simplify

data CombineSpace Source #

A combine can be fully or partially in-place. The initial arrays here work like the ones from the Scatter SOAC.

Constructors

CombineSpace 

Fields