{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE TypeFamilies #-}
module Unbound.Generics.LocallyNameless.Shift where
import Control.Applicative
import Control.DeepSeq (NFData(..))
import Data.Monoid (Monoid(..), All(..))
import Unbound.Generics.LocallyNameless.Alpha (Alpha(..),
decrLevelCtx, isTermCtx,
isZeroLevelCtx,
inconsistentDisjointSet)
import Unbound.Generics.LocallyNameless.Embed (IsEmbed(..))
import Unbound.Generics.LocallyNameless.Internal.Iso (iso)
newtype Shift e = Shift e
instance Functor Shift where
fmap f (Shift e) = Shift (f e)
instance IsEmbed e => IsEmbed (Shift e) where
type Embedded (Shift e) = Embedded e
embedded = iso (\(Shift e) -> e) Shift . embedded
instance NFData e => NFData (Shift e) where
rnf (Shift e) = rnf e `seq` ()
instance Show e => Show (Shift e) where
showsPrec _ (Shift e) = showString "{" . showsPrec 0 e . showString "}"
instance Alpha e => Alpha (Shift e) where
isPat (Shift e) = if (isEmbed e) then mempty else inconsistentDisjointSet
isTerm _ = All False
isEmbed (Shift e) = isEmbed e
swaps' ctx perm (Shift e) = Shift (swaps' (decrLevelCtx ctx) perm e)
freshen' ctx p =
if isTermCtx ctx
then error "LocallyNameless.freshen' called on a term"
else return (p, mempty)
lfreshen' ctx p kont =
if isTermCtx ctx
then error "LocallyNameless.lfreshen' called on a term"
else kont p mempty
aeq' ctx (Shift e1) (Shift e2) = aeq' ctx e1 e2
fvAny' ctx afa (Shift e) = Shift <$> fvAny' ctx afa e
close ctx b se@(Shift e) =
if isTermCtx ctx
then error "LocallyNameless.close on Shift"
else if isZeroLevelCtx ctx
then
se
else Shift (close (decrLevelCtx ctx) b e)
open ctx b se@(Shift e) =
if isTermCtx ctx
then error "LocallyNameless.open on Shift"
else if isZeroLevelCtx ctx
then se
else Shift (open (decrLevelCtx ctx) b e)
nthPatFind (Shift e) = nthPatFind e
namePatFind (Shift e) = namePatFind e
acompare' ctx (Shift x) (Shift y) = acompare' ctx x y