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

Copyright(c) 2014, Aleksey Kliger
LicenseBSD3 (See LICENSE)
MaintainerAleksey Kliger
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • TypeFamilies
  • DeriveGeneric
  • KindSignatures
  • ExplicitNamespaces

Unbound.Generics.LocallyNameless.Embed

Description

The pattern Embed t contains a term t.

Synopsis

Documentation

newtype Embed t Source #

Embed allows for terms to be embedded within patterns. Such embedded terms do not bind names along with the rest of the pattern. For examples, see the tutorial or examples directories.

If t is a term type, then Embed t is a pattern type.

Embed is not abstract since it involves no binding, and hence it is safe to manipulate directly. To create and destruct Embed terms, you may use the Embed constructor directly. (You may also use the functions embed and unembed, which additionally can construct or destruct any number of enclosing Shifts at the same time.)

Constructors

Embed t 

Instances

Subst c a => Subst c (Embed a) Source # 

Methods

isvar :: Embed a -> Maybe (SubstName (Embed a) c) Source #

isCoerceVar :: Embed a -> Maybe (SubstCoerce (Embed a) c) Source #

subst :: Name c -> c -> Embed a -> Embed a Source #

substs :: [(Name c, c)] -> Embed a -> Embed a Source #

Eq t => Eq (Embed t) Source # 

Methods

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

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

Ord t => Ord (Embed t) Source # 

Methods

compare :: Embed t -> Embed t -> Ordering #

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

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

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

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

max :: Embed t -> Embed t -> Embed t #

min :: Embed t -> Embed t -> Embed t #

Show a => Show (Embed a) Source # 

Methods

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

show :: Embed a -> String #

showList :: [Embed a] -> ShowS #

Generic (Embed t) Source # 

Associated Types

type Rep (Embed t) :: * -> * #

Methods

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

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

NFData t => NFData (Embed t) Source # 

Methods

rnf :: Embed t -> () #

Alpha t => Alpha (Embed t) Source # 
IsEmbed (Embed t) Source # 

Associated Types

type Embedded (Embed t) :: * Source #

Methods

embedded :: (Profunctor p, Functor f) => p (Embedded (Embed t)) (f (Embedded (Embed t))) -> p (Embed t) (f (Embed t)) Source #

type Rep (Embed t) Source # 
type Rep (Embed t) = D1 (MetaData "Embed" "Unbound.Generics.LocallyNameless.Embed" "unbound-generics-0.3.1-8vyzNZGjRzxHnWFlDb51nu" True) (C1 (MetaCons "Embed" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 t)))
type Embedded (Embed t) Source # 
type Embedded (Embed t) = t

class IsEmbed e where Source #

Minimal complete definition

embedded

Associated Types

type Embedded e :: * Source #

The term type embedded in the embedding e

Methods

embedded :: (Profunctor p, Functor f) => p (Embedded e) (f (Embedded e)) -> p e (f e) Source #

Insert or extract the embedded term. If you're not using the lens library, see embed and unembed otherwise embedded is an isomorphism that you can use with lens. embedded :: Iso' (Embedded e) e

Instances

IsEmbed (Embed t) Source # 

Associated Types

type Embedded (Embed t) :: * Source #

Methods

embedded :: (Profunctor p, Functor f) => p (Embedded (Embed t)) (f (Embedded (Embed t))) -> p (Embed t) (f (Embed t)) Source #

IsEmbed e => IsEmbed (Shift e) Source # 

Associated Types

type Embedded (Shift e) :: * Source #

Methods

embedded :: (Profunctor p, Functor f) => p (Embedded (Shift e)) (f (Embedded (Shift e))) -> p (Shift e) (f (Shift e)) Source #