{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE DeriveGeneric, TypeFamilies #-}
module Unbound.Generics.LocallyNameless.Embed where
import Control.Applicative (pure, (<$>))
import Control.DeepSeq (NFData(..))
import Data.Monoid (mempty, All(..))
import Data.Profunctor (Profunctor(..))
import GHC.Generics (Generic)
import Unbound.Generics.LocallyNameless.Alpha
import Unbound.Generics.LocallyNameless.Internal.Iso (iso)
newtype Embed t = Embed t deriving (Eq, Ord, Generic)
class IsEmbed e where
type Embedded e :: *
embedded :: (Profunctor p, Functor f) => p (Embedded e) (f (Embedded e)) -> p e (f e)
instance IsEmbed (Embed t) where
type Embedded (Embed t) = t
embedded = iso (\(Embed t) -> t) Embed
instance NFData t => NFData (Embed t) where
rnf (Embed t) = rnf t `seq` ()
instance Show a => Show (Embed a) where
showsPrec _ (Embed a) = showString "{" . showsPrec 0 a . showString "}"
instance Alpha t => Alpha (Embed t) where
isPat (Embed t) = if getAll (isTerm t) then mempty else inconsistentDisjointSet
isTerm _ = All False
isEmbed (Embed t) = getAll (isTerm t)
swaps' ctx perm (Embed t) =
if isTermCtx ctx
then Embed t
else Embed (swaps' (termCtx ctx) perm t)
freshen' ctx p =
if isTermCtx ctx
then error "LocallyNameless.freshen' called on a term"
else return (p, mempty)
lfreshen' ctx p cont =
if isTermCtx ctx
then error "LocallyNameless.lfreshen' called on a term"
else cont p mempty
aeq' ctx (Embed x) (Embed y) = aeq' (termCtx ctx) x y
fvAny' ctx afa ex@(Embed x) =
if isTermCtx ctx
then pure ex
else Embed <$> fvAny' (termCtx ctx) afa x
close ctx b (Embed x) =
if isTermCtx ctx
then error "LocallyNameless.close on Embed"
else Embed (close (termCtx ctx) b x)
open ctx b (Embed x) =
if isTermCtx ctx
then error "LocallyNameless.open on Embed"
else Embed (open (termCtx ctx) b x)
nthPatFind _ = mempty
namePatFind _ = mempty
acompare' ctx (Embed x) (Embed y) = acompare' (termCtx ctx) x y