uhc-util-0.1.6.7: UHC utilities

Safe HaskellNone
LanguageHaskell98

UHC.Util.ScopeMapGam

Contents

Description

Environment/Gamma where the lexical level + scoping is used to provide nesting behavior. Both a SGam and its entries know at which scope they are.

Insertion is efficient, lookup also, because a single Map is used.

The Map holds multiple entries, each with its own scope identifier. An SGam holds - a stack of scopes, encoding the nesting, where - each scope holds mappings for MetaLev's

Results are filtered out w.r.t. this stack, i.e. are checked to be in scope. In principle this can be done eagerly, that is, immediately after a change in scope, in particular in sgamPop. After some experimentation it did turn out that doing this lazily is overall faster, that is, when the SGam is consulted (lookup, conversion to association list, etc). Conceptually thus the invariant is that no entry is in the map which is not in scope. Guaranteeing this invariant is thus not done by the one function breaking it (sgamPop).

Synopsis

Documentation

data SGam k v Source #

Instances

Show (SGam k v) Source # 

Methods

showsPrec :: Int -> SGam k v -> ShowS #

show :: SGam k v -> String #

showList :: [SGam k v] -> ShowS #

Generic (SGam k v) Source # 

Associated Types

type Rep (SGam k v) :: * -> * #

Methods

from :: SGam k v -> Rep (SGam k v) x #

to :: Rep (SGam k v) x -> SGam k v #

(Ord k, Serialize k, Serialize v) => Serialize (SGam k v) Source # 

Methods

sput :: SGam k v -> SPut Source #

sget :: SGet (SGam k v) Source #

sputNested :: SGam k v -> SPut Source #

sgetNested :: SGet (SGam k v) Source #

type Rep (SGam k v) Source # 
type Rep (SGam k v)

Folding

sgamFilterMapEltAccumWithKey :: Ord k' => (k -> SGamElt v -> Bool) -> (k -> SGamElt v -> acc -> (k', SGamElt v', acc)) -> (k -> SGamElt v -> acc -> acc) -> acc -> SGam k v -> (SGam k' v', acc) Source #

do it all: map, filter, fold

sgamMapEltWithKey :: (Ord k, Ord k') => (k -> SGamElt v -> (k', SGamElt v')) -> SGam k v -> SGam k' v' Source #

sgamMapThr :: (Ord k, Ord k') => ((k, v) -> t -> ((k', v'), t)) -> t -> SGam k v -> (SGam k' v', t) Source #

sgamMap :: (Ord k, Ord k') => ((k, v) -> (k', v')) -> SGam k v -> SGam k' v' Source #

Construction & Destruction

sgamPop :: Ord k => SGam k v -> (SGam k v, SGam k v) Source #

split gam in top and the rest, both with the same scope

sgamTop :: Ord k => SGam k v -> SGam k v Source #

top gam, with same scope as g

sgamPushNew :: SGam k v -> SGam k v Source #

enter a new scope

sgamPushGam :: Ord k => SGam k v -> SGam k v -> SGam k v Source #

enter a new scope, add g1 in that scope to g2

sgamMetaLevSingleton :: Ord k => MetaLev -> k -> v -> SGam k v Source #

Construct singleton gam, on a particular meta level

sgamSingleton :: Ord k => k -> v -> SGam k v Source #

Construct singleton gam

sgamUnionWith :: Ord k => Maybe (v -> [v] -> [v]) -> SGam k v -> SGam k v -> SGam k v Source #

combine gam, g1 is added to g2 with scope of g2

sgamUnion :: Ord k => SGam k v -> SGam k v -> SGam k v Source #

sgamPartitionEltWithKey :: Ord k => (k -> SGamElt v -> Bool) -> SGam k v -> (SGam k v, SGam k v) Source #

equivalent of partition

sgamPartitionWithKey :: Ord k => (k -> v -> Bool) -> SGam k v -> (SGam k v, SGam k v) Source #

sgamUnzip :: Ord k => SGam k (v1, v2) -> (SGam k v1, SGam k v2) Source #

equivalent of unzip

Deletion

Update

sgamAlterDupOnTop :: Ord k => (Maybe v -> Maybe v) -> k -> SGam k v -> SGam k v Source #

Alter on top of the scope stack, including all duplicates

Lookup

sgamLookupMetaLevDup :: Ord k => MetaLev -> k -> SGam k v -> Maybe [v] Source #

lookup, return at least one found value, otherwise Nothing

Conversion

sgamToAssocDupL :: Ord k => SGam k v -> AssocL k [v] Source #

convert to association list, with all duplicates, scope is lost

sgamFromAssocDupL :: Ord k => AssocL k [v] -> SGam k v Source #

convert from association list, assume default scope

sgamNoDups :: Ord k => SGam k v -> SGam k v Source #

get rid of duplicate entries, by taking the first of them all

Re-exports

type MetaLev = Int Source #

Level to lookup into

metaLevVal :: MetaLev Source #

Base level (of values, usually)