{-# LANGUAGE UndecidableInstances, TemplateHaskell, FlexibleInstances #-}
module AST.Combinator.ANode
( ANode(..), _ANode
) where
import AST.Class.Has (HasChild(..))
import AST.Knot (Tree, type (#))
import AST.TH.Internal.Instances (makeCommonInstances)
import AST.TH.Traversable (makeKTraversableApplyAndBases)
import Control.Lens (Iso, iso)
import GHC.Generics (Generic)
newtype ANode c k = MkANode (k # c)
deriving stock Generic
{-# INLINE _ANode #-}
_ANode :: Iso (Tree (ANode c0) k0) (Tree (ANode c1) k1) (Tree k0 c0) (Tree k1 c1)
_ANode = iso (\(MkANode x) -> x) MkANode
makeKTraversableApplyAndBases ''ANode
makeCommonInstances [''ANode]
instance HasChild (ANode c) c where
{-# INLINE getChild #-}
getChild = _ANode