unbound-generics-0.3.3: Support for programming with names and binders using GHC Generics

Copyright(c) 2014 Aleksey Kliger
LicenseBSD3 (See LICENSE)
MaintainerAleksey Kliger
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010
ExtensionsDeriveGeneric

Unbound.Generics.LocallyNameless.Rec

Description

The pattern Rec p binds the names in p like p itself would, but additionally, the names in p are scope over p.

The term TRec p is shorthand for Bind (Rec p) ()

Synopsis

Documentation

data Rec p Source #

If p is a pattern type, then Rec p is also a pattern type, which is recursive in the sense that p may bind names in terms embedded within itself. Useful for encoding e.g. lectrec and Agda's dot notation.

Instances

Subst c p => Subst c (Rec p) Source # 

Methods

isvar :: Rec p -> Maybe (SubstName (Rec p) c) Source #

isCoerceVar :: Rec p -> Maybe (SubstCoerce (Rec p) c) Source #

subst :: Name c -> c -> Rec p -> Rec p Source #

substs :: [(Name c, c)] -> Rec p -> Rec p Source #

Eq p => Eq (Rec p) Source # 

Methods

(==) :: Rec p -> Rec p -> Bool #

(/=) :: Rec p -> Rec p -> Bool #

Show a => Show (Rec a) Source # 

Methods

showsPrec :: Int -> Rec a -> ShowS #

show :: Rec a -> String #

showList :: [Rec a] -> ShowS #

Generic (Rec p) Source # 

Associated Types

type Rep (Rec p) :: * -> * #

Methods

from :: Rec p -> Rep (Rec p) x #

to :: Rep (Rec p) x -> Rec p #

NFData p => NFData (Rec p) Source # 

Methods

rnf :: Rec p -> () #

Alpha p => Alpha (Rec p) Source # 
type Rep (Rec p) Source # 
type Rep (Rec p) = D1 * (MetaData "Rec" "Unbound.Generics.LocallyNameless.Rec" "unbound-generics-0.3.3-Bd10VW6EVFQ8rThToStmHN" True) (C1 * (MetaCons "Rec" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * p)))

rec :: Alpha p => p -> Rec p Source #

Constructor for recursive patterns.

unrec :: Alpha p => Rec p -> p Source #

Destructor for recursive patterns.

newtype TRec p Source #

TRec is a standalone variant of Rec: the only difference is that whereas Rec p is a pattern type, TRec p is a term type. It is isomorphic to Bind (Rec p) ().

Note that TRec corresponds to Pottier's abstraction construct from alpha-Caml. In this context, Embed t corresponds to alpha-Caml's inner t, and Shift (Embed t) corresponds to alpha-Caml's outer t.

Constructors

TRec (Bind (Rec p) ()) 

Instances

(Alpha p, Subst c p) => Subst c (TRec p) Source # 

Methods

isvar :: TRec p -> Maybe (SubstName (TRec p) c) Source #

isCoerceVar :: TRec p -> Maybe (SubstCoerce (TRec p) c) Source #

subst :: Name c -> c -> TRec p -> TRec p Source #

substs :: [(Name c, c)] -> TRec p -> TRec p Source #

Show a => Show (TRec a) Source # 

Methods

showsPrec :: Int -> TRec a -> ShowS #

show :: TRec a -> String #

showList :: [TRec a] -> ShowS #

Generic (TRec p) Source # 

Associated Types

type Rep (TRec p) :: * -> * #

Methods

from :: TRec p -> Rep (TRec p) x #

to :: Rep (TRec p) x -> TRec p #

Alpha p => Alpha (TRec p) Source # 
type Rep (TRec p) Source # 
type Rep (TRec p) = D1 * (MetaData "TRec" "Unbound.Generics.LocallyNameless.Rec" "unbound-generics-0.3.3-Bd10VW6EVFQ8rThToStmHN" True) (C1 * (MetaCons "TRec" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Bind (Rec p) ()))))