{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE DeriveGeneric #-}
module Unbound.Generics.LocallyNameless.Rec
(
Rec
, rec
, unrec
, TRec (..)
) where
import Control.DeepSeq (NFData(..))
import GHC.Generics (Generic)
import Data.Monoid(All(..))
import Unbound.Generics.LocallyNameless.Alpha
import Unbound.Generics.LocallyNameless.Bind
newtype Rec p = Rec p
deriving (Generic, Eq)
instance NFData p => NFData (Rec p) where
rnf (Rec p) = rnf p `seq` ()
instance Show a => Show (Rec a) where
showsPrec _ (Rec a) = showString "[" . showsPrec 0 a . showString "]"
newtype TRec p = TRec (Bind (Rec p) ())
deriving (Generic)
instance Show a => Show (TRec a) where
showsPrec _ (TRec (B (Rec p) ())) = showString "[" . showsPrec 0 p . showString "]"
instance Alpha p => Alpha (Rec p) where
isTerm _ = All False
isPat (Rec p) = isPat p
nthPatFind (Rec p) = nthPatFind p
namePatFind (Rec p) = namePatFind p
open ctx b (Rec p) = Rec (open (incrLevelCtx ctx) b p)
close ctx b (Rec p) = Rec (close (incrLevelCtx ctx) b p)
instance Alpha p => Alpha (TRec p)
rec :: Alpha p => p -> Rec p
rec p = Rec (close (patternCtx initialCtx) (namePatFind p) p)
unrec :: Alpha p => Rec p -> p
unrec r@(Rec p) = open (patternCtx initialCtx) (nthPatFind r) p