{-# LANGUAGE UndecidableInstances, TemplateHaskell #-}
module AST.Knot.Pure
( Pure(..), _Pure, KWitness(..)
, (&#)
) where
import AST.Class.Nodes (KNodes(..))
import AST.Knot (Tree, type (#))
import AST.TH.Internal.Instances (makeCommonInstances)
import AST.TH.Traversable (makeKTraversableApplyAndBases)
import Control.Lens (Iso, iso)
import Control.Lens.Operators
import GHC.Generics (Generic)
import Text.PrettyPrint.HughesPJClass (Pretty(..))
newtype Pure k = Pure (k # Pure)
deriving stock Generic
makeKTraversableApplyAndBases ''Pure
makeCommonInstances [''Pure]
{-# INLINE _Pure #-}
_Pure :: Iso (Tree Pure k) (Tree Pure j) (Tree k Pure) (Tree j Pure)
_Pure = iso (\(Pure x) -> x) Pure
infixl 1 &#
{-# INLINE (&#) #-}
(&#) :: a -> (a -> Tree k Pure) -> Tree Pure k
x &# f = _Pure # f x
instance Pretty (k # Pure) => Pretty (Pure k) where
pPrintPrec lvl p (Pure x) = pPrintPrec lvl p x