Safe Haskell | None |
---|---|
Language | GHC2021 |
Unbound.Generics.Unify
Description
Unification for unbound-generics
Synopsis
- unify' :: (Unification t m, Unify t t) => t -> t -> m (Either UnificationError t)
- class Subst t a => Unify t a where
- unify :: Unification t m => a -> a -> m (Either UnificationError a)
- type UnificationError = (Path, UnificationErrorCause)
- data UnificationErrorCause where
- OccursCheck :: forall t. Name t -> t -> UnificationErrorCause
- DifferentConstructor :: UnificationErrorCause
- DifferentListLength :: UnificationErrorCause
- type Path = [PathElement]
- data PathElement
- class Monad m => Unification t (m :: Type -> Type) where
- currentSubst :: m (Map (Name t) t)
- recordSubst :: Name t -> t -> m ()
- type UnificationM t = UnificationMT t Identity
- runUnification :: UnificationM t a -> (a, Map (Name t) t)
- type UnificationFreshM t = UnificationMT t FreshM
- runUnificationFresh :: UnificationFreshM t a -> (a, Map (Name t) t)
- newtype UnificationMT t (m :: Type -> Type) a = UnificationMT {
- unUnificationMT :: StateT (Map (Name t) t) m a
- runUnificationT :: forall t m a. Monad m => UnificationMT t m a -> m (a, Map (Name t) t)
- class GUnify t (f :: k -> Type) where
- gunify :: forall m (a :: k). Unification t m => f a -> f a -> m (Either UnificationError (f a))
Main unification functions
unify' :: (Unification t m, Unify t t) => t -> t -> m (Either UnificationError t) Source #
Tries to unify two terms, giving back a common term, or a unification error.
This variant requires the terms to be of the same type t
as the variables within them.
class Subst t a => Unify t a where Source #
Declares the ability to unify values of type a
containing variables of type t
.
Minimal complete definition
Nothing
Methods
unify :: Unification t m => a -> a -> m (Either UnificationError a) Source #
Tries to unify two terms, giving back a common term, or a unification error.
default unify :: (Generic a, GUnify t (Rep a), Unification t m) => a -> a -> m (Either UnificationError a) Source #
Instances
Unify t String Source # | |
Defined in Unbound.Generics.Unify Methods unify :: Unification t m => String -> String -> m (Either UnificationError String) Source # | |
Unify t (Name t) Source # | |
Defined in Unbound.Generics.Unify Methods unify :: Unification t m => Name t -> Name t -> m (Either UnificationError (Name t)) Source # | |
Unify t a => Unify t [a] Source # | |
Defined in Unbound.Generics.Unify Methods unify :: Unification t m => [a] -> [a] -> m (Either UnificationError [a]) Source # |
Information about errors
type UnificationError = (Path, UnificationErrorCause) Source #
Path to navigate to a unification error.
data UnificationErrorCause where Source #
Potential causes for unification errors.
Constructors
OccursCheck :: forall t. Name t -> t -> UnificationErrorCause | |
DifferentConstructor :: UnificationErrorCause | |
DifferentListLength :: UnificationErrorCause |
Instances
Show UnificationErrorCause Source # | |
Defined in Unbound.Generics.Unify Methods showsPrec :: Int -> UnificationErrorCause -> ShowS # show :: UnificationErrorCause -> String # showList :: [UnificationErrorCause] -> ShowS # |
type Path = [PathElement] Source #
data PathElement Source #
Ways to navigate within a value.
Constructors
PathConstructor String | |
PathSelector String | |
PathIndex Int |
Instances
Show PathElement Source # | |
Defined in Unbound.Generics.Unify Methods showsPrec :: Int -> PathElement -> ShowS # show :: PathElement -> String # showList :: [PathElement] -> ShowS # | |
Eq PathElement Source # | |
Defined in Unbound.Generics.Unify |
Unification as a monad
class Monad m => Unification t (m :: Type -> Type) where Source #
Stateful storage of substitutions as required for unification.
The substitution operates only on terms and variables of type t
.
Methods
currentSubst :: m (Map (Name t) t) Source #
Obtain the current substitution.
recordSubst :: Name t -> t -> m () Source #
Add a new substitution.
Instances
Monad m => Unification t (UnificationMT t m) Source # | |
Defined in Unbound.Generics.Unify Methods currentSubst :: UnificationMT t m (Map (Name t) t) Source # recordSubst :: Name t -> t -> UnificationMT t m () Source # |
Base implementation
type UnificationM t = UnificationMT t Identity Source #
runUnification :: UnificationM t a -> (a, Map (Name t) t) Source #
Including fresh creation
type UnificationFreshM t = UnificationMT t FreshM Source #
runUnificationFresh :: UnificationFreshM t a -> (a, Map (Name t) t) Source #
As a monad transformer
newtype UnificationMT t (m :: Type -> Type) a Source #
Constructors
UnificationMT | |
Fields
|
Instances
runUnificationT :: forall t m a. Monad m => UnificationMT t m a -> m (a, Map (Name t) t) Source #
Generic methods
class GUnify t (f :: k -> Type) where Source #
Implementation of unification using GHC.Generics
.
Methods
gunify :: forall m (a :: k). Unification t m => f a -> f a -> m (Either UnificationError (f a)) Source #
Instances
GUnify t (U1 :: k -> Type) Source # | |
Defined in Unbound.Generics.Unify Methods gunify :: forall m (a :: k). Unification t m => U1 a -> U1 a -> m (Either UnificationError (U1 a)) Source # | |
(GUnify t f, GUnify t g) => GUnify t (f :*: g :: k -> Type) Source # | |
Defined in Unbound.Generics.Unify Methods gunify :: forall m (a :: k). Unification t m => (f :*: g) a -> (f :*: g) a -> m (Either UnificationError ((f :*: g) a)) Source # | |
(GUnify t f, GUnify t g) => GUnify t (f :+: g :: k -> Type) Source # | |
Defined in Unbound.Generics.Unify Methods gunify :: forall m (a :: k). Unification t m => (f :+: g) a -> (f :+: g) a -> m (Either UnificationError ((f :+: g) a)) Source # | |
(Constructor c, GUnify t f) => GUnify t (C1 c f :: k -> Type) Source # | |
Defined in Unbound.Generics.Unify Methods gunify :: forall m (a :: k). Unification t m => C1 c f a -> C1 c f a -> m (Either UnificationError (C1 c f a)) Source # | |
GUnify t f => GUnify t (D1 d f :: k -> Type) Source # | |
Defined in Unbound.Generics.Unify Methods gunify :: forall m (a :: k). Unification t m => D1 d f a -> D1 d f a -> m (Either UnificationError (D1 d f a)) Source # | |
Unify t a => GUnify t (K1 i a :: k -> Type) Source # | |
Defined in Unbound.Generics.Unify Methods gunify :: forall m (a0 :: k). Unification t m => K1 i a a0 -> K1 i a a0 -> m (Either UnificationError (K1 i a a0)) Source # | |
(Selector s, GUnify t f) => GUnify t (S1 s f :: k -> Type) Source # | |
Defined in Unbound.Generics.Unify Methods gunify :: forall m (a :: k). Unification t m => S1 s f a -> S1 s f a -> m (Either UnificationError (S1 s f a)) Source # |