unbound-generics-0.4.3: Support for programming with names and binders using GHC Generics
Copyright(c) 2015 Aleksey Kliger
LicenseBSD3 (See LICENSE)
MaintainerAleksey Kliger
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • TypeFamilies
  • KindSignatures
  • ExplicitNamespaces

Unbound.Generics.LocallyNameless.Shift

Description

The pattern Shift e shifts the scope of the embedded term in e one level outwards.

Synopsis

Documentation

newtype Shift e Source #

The type Shift e is an embedding pattern that shifts the scope of the free variables of the embedded term Embedded e up by one level.

Constructors

Shift e 

Instances

Instances details
Functor Shift Source # 
Instance details

Defined in Unbound.Generics.LocallyNameless.Shift

Methods

fmap :: (a -> b) -> Shift a -> Shift b #

(<$) :: a -> Shift b -> Shift a #

Subst c e => Subst c (Shift e) Source # 
Instance details

Defined in Unbound.Generics.LocallyNameless.Subst

Methods

isvar :: Shift e -> Maybe (SubstName (Shift e) c) Source #

isCoerceVar :: Shift e -> Maybe (SubstCoerce (Shift e) c) Source #

subst :: Name c -> c -> Shift e -> Shift e Source #

substs :: [(Name c, c)] -> Shift e -> Shift e Source #

substBvs :: AlphaCtx -> [c] -> Shift e -> Shift e Source #

Show e => Show (Shift e) Source # 
Instance details

Defined in Unbound.Generics.LocallyNameless.Shift

Methods

showsPrec :: Int -> Shift e -> ShowS #

show :: Shift e -> String #

showList :: [Shift e] -> ShowS #

NFData e => NFData (Shift e) Source # 
Instance details

Defined in Unbound.Generics.LocallyNameless.Shift

Methods

rnf :: Shift e -> () #

Alpha e => Alpha (Shift e) Source # 
Instance details

Defined in Unbound.Generics.LocallyNameless.Shift

IsEmbed e => IsEmbed (Shift e) Source # 
Instance details

Defined in Unbound.Generics.LocallyNameless.Shift

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 #

type Embedded (Shift e) Source # 
Instance details

Defined in Unbound.Generics.LocallyNameless.Shift

type Embedded (Shift e) = Embedded e