uhc-util-0.1.1.0: UHC utilities

Safe HaskellNone

UHC.Util.ScopeMapGam

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

Typeable2 SGam 
(Data k, Data v, Ord k) => Data (SGam k v) 
Show (SGam k v) 
(Ord k, Serialize k, Serialize v) => Serialize (SGam k v) 

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

sgamSingleton :: k -> v -> SGam k vSource

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

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

sgamUnion :: Ord k => SGam k v -> SGam k v -> SGam k vSource

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

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 vSource

top gam, with same scope as g

sgamPushNew :: SGam k v -> SGam k vSource

enter a new scope

sgamPushGam :: Ord k => SGam k v -> SGam k v -> SGam k vSource

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

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

lookup, return at least one found value, otherwise Nothing

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 vSource

convert from association list, assume default scope

sgamNoDups :: Ord k => SGam k v -> SGam k vSource

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