futhark-0.20.2: 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 rep 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 rep) 
SegRed lvl SegSpace [SegBinOp rep] [Type] (KernelBody rep)

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

SegScan lvl SegSpace [SegBinOp rep] [Type] (KernelBody rep) 
SegHist lvl SegSpace [HistOp rep] [Type] (KernelBody rep) 

Instances

Instances details
(RepTypes rep, Eq lvl) => Eq (SegOp lvl rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

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

(RepTypes rep, Ord lvl) => Ord (SegOp lvl rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

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

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

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

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

max :: SegOp lvl rep -> SegOp lvl rep -> SegOp lvl rep #

min :: SegOp lvl rep -> SegOp lvl rep -> SegOp lvl rep #

(RepTypes rep, Show lvl) => Show (SegOp lvl rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

show :: SegOp lvl rep -> String #

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

(PrettyRep rep, Pretty lvl) => Pretty (SegOp lvl rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

ppr :: SegOp lvl rep -> Doc #

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

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

TypedOp (SegOp lvl rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

(ASTRep rep, FreeIn (LParamInfo rep), FreeIn lvl) => FreeIn (SegOp lvl rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

(ASTRep rep, Substitute lvl) => Substitute (SegOp lvl rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

(ASTRep rep, ASTConstraints lvl) => Rename (SegOp lvl rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

(ASTRep rep, ASTConstraints lvl) => IsOp (SegOp lvl rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

safeOp :: SegOp lvl rep -> Bool Source #

cheapOp :: SegOp lvl rep -> Bool Source #

(ASTRep rep, ASTRep (Aliases rep), CanBeAliased (Op rep), ASTConstraints lvl) => CanBeAliased (SegOp lvl rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Associated Types

type OpWithAliases (SegOp lvl rep) Source #

Methods

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

addOpAliases :: AliasTable -> SegOp lvl rep -> OpWithAliases (SegOp lvl rep) Source #

(ASTRep rep, Aliased rep, ASTConstraints lvl) => AliasedOp (SegOp lvl rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

consumedInOp :: SegOp lvl rep -> Names Source #

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

Defined in Futhark.IR.SegOp

Methods

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

(CanBeWise (Op rep), ASTRep rep, ASTConstraints lvl) => CanBeWise (SegOp lvl rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Associated Types

type OpWithWisdom (SegOp lvl rep) Source #

Methods

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

ASTRep rep => IndexOp (SegOp lvl rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

indexOp :: (ASTRep rep0, IndexOp (Op rep0)) => SymbolTable rep0 -> Int -> SegOp lvl rep -> [TPrimExp Int64 VName] -> Maybe Indexed Source #

SizeSubst (SegOp lvl rep) Source # 
Instance details

Defined in Futhark.Pass.ExplicitAllocations.SegOp

Methods

opSizeSubst :: PatT dec -> SegOp lvl rep -> ChunkMap Source #

opIsConst :: SegOp lvl rep -> Bool Source #

(ASTRep rep, Aliased rep, CSEInOp (Op rep)) => CSEInOp (SegOp lvl rep) Source # 
Instance details

Defined in Futhark.Optimise.CSE

Methods

cseInOp :: SegOp lvl rep -> CSEM rep0 (SegOp lvl rep)

type OpWithAliases (SegOp lvl rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

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

Defined in Futhark.IR.SegOp

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

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 rep -> lvl Source #

The level of a SegOp.

segBody :: SegOp lvl rep -> KernelBody rep Source #

The body of a SegOp.

segSpace :: SegOp lvl rep -> SegSpace Source #

The space of a SegOp.

typeCheckSegOp :: Checkable rep => (lvl -> TypeM rep ()) -> SegOp lvl (Aliases rep) -> TypeM rep () 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 rep 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 rep Source #

An operator for SegHist.

Constructors

HistOp 

Fields

Instances

Instances details
RepTypes rep => Eq (HistOp rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

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

RepTypes rep => Ord (HistOp rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

compare :: HistOp rep -> HistOp rep -> Ordering #

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

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

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

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

max :: HistOp rep -> HistOp rep -> HistOp rep #

min :: HistOp rep -> HistOp rep -> HistOp rep #

RepTypes rep => Show (HistOp rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

show :: HistOp rep -> String #

showList :: [HistOp rep] -> ShowS #

histType :: HistOp rep -> [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 rep Source #

An operator for SegScan and SegRed.

Constructors

SegBinOp 

Fields

Instances

Instances details
RepTypes rep => Eq (SegBinOp rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

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

RepTypes rep => Ord (SegBinOp rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

compare :: SegBinOp rep -> SegBinOp rep -> Ordering #

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

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

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

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

max :: SegBinOp rep -> SegBinOp rep -> SegBinOp rep #

min :: SegBinOp rep -> SegBinOp rep -> SegBinOp rep #

RepTypes rep => Show (SegBinOp rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

show :: SegBinOp rep -> String #

showList :: [SegBinOp rep] -> ShowS #

PrettyRep rep => Pretty (SegBinOp rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

ppr :: SegBinOp rep -> Doc #

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

pprList :: [SegBinOp rep] -> Doc #

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

How many reduction results are produced by these SegBinOps?

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

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

data KernelBody rep Source #

The body of a SegOp.

Instances

Instances details
RepTypes rep => Eq (KernelBody rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

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

RepTypes rep => Ord (KernelBody rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

compare :: KernelBody rep -> KernelBody rep -> Ordering #

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

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

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

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

max :: KernelBody rep -> KernelBody rep -> KernelBody rep #

min :: KernelBody rep -> KernelBody rep -> KernelBody rep #

RepTypes rep => Show (KernelBody rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

show :: KernelBody rep -> String #

showList :: [KernelBody rep] -> ShowS #

PrettyRep rep => Pretty (KernelBody rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

ppr :: KernelBody rep -> Doc #

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

pprList :: [KernelBody rep] -> Doc #

ASTRep rep => FreeIn (KernelBody rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

freeIn' :: KernelBody rep -> FV Source #

ASTRep rep => Substitute (KernelBody rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

ASTRep rep => Rename (KernelBody rep) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

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

aliasAnalyseKernelBody :: (ASTRep rep, CanBeAliased (Op rep)) => AliasTable -> KernelBody rep -> KernelBody (Aliases rep) Source #

Perform alias analysis on a KernelBody.

consumedInKernelBody :: Aliased rep => KernelBody rep -> 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 Certs 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 Certs Shape VName [(Slice SubExp, SubExp)] 
ConcatReturns Certs SplitOrdering SubExp SubExp VName 
TileReturns Certs [(SubExp, SubExp)] VName 
RegTileReturns Certs [(SubExp, 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 frep trep m Source #

Like Mapper, but just for SegOps.

Constructors

SegOpMapper 

Fields

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

A mapper that simply returns the SegOp verbatim.

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

Apply a SegOpMapper to the given SegOp.

Simplification

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

Simplify the given SegOp.

class HasSegOp rep where Source #

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

Associated Types

type SegOpLevel rep Source #

Methods

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

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

Instances

Instances details
HasSegOp MC Source # 
Instance details

Defined in Futhark.IR.MC

Associated Types

type SegOpLevel MC Source #

HasSegOp GPU Source # 
Instance details

Defined in Futhark.IR.GPU

Associated Types

type SegOpLevel GPU Source #

HasSegOp (Wise MC) Source # 
Instance details

Defined in Futhark.IR.MC

Associated Types

type SegOpLevel (Wise MC) Source #

HasSegOp (Wise GPU) Source # 
Instance details

Defined in Futhark.IR.GPU.Simplify

Associated Types

type SegOpLevel (Wise GPU) Source #

segOpRules :: (HasSegOp rep, BuilderOps rep, Buildable rep) => RuleBook rep Source #

Simplification rules for simplifying SegOps.

Memory

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

Like segOpType, but for memory representations.