License | BSD-3-Clause |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Swarm.Effect.Unify.Common
Description
implementations of unification.
Synopsis
- newtype Subst n a = Subst {}
- dom :: Subst n a -> Set n
- idS :: Subst n a
- (|->) :: n -> a -> Subst n a
- insert :: Ord n => n -> a -> Subst n a -> Subst n a
- lookup :: Ord n => n -> Subst n a -> Maybe a
- lookupS :: forall n a (sig :: (Type -> Type) -> Type -> Type) m. (Ord n, Has (State (Subst n a)) sig m) => n -> m (Maybe a)
Documentation
A value of type Subst n a
is a substitution which maps
names of type n
(the domain, see dom
) to values of type
a
. Substitutions can be applied to certain terms (see
subst
), replacing any free occurrences of names in the
domain with their corresponding values. Thus, substitutions can
be thought of as functions of type Term -> Term
(for suitable
Term
s that contain names and values of the right type).
Concretely, substitutions are stored using a Map
.
Instances
Functor (Subst n) Source # | |
(Show n, Show a) => Show (Subst n a) Source # | |
(Eq n, Eq a) => Eq (Subst n a) Source # | |
(Ord n, Ord a) => Ord (Subst n a) Source # | |
dom :: Subst n a -> Set n Source #
The domain of a substitution is the set of names for which the substitution is defined.
The identity substitution, i.e. the unique substitution with an empty domain, which acts as the identity function on terms.
(|->) :: n -> a -> Subst n a Source #
Construct a singleton substitution, which maps the given name to the given value.
insert :: Ord n => n -> a -> Subst n a -> Subst n a Source #
Insert a new name/value binding into the substitution.