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

Safe HaskellNone
LanguageHaskell2010

Futhark.Representation.Kernels.Kernel

Contents

Synopsis

Documentation

data Kernel lore Source #

Constructors

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.

Kernel KernelDebugHints KernelSpace [Type] (KernelBody lore) 
SegRed KernelSpace Commutativity (Lambda lore) [SubExp] [Type] (Body lore)

The KernelSpace must always have at least two dimensions, implying that the result of a SegRed is always an array.

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

Defined in Futhark.Representation.Kernels.Kernel

Methods

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

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

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

Defined in Futhark.Representation.Kernels.Kernel

Methods

compare :: Kernel lore -> Kernel lore -> Ordering #

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

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

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

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

max :: Kernel lore -> Kernel lore -> Kernel lore #

min :: Kernel lore -> Kernel lore -> Kernel lore #

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

Defined in Futhark.Representation.Kernels.Kernel

Methods

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

show :: Kernel lore -> String #

showList :: [Kernel lore] -> ShowS #

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

Defined in Futhark.Representation.Kernels.Kernel

Methods

ppr :: Kernel lore -> Doc #

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

pprList :: [Kernel lore] -> Doc #

(Attributes lore, FreeIn (LParamAttr lore)) => FreeIn (Kernel lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Methods

freeIn :: Kernel lore -> Names Source #

TypedOp (Kernel lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Methods

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

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

Defined in Futhark.Representation.Kernels.Kernel

Methods

substituteNames :: Map VName VName -> Kernel lore -> Kernel lore Source #

Attributes lore => Rename (Kernel lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Methods

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

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

Defined in Futhark.Representation.Kernels.Kernel

Methods

safeOp :: Kernel lore -> Bool Source #

cheapOp :: Kernel lore -> Bool Source #

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

Defined in Futhark.Representation.Kernels.Kernel

Associated Types

type OpWithAliases (Kernel lore) :: Type Source #

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

Defined in Futhark.Representation.Kernels.Kernel

Methods

opAliases :: Kernel lore -> [Names] Source #

consumedInOp :: Kernel lore -> Names Source #

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

Defined in Futhark.Representation.Kernels.Kernel

Methods

usageInOp :: Kernel lore -> UsageTable Source #

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

Defined in Futhark.Representation.Kernels.Kernel

Methods

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

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

Defined in Futhark.Representation.Kernels.Kernel

Associated Types

type OpWithRanges (Kernel lore) :: Type Source #

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

Defined in Futhark.Representation.Kernels.Kernel

Methods

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

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

Defined in Futhark.Representation.Kernels.Kernel

Associated Types

type OpWithWisdom (Kernel lore) :: Type Source #

Methods

removeOpWisdom :: OpWithWisdom (Kernel lore) -> Kernel lore Source #

Attributes lore => IndexOp (Kernel lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Methods

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

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

Defined in Futhark.Optimise.CSE

Methods

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

type OpWithAliases (Kernel lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

type OpWithAliases (Kernel lore) = Kernel (Aliases lore)
type OpWithRanges (Kernel lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

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

Defined in Futhark.Representation.Kernels.Kernel

type OpWithWisdom (Kernel lore) = Kernel (Wise lore)

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.

Constructors

KernelDebugHints 

Fields

data KernelBody lore Source #

The body of a Kernel.

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

Defined in Futhark.Representation.Kernels.Kernel

Methods

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

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

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

Defined in Futhark.Representation.Kernels.Kernel

Methods

compare :: KernelBody lore -> KernelBody lore -> Ordering #

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

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

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

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

max :: KernelBody lore -> KernelBody lore -> KernelBody lore #

min :: KernelBody lore -> KernelBody lore -> KernelBody lore #

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

Defined in Futhark.Representation.Kernels.Kernel

Methods

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

show :: KernelBody lore -> String #

showList :: [KernelBody lore] -> ShowS #

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

Defined in Futhark.Representation.Kernels.Kernel

Methods

ppr :: KernelBody lore -> Doc #

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

pprList :: [KernelBody lore] -> Doc #

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

Defined in Futhark.Representation.Kernels.Kernel

Methods

freeIn :: KernelBody lore -> Names Source #

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

Defined in Futhark.Representation.Kernels.Kernel

Attributes lore => Rename (KernelBody lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Methods

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

data KernelSpace Source #

first three bound in the kernel, the rest are params to kernel

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.

data WhichThreads Source #

Instances
Eq WhichThreads Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Ord WhichThreads Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Show WhichThreads Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

FreeIn WhichThreads Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Substitute WhichThreads Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Rename WhichThreads Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Simplifiable WhichThreads Source # 
Instance details

Defined in Futhark.Representation.Kernels.Simplify

data KernelResult Source #

Instances
Eq KernelResult Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Ord KernelResult Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Show KernelResult Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Pretty KernelResult Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

FreeIn KernelResult Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Substitute KernelResult Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Rename KernelResult Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Simplifiable KernelResult Source # 
Instance details

Defined in Futhark.Representation.Kernels.Simplify

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.

typeCheckKernel :: Checkable lore => Kernel (Aliases lore) -> TypeM lore () Source #

Generic traversal

data KernelMapper flore tlore m Source #

Like Mapper, but just for Kernels.

Constructors

KernelMapper 

Fields

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 #

Like Walker, but just for Kernels.

Constructors

KernelWalker 

Fields

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.