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

Futhark.Analysis.SymbolTable

Synopsis

Documentation

data SymbolTable rep Source #

Instances

Instances details
Semigroup (SymbolTable rep) Source # 
Instance details

Defined in Futhark.Analysis.SymbolTable

Methods

(<>) :: SymbolTable rep -> SymbolTable rep -> SymbolTable rep #

sconcat :: NonEmpty (SymbolTable rep) -> SymbolTable rep #

stimes :: Integral b => b -> SymbolTable rep -> SymbolTable rep #

Monoid (SymbolTable rep) Source # 
Instance details

Defined in Futhark.Analysis.SymbolTable

Methods

mempty :: SymbolTable rep #

mappend :: SymbolTable rep -> SymbolTable rep -> SymbolTable rep #

mconcat :: [SymbolTable rep] -> SymbolTable rep #

fromScope :: ASTRep rep => Scope rep -> SymbolTable rep Source #

Entries

data Entry rep Source #

Instances

Instances details
ASTRep rep => Typed (Entry rep) Source # 
Instance details

Defined in Futhark.Analysis.SymbolTable

Methods

typeOf :: Entry rep -> Type Source #

entryAccInput :: Entry rep -> Maybe (WithAccInput rep) Source #

For names that are tokens of an accumulator, this is the corresponding combining function and neutral element.

entryIsSize :: Entry rep -> Bool Source #

True if this name has been used as an array size, implying that it is non-negative.

entryStm :: Entry rep -> Maybe (Stm rep) Source #

Lookup

elem :: VName -> SymbolTable rep -> Bool Source #

You almost always want available instead of this one.

lookupLoopVar :: VName -> SymbolTable rep -> Maybe SubExp Source #

If the given variable name is the name of a ForLoop parameter, then return the bound of that loop.

available :: VName -> SymbolTable rep -> Bool Source #

In symbol table and not consumed.

data Indexed Source #

The result of indexing a delayed array.

Constructors

Indexed Certs (PrimExp VName)

A PrimExp based on the indexes (that is, without accessing any actual array).

IndexedArray Certs VName [TPrimExp Int64 VName]

The indexing corresponds to another (perhaps more advantageous) array.

Instances

Instances details
FreeIn Indexed Source # 
Instance details

Defined in Futhark.Analysis.SymbolTable

Methods

freeIn' :: Indexed -> FV Source #

class IndexOp op where Source #

Minimal complete definition

Nothing

Methods

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

Instances

Instances details
IndexOp () Source # 
Instance details

Defined in Futhark.Analysis.SymbolTable

Methods

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

RepTypes rep => IndexOp (SOAC rep) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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

IndexOp inner => IndexOp (MemOp inner) Source # 
Instance details

Defined in Futhark.IR.Mem

Methods

indexOp :: (ASTRep rep, IndexOp (Op rep)) => SymbolTable rep -> Int -> MemOp inner -> [TPrimExp Int64 VName] -> Maybe Indexed 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 #

(ASTRep rep, IndexOp op) => IndexOp (MCOp rep op) Source # 
Instance details

Defined in Futhark.IR.MC.Op

Methods

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

(ASTRep rep, IndexOp op) => IndexOp (HostOp rep op) Source # 
Instance details

Defined in Futhark.IR.GPU.Op

Methods

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

Insertion

insertStm :: (ASTRep rep, IndexOp (Op rep), Aliased rep) => Stm rep -> SymbolTable rep -> SymbolTable rep Source #

insertStms :: (ASTRep rep, IndexOp (Op rep), Aliased rep) => Stms rep -> SymbolTable rep -> SymbolTable rep Source #

insertFParams :: ASTRep rep => [FParam rep] -> SymbolTable rep -> SymbolTable rep Source #

insertLoopMerge :: ASTRep rep => [(FParam rep, SubExp, SubExpRes)] -> SymbolTable rep -> SymbolTable rep Source #

Insert entries corresponding to the parameters of a loop (not distinguishing contect and value part). Apart from the parameter itself, we also insert the initial value and the subexpression providing the final value. Note that the latter is likely not in scope in the symbol at this point. This is OK, and can still be used to help some loop optimisations detect invariant loop parameters.

Misc

hideCertified :: Names -> SymbolTable rep -> SymbolTable rep Source #

Hide these definitions, if they are protected by certificates in the set of names.

noteAccTokens :: [(VName, WithAccInput rep)] -> SymbolTable rep -> SymbolTable rep Source #

Note that these names are tokens for the corresponding accumulators. The names must already be present in the symbol table.