futhark-0.16.4: An optimising compiler for a functional, array-oriented language.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Futhark.Analysis.SymbolTable

Synopsis

Documentation

data SymbolTable lore Source #

Instances

Instances details
Semigroup (SymbolTable lore) Source # 
Instance details

Defined in Futhark.Analysis.SymbolTable

Methods

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

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

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

Monoid (SymbolTable lore) Source # 
Instance details

Defined in Futhark.Analysis.SymbolTable

Methods

mempty :: SymbolTable lore #

mappend :: SymbolTable lore -> SymbolTable lore -> SymbolTable lore #

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

fromScope :: ASTLore lore => Scope lore -> SymbolTable lore Source #

toScope :: SymbolTable lore -> Scope lore Source #

Entries

data Entry lore Source #

Instances

Instances details
ASTLore lore => Typed (Entry lore) Source # 
Instance details

Defined in Futhark.Analysis.SymbolTable

Methods

typeOf :: Entry lore -> Type Source #

entryIsSize :: Entry lore -> Bool Source #

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

Lookup

lookup :: VName -> SymbolTable lore -> Maybe (Entry lore) Source #

lookupStm :: VName -> SymbolTable lore -> Maybe (Stm lore) Source #

lookupLoopVar :: VName -> SymbolTable lore -> 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 lore -> Bool Source #

In symbol table and not consumed.

data Indexed Source #

The result of indexing a delayed array.

Constructors

Indexed Certificates (PrimExp VName)

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

IndexedArray Certificates VName [PrimExp 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 :: (ASTLore lore, IndexOp (Op lore)) => SymbolTable lore -> Int -> op -> [PrimExp VName] -> Maybe Indexed Source #

Instances

Instances details
IndexOp () Source # 
Instance details

Defined in Futhark.Analysis.SymbolTable

Methods

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

Decorations lore => IndexOp (SOAC lore) Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

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

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

Defined in Futhark.IR.Mem

Methods

indexOp :: (ASTLore lore, IndexOp (Op lore)) => SymbolTable lore -> Int -> MemOp inner -> [PrimExp VName] -> Maybe Indexed 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 #

(ASTLore lore, IndexOp op) => IndexOp (HostOp lore op) Source # 
Instance details

Defined in Futhark.IR.Kernels.Kernel

Methods

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

Insertion

insertStm :: (ASTLore lore, IndexOp (Op lore), Aliased lore) => Stm lore -> SymbolTable lore -> SymbolTable lore Source #

insertStms :: (ASTLore lore, IndexOp (Op lore), Aliased lore) => Stms lore -> SymbolTable lore -> SymbolTable lore Source #

insertFParams :: ASTLore lore => [FParam lore] -> SymbolTable lore -> SymbolTable lore Source #

insertLParam :: ASTLore lore => LParam lore -> SymbolTable lore -> SymbolTable lore Source #

Misc

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

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