swarm-0.7.0.0: 2D resource gathering game with programmable robots
LicenseBSD-3-Clause
Safe HaskellNone
LanguageHaskell2010

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

Documentation

newtype CtxHash Source #

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

Instances details
FromJSON CtxHash Source # 
Instance details

Defined in Swarm.Language.Context

FromJSONKey CtxHash Source # 
Instance details

Defined in Swarm.Language.Context

ToJSON CtxHash Source # 
Instance details

Defined in Swarm.Language.Context

ToJSONKey CtxHash Source # 
Instance details

Defined in Swarm.Language.Context

Data CtxHash Source # 
Instance details

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 # 
Instance details

Defined in Swarm.Language.Context

Semigroup CtxHash Source # 
Instance details

Defined in Swarm.Language.Context

Generic CtxHash Source # 
Instance details

Defined in Swarm.Language.Context

Associated Types

type Rep CtxHash 
Instance details

Defined in Swarm.Language.Context

type Rep CtxHash = D1 ('MetaData "CtxHash" "Swarm.Language.Context" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'True) (C1 ('MetaCons "CtxHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "getCtxHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

Methods

from :: CtxHash -> Rep CtxHash x #

to :: Rep CtxHash x -> CtxHash #

Num CtxHash Source # 
Instance details

Defined in Swarm.Language.Context

Show CtxHash Source # 
Instance details

Defined in Swarm.Language.Context

Eq CtxHash Source # 
Instance details

Defined in Swarm.Language.Context

Methods

(==) :: CtxHash -> CtxHash -> Bool #

(/=) :: CtxHash -> CtxHash -> Bool #

Ord CtxHash Source # 
Instance details

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.

Instance details

Defined in Swarm.Language.Context

Methods

parseJSONE :: Value -> ParserE (CtxMap CtxTree v t) (Ctx v t)

parseJSONE' :: CtxMap CtxTree v t -> Value -> Parser (Ctx v t)

type Rep CtxHash Source # 
Instance details

Defined in Swarm.Language.Context

type Rep CtxHash = D1 ('MetaData "CtxHash" "Swarm.Language.Context" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'True) (C1 ('MetaCons "CtxHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "getCtxHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

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.

Constructors

CtxEmpty 
CtxSingle v t 
CtxDelete v t (f v t) 
CtxUnion (f v t) (f v t) 

Instances

Instances details
Foldable (f v) => Foldable (CtxF f v) Source # 
Instance details

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 #

toList :: CtxF f v a -> [a] #

null :: CtxF f v a -> Bool #

length :: CtxF f v a -> Int #

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 #

sum :: Num a => CtxF f v a -> a #

product :: Num a => CtxF f v a -> a #

Traversable (f v) => Traversable (CtxF f v) Source # 
Instance details

Defined in Swarm.Language.Context

Methods

traverse :: Applicative f0 => (a -> f0 b) -> CtxF f v a -> f0 (CtxF f v b) #

sequenceA :: Applicative f0 => CtxF f v (f0 a) -> f0 (CtxF f v a) #

mapM :: Monad m => (a -> m b) -> CtxF f v a -> m (CtxF f v b) #

sequence :: Monad m => CtxF f v (m a) -> m (CtxF f v a) #

Functor (f v) => Functor (CtxF f v) Source # 
Instance details

Defined in Swarm.Language.Context

Methods

fmap :: (a -> b) -> CtxF f v a -> CtxF f v b #

(<$) :: a -> CtxF f v b -> CtxF f v a #

(FromJSON v, FromJSON t, FromJSON (f v t)) => FromJSON (CtxF f v t) Source # 
Instance details

Defined in Swarm.Language.Context

Methods

parseJSON :: Value -> Parser (CtxF f v t) #

parseJSONList :: Value -> Parser [CtxF f v t] #

omittedField :: Maybe (CtxF f v t) #

(ToJSON v, ToJSON t, ToJSON (f v t)) => ToJSON (CtxF f v t) Source # 
Instance details

Defined in Swarm.Language.Context

Methods

toJSON :: CtxF f v t -> Value #

toEncoding :: CtxF f v t -> Encoding #

toJSONList :: [CtxF f v t] -> Value #

toEncodingList :: [CtxF f v t] -> Encoding #

omitField :: CtxF f v t -> Bool #

(Typeable f, Data v, Data t, Data (f v t)) => Data (CtxF f v t) Source # 
Instance details

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 # 
Instance details

Defined in Swarm.Language.Context

Methods

from :: CtxF f v t -> Rep (CtxF f v t) x #

to :: Rep (CtxF f v t) x -> CtxF f v t #

(Show v, Show t, Show (f v t)) => Show (CtxF f v t) Source # 
Instance details

Defined in Swarm.Language.Context

Methods

showsPrec :: Int -> CtxF f v t -> ShowS #

show :: CtxF f v t -> String #

showList :: [CtxF f v t] -> ShowS #

(Eq v, Eq t, Eq (f v t)) => Eq (CtxF f v t) Source # 
Instance details

Defined in Swarm.Language.Context

Methods

(==) :: CtxF f v t -> CtxF f v t -> Bool #

(/=) :: CtxF f v t -> CtxF f v t -> Bool #

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.

Instance details

Defined in Swarm.Language.Context

Methods

parseJSONE :: Value -> ParserE (CtxMap CtxTree v t) (Ctx v t)

parseJSONE' :: CtxMap CtxTree v t -> Value -> Parser (Ctx v t)

type Rep (CtxF f v t) Source # 
Instance details

Defined in Swarm.Language.Context

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.

data CtxTree v t Source #

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.

Constructors

CtxTree CtxHash (CtxF CtxTree v t) 

Instances

Instances details
Foldable (CtxTree v) Source # 
Instance details

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] #

null :: CtxTree v a -> Bool #

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 #

sum :: Num a => CtxTree v a -> a #

product :: Num a => CtxTree v a -> a #

Traversable (CtxTree v) Source # 
Instance details

Defined in Swarm.Language.Context

Methods

traverse :: Applicative f => (a -> f b) -> CtxTree v a -> f (CtxTree v b) #

sequenceA :: Applicative f => CtxTree v (f a) -> f (CtxTree v a) #

mapM :: Monad m => (a -> m b) -> CtxTree v a -> m (CtxTree v b) #

sequence :: Monad m => CtxTree v (m a) -> m (CtxTree v a) #

Functor (CtxTree v) Source # 
Instance details

Defined in Swarm.Language.Context

Methods

fmap :: (a -> b) -> CtxTree v a -> CtxTree v b #

(<$) :: a -> CtxTree v b -> CtxTree v a #

(FromJSON v, FromJSON t) => FromJSON (CtxTree v t) Source # 
Instance details

Defined in Swarm.Language.Context

(ToJSON v, ToJSON t) => ToJSON (CtxTree v t) Source # 
Instance details

Defined in Swarm.Language.Context

(Data v, Data t) => Data (CtxTree v t) Source # 
Instance details

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 # 
Instance details

Defined in Swarm.Language.Context

Associated Types

type Rep (CtxTree v t) 
Instance details

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))))

Methods

from :: CtxTree v t -> Rep (CtxTree v t) x #

to :: Rep (CtxTree v t) x -> CtxTree v t #

(Show v, Show t) => Show (CtxTree v t) Source # 
Instance details

Defined in Swarm.Language.Context

Methods

showsPrec :: Int -> CtxTree v t -> ShowS #

show :: CtxTree v t -> String #

showList :: [CtxTree v t] -> ShowS #

(Eq v, Eq t) => Eq (CtxTree v t) Source # 
Instance details

Defined in Swarm.Language.Context

Methods

(==) :: CtxTree v t -> CtxTree v t -> Bool #

(/=) :: CtxTree v t -> CtxTree v t -> Bool #

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.

Instance details

Defined in Swarm.Language.Context

Methods

parseJSONE :: Value -> ParserE (CtxMap CtxTree v t) (Ctx v t)

parseJSONE' :: CtxMap CtxTree v t -> Value -> Parser (Ctx v t)

type Rep (CtxTree v t) Source # 
Instance details

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))))

data Ctx v t Source #

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).

Constructors

Ctx 

Fields

Instances

Instances details
Foldable (Ctx v) Source # 
Instance details

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 #

toList :: Ctx v a -> [a] #

null :: Ctx v a -> Bool #

length :: Ctx v a -> Int #

elem :: Eq a => a -> Ctx v a -> Bool #

maximum :: Ord a => Ctx v a -> a #

minimum :: Ord a => Ctx v a -> a #

sum :: Num a => Ctx v a -> a #

product :: Num a => Ctx v a -> a #

Traversable (Ctx v) Source # 
Instance details

Defined in Swarm.Language.Context

Methods

traverse :: Applicative f => (a -> f b) -> Ctx v a -> f (Ctx v b) #

sequenceA :: Applicative f => Ctx v (f a) -> f (Ctx v a) #

mapM :: Monad m => (a -> m b) -> Ctx v a -> m (Ctx v b) #

sequence :: Monad m => Ctx v (m a) -> m (Ctx v a) #

Functor (Ctx v) Source # 
Instance details

Defined in Swarm.Language.Context

Methods

fmap :: (a -> b) -> Ctx v a -> Ctx v b #

(<$) :: a -> Ctx v b -> Ctx v a #

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.

Instance details

Defined in Swarm.Language.Context

Methods

toJSON :: Ctx v t -> Value #

toEncoding :: Ctx v t -> Encoding #

toJSONList :: [Ctx v t] -> Value #

toEncodingList :: [Ctx v t] -> Encoding #

omitField :: Ctx v t -> Bool #

(Data v, Data t, Ord v) => Data (Ctx v t) Source # 
Instance details

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 # 
Instance details

Defined in Swarm.Language.Context

Methods

mempty :: Ctx v t #

mappend :: Ctx v t -> Ctx v t -> Ctx v t #

mconcat :: [Ctx v t] -> Ctx v t #

(Ord v, Hashable v, Hashable t) => Semigroup (Ctx v t) Source #

The semigroup operation for contexts is right-biased union.

Instance details

Defined in Swarm.Language.Context

Methods

(<>) :: Ctx v t -> Ctx v t -> Ctx v t #

sconcat :: NonEmpty (Ctx v t) -> Ctx v t #

stimes :: Integral b => b -> Ctx v t -> Ctx v t #

Generic (Ctx v t) Source # 
Instance details

Defined in Swarm.Language.Context

Associated Types

type Rep (Ctx v t) 
Instance details

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))))

Methods

from :: Ctx v t -> Rep (Ctx v t) x #

to :: Rep (Ctx v t) x -> Ctx v t #

Show (Ctx v t) Source # 
Instance details

Defined in Swarm.Language.Context

Methods

showsPrec :: Int -> Ctx v t -> ShowS #

show :: Ctx v t -> String #

showList :: [Ctx v t] -> ShowS #

Eq (Ctx v t) Source #

Compare contexts for equality just by comparing their hashes.

Instance details

Defined in Swarm.Language.Context

Methods

(==) :: Ctx v t -> Ctx v t -> Bool #

(/=) :: Ctx v t -> Ctx v t -> Bool #

(Hashable v, Hashable t) => Hashable (Ctx v t) Source # 
Instance details

Defined in Swarm.Language.Context

Methods

hashWithSalt :: Int -> Ctx v t -> Int #

hash :: Ctx v t -> Int #

AsEmpty (Ctx v t) Source # 
Instance details

Defined in Swarm.Language.Context

Methods

_Empty :: Prism' (Ctx v t) () #

PrettyPrec t => PrettyPrec (Ctx v t) Source # 
Instance details

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.

Instance details

Defined in Swarm.Language.Context

Methods

parseJSONE :: Value -> ParserE (CtxMap CtxTree v t) (Ctx v t)

parseJSONE' :: CtxMap CtxTree v t -> Value -> Parser (Ctx v t)

type Rep (Ctx v t) Source # 
Instance details

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))))

ctxHash :: Ctx v t -> CtxHash Source #

Get the top-level hash of a context.

ctxFromTree :: Ord v => CtxTree v t -> Ctx v t Source #

Rebuild a complete Ctx from a CtxTree.

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.

empty :: Ctx v t Source #

The empty context.

singleton :: (Ord v, Hashable v, Hashable t) => v -> t -> Ctx v t Source #

A singleton context.

fromMap :: (Ord v, Hashable v, Hashable t) => Map v t -> Ctx v t Source #

Create a Ctx from a Map.

lookup :: Ord v => v -> Ctx v t -> Maybe t Source #

Look up a variable in a context.

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.

assocs :: Ctx v t -> [(v, t)] Source #

Get the list of key-value associations from a context.

vars :: Ctx v t -> [v] Source #

Get the list of bound variables 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 #

Constructors

ConstHash CtxHash 

Instances

Instances details
FromJSON (ConstHash v t) Source # 
Instance details

Defined in Swarm.Language.Context

ToJSON (ConstHash v t) Source # 
Instance details

Defined in Swarm.Language.Context

Generic (ConstHash v t) Source # 
Instance details

Defined in Swarm.Language.Context

Associated Types

type Rep (ConstHash v t) 
Instance details

Defined in Swarm.Language.Context

type Rep (ConstHash v t) = D1 ('MetaData "ConstHash" "Swarm.Language.Context" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'True) (C1 ('MetaCons "ConstHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CtxHash)))

Methods

from :: ConstHash v t -> Rep (ConstHash v t) x #

to :: Rep (ConstHash v t) x -> ConstHash v t #

Show (ConstHash v t) Source # 
Instance details

Defined in Swarm.Language.Context

Methods

showsPrec :: Int -> ConstHash v t -> ShowS #

show :: ConstHash v t -> String #

showList :: [ConstHash v t] -> ShowS #

Eq (ConstHash v t) Source # 
Instance details

Defined in Swarm.Language.Context

Methods

(==) :: ConstHash v t -> ConstHash v t -> Bool #

(/=) :: ConstHash v t -> ConstHash v t -> Bool #

type Rep (ConstHash v t) Source # 
Instance details

Defined in Swarm.Language.Context

type Rep (ConstHash v t) = D1 ('MetaData "ConstHash" "Swarm.Language.Context" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'True) (C1 ('MetaCons "ConstHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CtxHash)))

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.