zabt-0.3.0.0: Arity-typed abstract binding trees

Safe HaskellNone
LanguageHaskell2010

Zabt.View

Synopsis

Documentation

data View v f x a where Source #

Constructors

VVar :: !v -> View v f x G 
VPat :: f x -> View v f x G 
VAbs :: !v -> x a -> View v f x (B a) 

Instances

(Eq (x a), Eq (f x)) => Eq (View v f x (B a)) Source #

Alpha-equivalence

Methods

(==) :: View v f x (B a) -> View v f x (B a) -> Bool #

(/=) :: View v f x (B a) -> View v f x (B a) -> Bool #

(Eq v, Eq (f x)) => Eq (View v f x G) Source #

Alpha-equivalence

Methods

(==) :: View v f x G -> View v f x G -> Bool #

(/=) :: View v f x G -> View v f x G -> Bool #

(Ord v, Ord (x a), Ord (f x)) => Ord (View v f x (B a)) Source # 

Methods

compare :: View v f x (B a) -> View v f x (B a) -> Ordering #

(<) :: View v f x (B a) -> View v f x (B a) -> Bool #

(<=) :: View v f x (B a) -> View v f x (B a) -> Bool #

(>) :: View v f x (B a) -> View v f x (B a) -> Bool #

(>=) :: View v f x (B a) -> View v f x (B a) -> Bool #

max :: View v f x (B a) -> View v f x (B a) -> View v f x (B a) #

min :: View v f x (B a) -> View v f x (B a) -> View v f x (B a) #

(Ord v, Ord (f x)) => Ord (View v f x G) Source # 

Methods

compare :: View v f x G -> View v f x G -> Ordering #

(<) :: View v f x G -> View v f x G -> Bool #

(<=) :: View v f x G -> View v f x G -> Bool #

(>) :: View v f x G -> View v f x G -> Bool #

(>=) :: View v f x G -> View v f x G -> Bool #

max :: View v f x G -> View v f x G -> View v f x G #

min :: View v f x G -> View v f x G -> View v f x G #

(Show v, Show (x a), Show (f x)) => Show (View v f x (B a)) Source # 

Methods

showsPrec :: Int -> View v f x (B a) -> ShowS #

show :: View v f x (B a) -> String #

showList :: [View v f x (B a)] -> ShowS #

(Show v, Show (x G), Show (f x)) => Show (View v f x G) Source # 

Methods

showsPrec :: Int -> View v f x G -> ShowS #

show :: View v f x G -> String #

showList :: [View v f x G] -> ShowS #

pattern Var :: forall f v a. (Visits f, Freshen v, Ord v) => (~#) Arity Arity a G => v -> Term v f a Source #

Var v creates and matches a Term value corresponding to a free variable.

pattern Abs :: forall f v a. (Visits f, Freshen v, Ord v) => forall a1. (~#) Arity Arity a (B a1) => v -> Term v f a1 -> Term v f a Source #

Abs v t creates and matches a Term value where the free variable v has been abstracted over, becoming bound.

pattern Pat :: forall f v a. (Visits f, Freshen v, Ord v) => (~#) Arity Arity a G => f (Term v f) -> Term v f a Source #

Pat f creates and matches a Term value built from a layer of the pattern functor f.

fold :: (Visits f, Ord v) => View v f (Term v f) a -> Term v f a Source #

unfold :: (Visits f, Ord v, Freshen v) => Term v f a -> View v f (Term v f) a Source #