License | BSD-3-Clause |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Swarm.Language.Context
Description
Generic contexts (mappings from variables to other things, such as
types, values, or capability sets) used throughout the codebase.
For example, while typechecking we use a context to store a mapping
from variables in scope to their types. As another example, at
runtime, robots store an Env
which contains several contexts,
mapping variables to things like their current value, any
requirements associated with using the variable, and so on.
The implementation here goes to some effort to make it possible to serialize and deserialize contexts so that sharing is preserved and the encoding of serialized contexts does not blow up due to repeated values.
Synopsis
- newtype CtxHash = CtxHash {
- getCtxHash :: Int
- singletonHash :: (Hashable v, Hashable t) => v -> t -> CtxHash
- mapHash :: (Hashable v, Hashable t) => Map v t -> CtxHash
- data CtxF (f :: Type -> Type -> Type) v t
- restructureCtx :: (f v t -> g v t) -> CtxF f v t -> CtxF g v t
- data CtxTree v t = CtxTree CtxHash (CtxF CtxTree v t)
- data Ctx v t = Ctx {}
- ctxHash :: Ctx v t -> CtxHash
- ctxFromTree :: Ord v => CtxTree v t -> Ctx v t
- rollCtx :: (Ord v, Hashable v, Hashable t) => CtxF Ctx v t -> Ctx v t
- empty :: Ctx v t
- singleton :: (Ord v, Hashable v, Hashable t) => v -> t -> Ctx v t
- fromMap :: (Ord v, Hashable v, Hashable t) => Map v t -> Ctx v t
- lookup :: Ord v => v -> Ctx v t -> Maybe t
- lookupR :: forall v t (sig :: (Type -> Type) -> Type -> Type) m. (Ord v, Has (Reader (Ctx v t)) sig m) => v -> m (Maybe t)
- delete :: (Ord v, Hashable v, Hashable t) => v -> Ctx v t -> Ctx v t
- assocs :: Ctx v t -> [(v, t)]
- vars :: Ctx v t -> [v]
- addBinding :: (Ord v, Hashable v, Hashable t) => v -> t -> Ctx v t -> Ctx v t
- union :: (Ord v, Hashable v, Hashable t) => Ctx v t -> Ctx v t -> Ctx v t
- withBinding :: forall v t (sig :: (Type -> Type) -> Type -> Type) m a. (Has (Reader (Ctx v t)) sig m, Ord v, Hashable v, Hashable t) => v -> t -> m a -> m a
- withBindings :: forall v t (sig :: (Type -> Type) -> Type -> Type) m a. (Has (Reader (Ctx v t)) sig m, Ord v, Hashable v, Hashable t) => Ctx v t -> m a -> m a
- type CtxMap (f :: Type -> Type -> Type) v t = Map CtxHash (CtxF f v t)
- getCtx :: Ord v => CtxHash -> CtxMap CtxTree v t -> Maybe (Ctx v t)
- toCtxMap :: Ord v => Ctx v t -> CtxMap CtxTree v t
- buildCtxMap :: forall v t m (sig :: (Type -> Type) -> Type -> Type). (Ord v, Has (State (CtxMap CtxTree v t)) sig m) => Map v t -> CtxTree v t -> m ()
- newtype ConstHash v t = ConstHash CtxHash
- dehydrate :: CtxMap CtxTree v t -> CtxMap ConstHash v t
- rehydrate :: CtxMap ConstHash v t -> CtxMap CtxTree v t
Documentation
A context hash is a hash value used to identify contexts without having to compare them for equality. Hash values are computed homomorphically, so that two equal contexts will be guaranteed to have the same hash value, even if they were constructed with a different sequence of operations.
The downside of this approach is that, in theory, there could be hash collisions, that is, two different contexts which nonetheless have the same hash value. However, this is extremely unlikely. The benefit is that everything can be purely functional, without the need to thread around some kind of globally unique ID generation effect.
Constructors
CtxHash | |
Fields
|
Instances
FromJSON CtxHash Source # | |||||
Defined in Swarm.Language.Context | |||||
FromJSONKey CtxHash Source # | |||||
Defined in Swarm.Language.Context Methods | |||||
ToJSON CtxHash Source # | |||||
ToJSONKey CtxHash Source # | |||||
Defined in Swarm.Language.Context | |||||
Data CtxHash Source # | |||||
Defined in Swarm.Language.Context Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CtxHash -> c CtxHash # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CtxHash # toConstr :: CtxHash -> Constr # dataTypeOf :: CtxHash -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CtxHash) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CtxHash) # gmapT :: (forall b. Data b => b -> b) -> CtxHash -> CtxHash # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CtxHash -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CtxHash -> r # gmapQ :: (forall d. Data d => d -> u) -> CtxHash -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CtxHash -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CtxHash -> m CtxHash # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CtxHash -> m CtxHash # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CtxHash -> m CtxHash # | |||||
Monoid CtxHash Source # | |||||
Semigroup CtxHash Source # | |||||
Generic CtxHash Source # | |||||
Defined in Swarm.Language.Context Associated Types
| |||||
Num CtxHash Source # | |||||
Show CtxHash Source # | |||||
Eq CtxHash Source # | |||||
Ord CtxHash Source # | |||||
Defined in Swarm.Language.Context | |||||
Ord v => FromJSONE (CtxMap CtxTree v t) (Ctx v t) Source # | Deserialize a context. We expect to see a hash, and look it up in the provided CtxMap. | ||||
Defined in Swarm.Language.Context | |||||
type Rep CtxHash Source # | |||||
Defined in Swarm.Language.Context |
singletonHash :: (Hashable v, Hashable t) => v -> t -> CtxHash Source #
The hash for a single variable -> value binding.
mapHash :: (Hashable v, Hashable t) => Map v t -> CtxHash Source #
The hash for an entire Map's worth of bindings.
data CtxF (f :: Type -> Type -> Type) v t Source #
CtxF
represents one level of structure of a context: a context
is either empty, a singleton, or built via deletion or union.
Instances
Foldable (f v) => Foldable (CtxF f v) Source # | |
Defined in Swarm.Language.Context Methods fold :: Monoid m => CtxF f v m -> m # foldMap :: Monoid m => (a -> m) -> CtxF f v a -> m # foldMap' :: Monoid m => (a -> m) -> CtxF f v a -> m # foldr :: (a -> b -> b) -> b -> CtxF f v a -> b # foldr' :: (a -> b -> b) -> b -> CtxF f v a -> b # foldl :: (b -> a -> b) -> b -> CtxF f v a -> b # foldl' :: (b -> a -> b) -> b -> CtxF f v a -> b # foldr1 :: (a -> a -> a) -> CtxF f v a -> a # foldl1 :: (a -> a -> a) -> CtxF f v a -> a # elem :: Eq a => a -> CtxF f v a -> Bool # maximum :: Ord a => CtxF f v a -> a # minimum :: Ord a => CtxF f v a -> a # | |
Traversable (f v) => Traversable (CtxF f v) Source # | |
Defined in Swarm.Language.Context | |
Functor (f v) => Functor (CtxF f v) Source # | |
(FromJSON v, FromJSON t, FromJSON (f v t)) => FromJSON (CtxF f v t) Source # | |
Defined in Swarm.Language.Context | |
(ToJSON v, ToJSON t, ToJSON (f v t)) => ToJSON (CtxF f v t) Source # | |
(Typeable f, Data v, Data t, Data (f v t)) => Data (CtxF f v t) Source # | |
Defined in Swarm.Language.Context Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CtxF f v t -> c (CtxF f v t) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CtxF f v t) # toConstr :: CtxF f v t -> Constr # dataTypeOf :: CtxF f v t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (CtxF f v t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (CtxF f v t)) # gmapT :: (forall b. Data b => b -> b) -> CtxF f v t -> CtxF f v t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CtxF f v t -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CtxF f v t -> r # gmapQ :: (forall d. Data d => d -> u) -> CtxF f v t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CtxF f v t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CtxF f v t -> m (CtxF f v t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CtxF f v t -> m (CtxF f v t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CtxF f v t -> m (CtxF f v t) # | |
Generic (CtxF f v t) Source # | |
Defined in Swarm.Language.Context Associated Types | |
(Show v, Show t, Show (f v t)) => Show (CtxF f v t) Source # | |
(Eq v, Eq t, Eq (f v t)) => Eq (CtxF f v t) Source # | |
Ord v => FromJSONE (CtxMap CtxTree v t) (Ctx v t) Source # | Deserialize a context. We expect to see a hash, and look it up in the provided CtxMap. |
Defined in Swarm.Language.Context | |
type Rep (CtxF f v t) Source # | |
Defined in Swarm.Language.Context type Rep (CtxF f v t) = D1 ('MetaData "CtxF" "Swarm.Language.Context" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) ((C1 ('MetaCons "CtxEmpty" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CtxSingle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 v) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 t))) :+: (C1 ('MetaCons "CtxDelete" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 v) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 t) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f v t)))) :+: C1 ('MetaCons "CtxUnion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f v t)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f v t))))) |
restructureCtx :: (f v t -> g v t) -> CtxF f v t -> CtxF g v t Source #
Map over the recursive structure stored in a CtxF
.
A CtxTree
is one possible representation of a context,
consisting of a structured record of the process by which a
context was constructed. This representation would be terrible
for doing efficient variable lookups, but it can be used to
efficiently serialize/deserialize the context while recovering
sharing.
It stores a top-level hash of the context, along with a recursive
tree built via CtxF
.
Instances
Foldable (CtxTree v) Source # | |||||
Defined in Swarm.Language.Context Methods fold :: Monoid m => CtxTree v m -> m # foldMap :: Monoid m => (a -> m) -> CtxTree v a -> m # foldMap' :: Monoid m => (a -> m) -> CtxTree v a -> m # foldr :: (a -> b -> b) -> b -> CtxTree v a -> b # foldr' :: (a -> b -> b) -> b -> CtxTree v a -> b # foldl :: (b -> a -> b) -> b -> CtxTree v a -> b # foldl' :: (b -> a -> b) -> b -> CtxTree v a -> b # foldr1 :: (a -> a -> a) -> CtxTree v a -> a # foldl1 :: (a -> a -> a) -> CtxTree v a -> a # toList :: CtxTree v a -> [a] # length :: CtxTree v a -> Int # elem :: Eq a => a -> CtxTree v a -> Bool # maximum :: Ord a => CtxTree v a -> a # minimum :: Ord a => CtxTree v a -> a # | |||||
Traversable (CtxTree v) Source # | |||||
Defined in Swarm.Language.Context | |||||
Functor (CtxTree v) Source # | |||||
(FromJSON v, FromJSON t) => FromJSON (CtxTree v t) Source # | |||||
Defined in Swarm.Language.Context | |||||
(ToJSON v, ToJSON t) => ToJSON (CtxTree v t) Source # | |||||
(Data v, Data t) => Data (CtxTree v t) Source # | |||||
Defined in Swarm.Language.Context Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CtxTree v t -> c (CtxTree v t) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CtxTree v t) # toConstr :: CtxTree v t -> Constr # dataTypeOf :: CtxTree v t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (CtxTree v t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (CtxTree v t)) # gmapT :: (forall b. Data b => b -> b) -> CtxTree v t -> CtxTree v t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CtxTree v t -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CtxTree v t -> r # gmapQ :: (forall d. Data d => d -> u) -> CtxTree v t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CtxTree v t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CtxTree v t -> m (CtxTree v t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CtxTree v t -> m (CtxTree v t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CtxTree v t -> m (CtxTree v t) # | |||||
Generic (CtxTree v t) Source # | |||||
Defined in Swarm.Language.Context Associated Types
| |||||
(Show v, Show t) => Show (CtxTree v t) Source # | |||||
(Eq v, Eq t) => Eq (CtxTree v t) Source # | |||||
Ord v => FromJSONE (CtxMap CtxTree v t) (Ctx v t) Source # | Deserialize a context. We expect to see a hash, and look it up in the provided CtxMap. | ||||
Defined in Swarm.Language.Context | |||||
type Rep (CtxTree v t) Source # | |||||
Defined in Swarm.Language.Context type Rep (CtxTree v t) = D1 ('MetaData "CtxTree" "Swarm.Language.Context" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "CtxTree" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CtxHash) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (CtxF CtxTree v t)))) |
A context is a mapping from variable names to things. We store
both a Map
(for efficient lookup) as well as a CtxTree
(for
sharing-aware serializing/deserializing).
Instances
Foldable (Ctx v) Source # | |||||
Defined in Swarm.Language.Context Methods fold :: Monoid m => Ctx v m -> m # foldMap :: Monoid m => (a -> m) -> Ctx v a -> m # foldMap' :: Monoid m => (a -> m) -> Ctx v a -> m # foldr :: (a -> b -> b) -> b -> Ctx v a -> b # foldr' :: (a -> b -> b) -> b -> Ctx v a -> b # foldl :: (b -> a -> b) -> b -> Ctx v a -> b # foldl' :: (b -> a -> b) -> b -> Ctx v a -> b # foldr1 :: (a -> a -> a) -> Ctx v a -> a # foldl1 :: (a -> a -> a) -> Ctx v a -> a # elem :: Eq a => a -> Ctx v a -> Bool # maximum :: Ord a => Ctx v a -> a # minimum :: Ord a => Ctx v a -> a # | |||||
Traversable (Ctx v) Source # | |||||
Functor (Ctx v) Source # | |||||
ToJSON (Ctx v t) Source # | Serialize a context simply as its hash; we assume that a top-level CtxMap has been seralized somewhere, from which we can recover this context by looking it up. | ||||
(Data v, Data t, Ord v) => Data (Ctx v t) Source # | |||||
Defined in Swarm.Language.Context Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ctx v t -> c (Ctx v t) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ctx v t) # toConstr :: Ctx v t -> Constr # dataTypeOf :: Ctx v t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Ctx v t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Ctx v t)) # gmapT :: (forall b. Data b => b -> b) -> Ctx v t -> Ctx v t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ctx v t -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ctx v t -> r # gmapQ :: (forall d. Data d => d -> u) -> Ctx v t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ctx v t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ctx v t -> m (Ctx v t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ctx v t -> m (Ctx v t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ctx v t -> m (Ctx v t) # | |||||
(Ord v, Hashable v, Hashable t) => Monoid (Ctx v t) Source # | |||||
(Ord v, Hashable v, Hashable t) => Semigroup (Ctx v t) Source # | The semigroup operation for contexts is right-biased union. | ||||
Generic (Ctx v t) Source # | |||||
Defined in Swarm.Language.Context Associated Types
| |||||
Show (Ctx v t) Source # | |||||
Eq (Ctx v t) Source # | Compare contexts for equality just by comparing their hashes. | ||||
(Hashable v, Hashable t) => Hashable (Ctx v t) Source # | |||||
Defined in Swarm.Language.Context | |||||
AsEmpty (Ctx v t) Source # | |||||
Defined in Swarm.Language.Context | |||||
PrettyPrec t => PrettyPrec (Ctx v t) Source # | |||||
Defined in Swarm.Language.Context Methods prettyPrec :: Int -> Ctx v t -> Doc ann | |||||
Ord v => FromJSONE (CtxMap CtxTree v t) (Ctx v t) Source # | Deserialize a context. We expect to see a hash, and look it up in the provided CtxMap. | ||||
Defined in Swarm.Language.Context | |||||
type Rep (Ctx v t) Source # | |||||
Defined in Swarm.Language.Context type Rep (Ctx v t) = D1 ('MetaData "Ctx" "Swarm.Language.Context" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "Ctx" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCtx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map v t)) :*: S1 ('MetaSel ('Just "ctxStruct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (CtxTree v t)))) |
rollCtx :: (Ord v, Hashable v, Hashable t) => CtxF Ctx v t -> Ctx v t Source #
"Roll up" one level of context structure while building a new top-level Map and computing an appropriate top-level hash.
In other words, the input of type CtxF Ctx t
represents a
context where the topmost level of structure is split out by
itself as CtxF
, with the rest of the recursive structure stored
in the embedded Ctx
values. rollCtx
takes the single level
of structure with recursive subtrees and "rolls them up" into one
recursive tree.
lookupR :: forall v t (sig :: (Type -> Type) -> Type -> Type) m. (Ord v, Has (Reader (Ctx v t)) sig m) => v -> m (Maybe t) Source #
Look up a variable in a context in an ambient Reader effect.
delete :: (Ord v, Hashable v, Hashable t) => v -> Ctx v t -> Ctx v t Source #
Delete a variable from a context.
addBinding :: (Ord v, Hashable v, Hashable t) => v -> t -> Ctx v t -> Ctx v t Source #
Add a key-value binding to a context (overwriting the old one if the key is already present).
union :: (Ord v, Hashable v, Hashable t) => Ctx v t -> Ctx v t -> Ctx v t Source #
Right-biased union of contexts.
withBinding :: forall v t (sig :: (Type -> Type) -> Type -> Type) m a. (Has (Reader (Ctx v t)) sig m, Ord v, Hashable v, Hashable t) => v -> t -> m a -> m a Source #
Locally extend the context with an additional binding.
withBindings :: forall v t (sig :: (Type -> Type) -> Type -> Type) m a. (Has (Reader (Ctx v t)) sig m, Ord v, Hashable v, Hashable t) => Ctx v t -> m a -> m a Source #
Locally extend the context with an additional context of bindings.
type CtxMap (f :: Type -> Type -> Type) v t = Map CtxHash (CtxF f v t) Source #
A CtxMap
maps context hashes to context structures. Those
structures could either be complete context trees, or just a
single level of structure containing more hashes.
getCtx :: Ord v => CtxHash -> CtxMap CtxTree v t -> Maybe (Ctx v t) Source #
Reconstitute the context corresponding to a particular hash, by looking it up in a context map.
toCtxMap :: Ord v => Ctx v t -> CtxMap CtxTree v t Source #
Turn a context into a context map containing every subtree of its structure.
buildCtxMap :: forall v t m (sig :: (Type -> Type) -> Type -> Type). (Ord v, Has (State (CtxMap CtxTree v t)) sig m) => Map v t -> CtxTree v t -> m () Source #
Build a context map by keeping track of the incrementally built map in a state effect, and traverse the given context structure to add all subtrees to the map---but, of course, stopping without recursing further whenever we see a hash that is already in the map.
newtype ConstHash v t Source #
Instances
FromJSON (ConstHash v t) Source # | |||||
Defined in Swarm.Language.Context | |||||
ToJSON (ConstHash v t) Source # | |||||
Generic (ConstHash v t) Source # | |||||
Defined in Swarm.Language.Context Associated Types
| |||||
Show (ConstHash v t) Source # | |||||
Eq (ConstHash v t) Source # | |||||
type Rep (ConstHash v t) Source # | |||||
Defined in Swarm.Language.Context |
dehydrate :: CtxMap CtxTree v t -> CtxMap ConstHash v t Source #
Dehydrate a context map by replacing the actual context trees with single structure layers containing only hashes. A dehydrated context map is very suitable for serializing, since it makes sharing completely explicit---even if a given context is referenced multiple times, the references are simply hash values, and the context is stored only once, under its hash.
rehydrate :: CtxMap ConstHash v t -> CtxMap CtxTree v t Source #
Rehydrate a dehydrated context map by replacing every hash with an actual context structure. We do this by building the result as a lazy, recursive map, replacing each hash by the result we get when looking it up in the map being built. A context which is referenced multiple times will thus be shared in memory.