| Safe Haskell | None |
|---|
DDC.Core.Eval.Store
Contents
Description
Definition of the store.
- data Store = Store {
- storeNextLoc :: Int
- storeNextRgn :: Int
- storeRegions :: Set Rgn
- storeGlobal :: Set Rgn
- storeBinds :: Map Loc (Rgn, Type Name, SBind)
- data Loc = Loc Int (Type Name)
- data Rgn = Rgn Int
- data SBind
- = SObj {
- sbindDataTag :: DaCon Name
- sbindDataArgs :: [Loc]
- | SLams {
- sbindLamBinds :: [(Bool, Bind Name)]
- sbindLamBody :: Exp () Name
- | SThunk {
- sbindThunkExp :: Exp () Name
- = SObj {
- initial :: Store
- locUnit :: Loc
- isUnitOrLocX :: Show a => Exp a Name -> Bool
- newLoc :: Type Name -> Store -> (Store, Loc)
- newLocs :: [Type Name] -> Store -> (Store, [Loc])
- newRgn :: Store -> (Store, Rgn)
- newRgns :: Int -> Store -> (Store, [Rgn])
- delRgn :: Rgn -> Store -> Store
- hasRgn :: Store -> Rgn -> Bool
- setGlobal :: Rgn -> Store -> Store
- addBind :: Loc -> Rgn -> Type Name -> SBind -> Store -> Store
- allocBind :: Rgn -> Type Name -> SBind -> Store -> (Store, Loc)
- allocBinds :: [[Loc] -> (Rgn, Type Name, SBind)] -> [Type Name] -> Store -> (Store, [Loc])
- lookupBind :: Loc -> Store -> Maybe SBind
- lookupTypeOfLoc :: Loc -> Store -> Maybe (Type Name)
- lookupRegionTypeBind :: Loc -> Store -> Maybe (Rgn, Type Name, SBind)
Documentation
Constructors
| Store | |
Fields
| |
A store location, tagged with the type of the value contained at that location.
These are pretty printed like l4#.
A region handle.
These are pretty printed like r5#.
Constructors
| Rgn Int |
Store binding. These are naked objects that can be allocated directly into the heap.
Constructors
| SObj | An algebraic data constructor. |
Fields
| |
| SLams | Lambda abstraction, used for recursive bindings. The flag indicates whether each binder is level-1 (True) or level-0 (False). |
Fields
| |
| SThunk | A thunk, used for lazy evaluation. |
Fields
| |
Operators
isUnitOrLocX :: Show a => Exp a Name -> BoolSource
Check whether an expression is the unit constructor, or its static heap location.
addBind :: Loc -> Rgn -> Type Name -> SBind -> Store -> StoreSource
Add a store binding to the store, at the given location.
allocBind :: Rgn -> Type Name -> SBind -> Store -> (Store, Loc)Source
Allocate a new binding into the given region, returning the new location.
allocBinds :: [[Loc] -> (Rgn, Type Name, SBind)] -> [Type Name] -> Store -> (Store, [Loc])Source
Alloc some recursive bindings into the given region, returning the new locations.
lookupBind :: Loc -> Store -> Maybe SBindSource
Lookup a the binding for a location.