Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data SymbolTable lore
- empty :: SymbolTable lore
- fromScope :: Attributes lore => Scope lore -> SymbolTable lore
- toScope :: SymbolTable lore -> Scope lore
- castSymbolTable :: (SameScope from to, ExpAttr from ~ ExpAttr to, BodyAttr from ~ BodyAttr to, RetType from ~ RetType to, BranchType from ~ BranchType to) => SymbolTable from -> SymbolTable to
- data Entry lore
- deepen :: SymbolTable lore -> SymbolTable lore
- bindingDepth :: Entry lore -> Int
- valueRange :: Entry lore -> ScalExpRange
- loopVariable :: Entry lore -> Bool
- entryStm :: Entry lore -> Maybe (Stm lore)
- entryLetBoundAttr :: Entry lore -> Maybe (LetAttr lore)
- entryFParamLore :: Entry lore -> Maybe (FParamAttr lore)
- entryType :: Attributes lore => Entry lore -> Type
- asScalExp :: Entry lore -> Maybe ScalExp
- elem :: VName -> SymbolTable lore -> Bool
- lookup :: VName -> SymbolTable lore -> Maybe (Entry lore)
- lookupStm :: VName -> SymbolTable lore -> Maybe (Stm lore)
- lookupExp :: VName -> SymbolTable lore -> Maybe (Exp lore, Certificates)
- lookupBasicOp :: VName -> SymbolTable lore -> Maybe (BasicOp lore, Certificates)
- lookupType :: Attributes lore => VName -> SymbolTable lore -> Maybe Type
- lookupSubExp :: VName -> SymbolTable lore -> Maybe (SubExp, Certificates)
- lookupScalExp :: Attributes lore => VName -> SymbolTable lore -> Maybe ScalExp
- lookupValue :: VName -> SymbolTable lore -> Maybe (PrimValue, Certificates)
- lookupVar :: VName -> SymbolTable lore -> Maybe (VName, Certificates)
- lookupAliases :: VName -> SymbolTable lore -> Names
- available :: VName -> SymbolTable lore -> Bool
- consume :: Attributes lore => VName -> SymbolTable lore -> SymbolTable lore
- index :: Attributes lore => VName -> [SubExp] -> SymbolTable lore -> Maybe (PrimExp VName, Certificates)
- index' :: VName -> [PrimExp VName] -> SymbolTable lore -> Maybe (PrimExp VName, Certificates)
- class IndexOp op where
- indexOp :: (Attributes lore, IndexOp (Op lore)) => SymbolTable lore -> Int -> op -> [PrimExp VName] -> Maybe (PrimExp VName, Certificates)
- insertStm :: (IndexOp (Op lore), Ranged lore, Aliased lore) => Stm lore -> SymbolTable lore -> SymbolTable lore
- insertFParams :: Attributes lore => [FParam lore] -> SymbolTable lore -> SymbolTable lore
- insertLParam :: Attributes lore => LParam lore -> SymbolTable lore -> SymbolTable lore
- insertArrayLParam :: Attributes lore => LParam lore -> Maybe VName -> SymbolTable lore -> SymbolTable lore
- insertChunkLParam :: Attributes lore => VName -> LParam lore -> VName -> SymbolTable lore -> SymbolTable lore
- insertLoopVar :: Attributes lore => VName -> IntType -> SubExp -> SymbolTable lore -> SymbolTable lore
- updateBounds :: Attributes lore => Bool -> SubExp -> SymbolTable lore -> SymbolTable lore
- setUpperBound :: VName -> ScalExp -> SymbolTable lore -> SymbolTable lore
- setLowerBound :: VName -> ScalExp -> SymbolTable lore -> SymbolTable lore
- isAtLeast :: VName -> Int -> SymbolTable lore -> SymbolTable lore
- enclosingLoopVars :: [VName] -> SymbolTable lore -> [VName]
- rangesRep :: SymbolTable lore -> RangesRep
Documentation
data SymbolTable lore Source #
Instances
Semigroup (SymbolTable lore) Source # | |
Defined in Futhark.Analysis.SymbolTable (<>) :: SymbolTable lore -> SymbolTable lore -> SymbolTable lore # sconcat :: NonEmpty (SymbolTable lore) -> SymbolTable lore # stimes :: Integral b => b -> SymbolTable lore -> SymbolTable lore # | |
Monoid (SymbolTable lore) Source # | |
Defined in Futhark.Analysis.SymbolTable mempty :: SymbolTable lore # mappend :: SymbolTable lore -> SymbolTable lore -> SymbolTable lore # mconcat :: [SymbolTable lore] -> SymbolTable lore # |
empty :: SymbolTable lore Source #
fromScope :: Attributes lore => Scope lore -> SymbolTable lore Source #
toScope :: SymbolTable lore -> Scope lore Source #
castSymbolTable :: (SameScope from to, ExpAttr from ~ ExpAttr to, BodyAttr from ~ BodyAttr to, RetType from ~ RetType to, BranchType from ~ BranchType to) => SymbolTable from -> SymbolTable to Source #
Try to convert a symbol table for one representation into a symbol table for another. The two symbol tables will have the same keys, but some entries may be diferent (i.e. some expression entries will have been turned into free variable entries).
Entries
deepen :: SymbolTable lore -> SymbolTable lore Source #
bindingDepth :: Entry lore -> Int Source #
valueRange :: Entry lore -> ScalExpRange Source #
loopVariable :: Entry lore -> Bool Source #
entryFParamLore :: Entry lore -> Maybe (FParamAttr lore) Source #
Lookup
lookupExp :: VName -> SymbolTable lore -> Maybe (Exp lore, Certificates) Source #
lookupBasicOp :: VName -> SymbolTable lore -> Maybe (BasicOp lore, Certificates) Source #
lookupType :: Attributes lore => VName -> SymbolTable lore -> Maybe Type Source #
lookupSubExp :: VName -> SymbolTable lore -> Maybe (SubExp, Certificates) Source #
lookupScalExp :: Attributes lore => VName -> SymbolTable lore -> Maybe ScalExp Source #
lookupValue :: VName -> SymbolTable lore -> Maybe (PrimValue, Certificates) Source #
lookupVar :: VName -> SymbolTable lore -> Maybe (VName, Certificates) Source #
lookupAliases :: VName -> SymbolTable lore -> Names Source #
consume :: Attributes lore => VName -> SymbolTable lore -> SymbolTable lore Source #
index :: Attributes lore => VName -> [SubExp] -> SymbolTable lore -> Maybe (PrimExp VName, Certificates) Source #
index' :: VName -> [PrimExp VName] -> SymbolTable lore -> Maybe (PrimExp VName, Certificates) Source #
class IndexOp op where Source #
Nothing
indexOp :: (Attributes lore, IndexOp (Op lore)) => SymbolTable lore -> Int -> op -> [PrimExp VName] -> Maybe (PrimExp VName, Certificates) Source #
Instances
Insertion
insertStm :: (IndexOp (Op lore), Ranged lore, Aliased lore) => Stm lore -> SymbolTable lore -> SymbolTable lore Source #
insertFParams :: Attributes lore => [FParam lore] -> SymbolTable lore -> SymbolTable lore Source #
insertLParam :: Attributes lore => LParam lore -> SymbolTable lore -> SymbolTable lore Source #
insertArrayLParam :: Attributes lore => LParam lore -> Maybe VName -> SymbolTable lore -> SymbolTable lore Source #
insertChunkLParam :: Attributes lore => VName -> LParam lore -> VName -> SymbolTable lore -> SymbolTable lore Source #
insertLoopVar :: Attributes lore => VName -> IntType -> SubExp -> SymbolTable lore -> SymbolTable lore Source #
Bounds
updateBounds :: Attributes lore => Bool -> SubExp -> SymbolTable lore -> SymbolTable lore Source #
setUpperBound :: VName -> ScalExp -> SymbolTable lore -> SymbolTable lore Source #
setLowerBound :: VName -> ScalExp -> SymbolTable lore -> SymbolTable lore Source #
isAtLeast :: VName -> Int -> SymbolTable lore -> SymbolTable lore Source #
Misc
enclosingLoopVars :: [VName] -> SymbolTable lore -> [VName] Source #
rangesRep :: SymbolTable lore -> RangesRep Source #