futhark-0.16.1: An optimising compiler for a functional, array-oriented language.
Safe HaskellNone
LanguageHaskell2010

Futhark.IR.SegOp

Description

Segmented operations. These correspond to perfect map nests on top of something, except that the maps are conceptually only over iotas (so there will be explicit indexing inside them).

Synopsis

Documentation

data SegOp lvl lore Source #

A SegOp is semantically a perfectly nested stack of maps, on top of some bottommost computation (scalar computation, reduction, scan, or histogram). The SegSpace encodes the original map structure.

All SegOps are parameterised by the representation of their body, as well as a *level*. The *level* is a representation-specific bit of information. For example, in GPU backends, it is used to indicate whether the SegOp is expected to run at the thread-level or the group-level.

Constructors

SegMap lvl SegSpace [Type] (KernelBody lore) 
SegRed lvl SegSpace [SegBinOp 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 lvl SegSpace [SegBinOp lore] [Type] (KernelBody lore) 
SegHist lvl SegSpace [HistOp lore] [Type] (KernelBody lore) 

Instances

Instances details
(Decorations lore, Eq lvl) => Eq (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

(==) :: SegOp lvl lore -> SegOp lvl lore -> Bool #

(/=) :: SegOp lvl lore -> SegOp lvl lore -> Bool #

(Decorations lore, Ord lvl) => Ord (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

compare :: SegOp lvl lore -> SegOp lvl lore -> Ordering #

(<) :: SegOp lvl lore -> SegOp lvl lore -> Bool #

(<=) :: SegOp lvl lore -> SegOp lvl lore -> Bool #

(>) :: SegOp lvl lore -> SegOp lvl lore -> Bool #

(>=) :: SegOp lvl lore -> SegOp lvl lore -> Bool #

max :: SegOp lvl lore -> SegOp lvl lore -> SegOp lvl lore #

min :: SegOp lvl lore -> SegOp lvl lore -> SegOp lvl lore #

(Decorations lore, Show lvl) => Show (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

showsPrec :: Int -> SegOp lvl lore -> ShowS #

show :: SegOp lvl lore -> String #

showList :: [SegOp lvl lore] -> ShowS #

(PrettyLore lore, Pretty lvl) => Pretty (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

ppr :: SegOp lvl lore -> Doc #

pprPrec :: Int -> SegOp lvl lore -> Doc #

pprList :: [SegOp lvl lore] -> Doc #

TypedOp (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

(ASTLore lore, FreeIn (LParamInfo lore), FreeIn lvl) => FreeIn (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

freeIn' :: SegOp lvl lore -> FV Source #

(ASTLore lore, Substitute lvl) => Substitute (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

substituteNames :: Map VName VName -> SegOp lvl lore -> SegOp lvl lore Source #

(ASTLore lore, ASTConstraints lvl) => Rename (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

rename :: SegOp lvl lore -> RenameM (SegOp lvl lore) Source #

(ASTLore lore, ASTConstraints lvl) => IsOp (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

safeOp :: SegOp lvl lore -> Bool Source #

cheapOp :: SegOp lvl lore -> Bool Source #

(ASTLore lore, ASTLore (Aliases lore), CanBeAliased (Op lore), ASTConstraints lvl) => CanBeAliased (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Associated Types

type OpWithAliases (SegOp lvl lore) Source #

Methods

removeOpAliases :: OpWithAliases (SegOp lvl lore) -> SegOp lvl lore Source #

addOpAliases :: SegOp lvl lore -> OpWithAliases (SegOp lvl lore) Source #

(ASTLore lore, Aliased lore, ASTConstraints lvl) => AliasedOp (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

opAliases :: SegOp lvl lore -> [Names] Source #

consumedInOp :: SegOp lvl lore -> Names Source #

OpMetrics (Op lore) => OpMetrics (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

opMetrics :: SegOp lvl lore -> MetricsM () Source #

(CanBeWise (Op lore), ASTLore lore, ASTConstraints lvl) => CanBeWise (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Associated Types

type OpWithWisdom (SegOp lvl lore) Source #

Methods

removeOpWisdom :: OpWithWisdom (SegOp lvl lore) -> SegOp lvl lore Source #

ASTLore lore => IndexOp (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

indexOp :: (ASTLore lore0, IndexOp (Op lore0)) => SymbolTable lore0 -> Int -> SegOp lvl lore -> [PrimExp VName] -> Maybe Indexed Source #

SizeSubst (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.Pass.ExplicitAllocations.Kernels

Methods

opSizeSubst :: PatternT dec -> SegOp lvl lore -> ChunkMap Source #

opIsConst :: SegOp lvl lore -> Bool Source #

(ASTLore lore, Aliased lore, CSEInOp (Op lore)) => CSEInOp (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.Optimise.CSE

Methods

cseInOp :: SegOp lvl lore -> CSEM lore0 (SegOp lvl lore)

type OpWithAliases (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

type OpWithAliases (SegOp lvl lore) = SegOp lvl (Aliases lore)
type OpWithWisdom (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

type OpWithWisdom (SegOp lvl lore) = SegOp lvl (Wise lore)

data SegVirt Source #

Do we need group-virtualisation when generating code for the segmented operation? In most cases, we do, but for some simple kernels, we compute the full number of groups in advance, and then virtualisation is an unnecessary (but generally very small) overhead. This only really matters for fairly trivial but very wide map kernels where each thread performs constant-time work on scalars.

Constructors

SegVirt 
SegNoVirt 
SegNoVirtFull

Not only do we not need virtualisation, but we _guarantee_ that all physical threads participate in the work. This can save some checks in code generation.

Instances

Instances details
Eq SegVirt Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

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

Ord SegVirt Source # 
Instance details

Defined in Futhark.IR.SegOp

Show SegVirt Source # 
Instance details

Defined in Futhark.IR.SegOp

segLevel :: SegOp lvl lore -> lvl Source #

The level of a SegOp.

segSpace :: SegOp lvl lore -> SegSpace Source #

The space of a SegOp.

typeCheckSegOp :: Checkable lore => (lvl -> TypeM lore ()) -> SegOp lvl (Aliases lore) -> TypeM lore () Source #

Type check a SegOp, given a checker for its level.

data SegSpace Source #

Index space of a SegOp.

Constructors

SegSpace 

Fields

Instances

Instances details
Eq SegSpace Source # 
Instance details

Defined in Futhark.IR.SegOp

Ord SegSpace Source # 
Instance details

Defined in Futhark.IR.SegOp

Show SegSpace Source # 
Instance details

Defined in Futhark.IR.SegOp

Pretty SegSpace Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

ppr :: SegSpace -> Doc #

pprPrec :: Int -> SegSpace -> Doc #

pprList :: [SegSpace] -> Doc #

Simplifiable SegSpace Source # 
Instance details

Defined in Futhark.IR.SegOp

scopeOfSegSpace :: SegSpace -> Scope lore Source #

A Scope containing all the identifiers brought into scope by this SegSpace.

segSpaceDims :: SegSpace -> [SubExp] Source #

The sizes spanned by the indexes of the SegSpace.

Details

data HistOp lore Source #

An operator for SegHist.

Constructors

HistOp 

Fields

Instances

Instances details
Decorations lore => Eq (HistOp lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

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

Decorations lore => Ord (HistOp lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

compare :: HistOp lore -> HistOp lore -> Ordering #

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

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

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

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

max :: HistOp lore -> HistOp lore -> HistOp lore #

min :: HistOp lore -> HistOp lore -> HistOp lore #

Decorations lore => Show (HistOp lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

show :: HistOp lore -> String #

showList :: [HistOp lore] -> ShowS #

histType :: HistOp lore -> [Type] Source #

The type of a histogram produced by a HistOp. This can be different from the type of the histDests in case we are dealing with a segmented histogram.

data SegBinOp lore Source #

An operator for SegScan and SegRed.

Constructors

SegBinOp 

Fields

Instances

Instances details
Decorations lore => Eq (SegBinOp lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

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

Decorations lore => Ord (SegBinOp lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

compare :: SegBinOp lore -> SegBinOp lore -> Ordering #

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

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

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

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

max :: SegBinOp lore -> SegBinOp lore -> SegBinOp lore #

min :: SegBinOp lore -> SegBinOp lore -> SegBinOp lore #

Decorations lore => Show (SegBinOp lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

show :: SegBinOp lore -> String #

showList :: [SegBinOp lore] -> ShowS #

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

Defined in Futhark.IR.SegOp

Methods

ppr :: SegBinOp lore -> Doc #

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

pprList :: [SegBinOp lore] -> Doc #

segBinOpResults :: [SegBinOp lore] -> Int Source #

How many reduction results are produced by these SegBinOps?

segBinOpChunks :: [SegBinOp lore] -> [a] -> [[a]] Source #

Split some list into chunks equal to the number of values returned by each SegBinOp

data KernelBody lore Source #

The body of a SegOp.

Instances

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

Defined in Futhark.IR.SegOp

Methods

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

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

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

Defined in Futhark.IR.SegOp

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 #

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

Defined in Futhark.IR.SegOp

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.IR.SegOp

Methods

ppr :: KernelBody lore -> Doc #

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

pprList :: [KernelBody lore] -> Doc #

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

Defined in Futhark.IR.SegOp

Methods

freeIn' :: KernelBody lore -> FV Source #

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

Defined in Futhark.IR.SegOp

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

Defined in Futhark.IR.SegOp

Methods

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

aliasAnalyseKernelBody :: (ASTLore lore, CanBeAliased (Op lore)) => KernelBody lore -> KernelBody (Aliases lore) Source #

Perform alias analysis on a KernelBody.

consumedInKernelBody :: Aliased lore => KernelBody lore -> Names Source #

The variables consumed in the kernel body.

data ResultManifest Source #

Metadata about whether there is a subtle point to this KernelResult. This is used to protect things like tiling, which might otherwise be removed by the simplifier because they're semantically redundant. This has no semantic effect and can be ignored at code generation.

Constructors

ResultNoSimplify

Don't simplify this one!

ResultMaySimplify

Go nuts.

ResultPrivate

The results produced are only used within the same physical thread later on, and can thus be kept in registers.

data KernelResult Source #

A KernelBody does not return an ordinary Result. Instead, it returns a list of these.

Constructors

Returns ResultManifest SubExp

Each "worker" in the kernel returns this. Whether this is a result-per-thread or a result-per-group depends on where the SegOp occurs.

WriteReturns [SubExp] VName [(Slice SubExp, SubExp)] 
ConcatReturns SplitOrdering SubExp SubExp VName 
TileReturns [(SubExp, SubExp)] VName 

Instances

Instances details
Eq KernelResult Source # 
Instance details

Defined in Futhark.IR.SegOp

Ord KernelResult Source # 
Instance details

Defined in Futhark.IR.SegOp

Show KernelResult Source # 
Instance details

Defined in Futhark.IR.SegOp

Pretty KernelResult Source # 
Instance details

Defined in Futhark.IR.SegOp

FreeIn KernelResult Source # 
Instance details

Defined in Futhark.IR.SegOp

Substitute KernelResult Source # 
Instance details

Defined in Futhark.IR.SegOp

Rename KernelResult Source # 
Instance details

Defined in Futhark.IR.SegOp

Simplifiable KernelResult Source # 
Instance details

Defined in Futhark.IR.SegOp

kernelResultSubExp :: KernelResult -> SubExp Source #

Get the root SubExp corresponding values for a KernelResult.

data SplitOrdering Source #

How an array is split into chunks.

Generic traversal

data SegOpMapper lvl flore tlore m Source #

Like Mapper, but just for SegOps.

Constructors

SegOpMapper 

Fields

identitySegOpMapper :: Monad m => SegOpMapper lvl lore lore m Source #

A mapper that simply returns the SegOp verbatim.

mapSegOpM :: (Applicative m, Monad m) => SegOpMapper lvl flore tlore m -> SegOp lvl flore -> m (SegOp lvl tlore) Source #

Apply a SegOpMapper to the given SegOp.

Simplification

simplifySegOp :: (SimplifiableLore lore, BodyDec lore ~ (), Simplifiable lvl) => SegOp lvl lore -> SimpleM lore (SegOp lvl (Wise lore), Stms (Wise lore)) Source #

Simplify the given SegOp.

class HasSegOp lore where Source #

Does this lore contain SegOps in its Ops? A lore must be an instance of this class for the simplification rules to work.

Associated Types

type SegOpLevel lore Source #

Methods

asSegOp :: Op lore -> Maybe (SegOp (SegOpLevel lore) lore) Source #

segOp :: SegOp (SegOpLevel lore) lore -> Op lore Source #

segOpRules :: (HasSegOp lore, BinderOps lore, Bindable lore) => RuleBook lore Source #

Simplification rules for simplifying SegOps.

Memory

segOpReturns :: (Mem lore, Monad m, HasScope lore m) => SegOp lvl lore -> m [ExpReturns] Source #

Like segOpType, but for memory representations.