hypertypes-0.1.0.2: Typed ASTs
Safe HaskellNone
LanguageHaskell2010

Hyper.Unify.Binding

Description

A pure data structures implementation of unification variables state

Synopsis

Documentation

newtype UVar (t :: AHyperType) Source #

A unification variable identifier pure state based unification

Constructors

UVar Int 

Instances

Instances details
Eq (UVar t) Source # 
Instance details

Defined in Hyper.Unify.Binding

Methods

(==) :: UVar t -> UVar t -> Bool #

(/=) :: UVar t -> UVar t -> Bool #

Ord (UVar t) Source # 
Instance details

Defined in Hyper.Unify.Binding

Methods

compare :: UVar t -> UVar t -> Ordering #

(<) :: UVar t -> UVar t -> Bool #

(<=) :: UVar t -> UVar t -> Bool #

(>) :: UVar t -> UVar t -> Bool #

(>=) :: UVar t -> UVar t -> Bool #

max :: UVar t -> UVar t -> UVar t #

min :: UVar t -> UVar t -> UVar t #

Show (UVar t) Source # 
Instance details

Defined in Hyper.Unify.Binding

Methods

showsPrec :: Int -> UVar t -> ShowS #

show :: UVar t -> String #

showList :: [UVar t] -> ShowS #

Generic (UVar t) Source # 
Instance details

Defined in Hyper.Unify.Binding

Associated Types

type Rep (UVar t) :: Type -> Type #

Methods

from :: UVar t -> Rep (UVar t) x #

to :: Rep (UVar t) x -> UVar t #

type Rep (UVar t) Source # 
Instance details

Defined in Hyper.Unify.Binding

type Rep (UVar t) = D1 ('MetaData "UVar" "Hyper.Unify.Binding" "hypertypes-0.1.0.2-GDiSRF0EwgQ6Mkx3yytlTL" 'True) (C1 ('MetaCons "UVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

_UVar :: forall t t. Iso (UVar t) (UVar t) Int Int Source #

newtype Binding t Source #

The state of unification variables implemented in a pure data structure

Constructors

Binding (Seq (UTerm UVar t)) 

Instances

Instances details
Constraints (Binding t) Eq => Eq (Binding t) Source # 
Instance details

Defined in Hyper.Unify.Binding

Methods

(==) :: Binding t -> Binding t -> Bool #

(/=) :: Binding t -> Binding t -> Bool #

Constraints (Binding t) Ord => Ord (Binding t) Source # 
Instance details

Defined in Hyper.Unify.Binding

Methods

compare :: Binding t -> Binding t -> Ordering #

(<) :: Binding t -> Binding t -> Bool #

(<=) :: Binding t -> Binding t -> Bool #

(>) :: Binding t -> Binding t -> Bool #

(>=) :: Binding t -> Binding t -> Bool #

max :: Binding t -> Binding t -> Binding t #

min :: Binding t -> Binding t -> Binding t #

Constraints (Binding t) Show => Show (Binding t) Source # 
Instance details

Defined in Hyper.Unify.Binding

Methods

showsPrec :: Int -> Binding t -> ShowS #

show :: Binding t -> String #

showList :: [Binding t] -> ShowS #

Generic (Binding t) Source # 
Instance details

Defined in Hyper.Unify.Binding

Associated Types

type Rep (Binding t) :: Type -> Type #

Methods

from :: Binding t -> Rep (Binding t) x #

to :: Rep (Binding t) x -> Binding t #

Constraints (Binding t) Binary => Binary (Binding t) Source # 
Instance details

Defined in Hyper.Unify.Binding

Methods

put :: Binding t -> Put #

get :: Get (Binding t) #

putList :: [Binding t] -> Put #

Constraints (Binding t) NFData => NFData (Binding t) Source # 
Instance details

Defined in Hyper.Unify.Binding

Methods

rnf :: Binding t -> () #

type Rep (Binding t) Source # 
Instance details

Defined in Hyper.Unify.Binding

type Rep (Binding t) = D1 ('MetaData "Binding" "Hyper.Unify.Binding" "hypertypes-0.1.0.2-GDiSRF0EwgQ6Mkx3yytlTL" 'True) (C1 ('MetaCons "Binding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq (UTerm UVar t)))))

_Binding :: forall t t. Iso (Binding t) (Binding t) (Seq (UTerm UVar t)) (Seq (UTerm UVar t)) Source #

bindingDict :: MonadState s m => ALens' s (Binding # t) -> BindingDict UVar m t Source #

A BindingDict for UVars in a MonadState whose state contains a Binding