{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoImplicitPrelude #-}

-- |
-- Module      : Data.Morpheus.Types.SelectionTree
-- Description : A simple interface for Morpheus internal Selection Set's representation.
module Data.Morpheus.Types.SelectionTree where

import Data.Morpheus.Internal.Utils (keyOf)
import Data.Morpheus.Types.Internal.AST
  ( Selection (..),
    SelectionContent (..),
    UnionTag (..),
    VALID,
    unpackName,
  )
import Data.Text (unpack)
import Relude

-- | The 'SelectionTree' instance is a simple interface for interacting
-- with morpheus's internal AST while keeping the ability to safely change the concrete
-- representation of the AST.
-- The set of operation is very limited on purpose.
class SelectionTree nodeType where
  -- | leaf test: is the list of children empty?
  isLeaf :: nodeType -> Bool

  -- | Get the children
  getChildrenList :: nodeType -> [nodeType]

  -- | get a node's name
  getName :: IsString name => nodeType -> name

instance SelectionTree (Selection VALID) where
  isLeaf :: Selection VALID -> Bool
isLeaf Selection VALID
node = case forall (s :: Stage). Selection s -> SelectionContent s
selectionContent Selection VALID
node of
    SelectionContent VALID
SelectionField -> Bool
True
    SelectionContent VALID
_ -> Bool
False

  getChildrenList :: Selection VALID -> [Selection VALID]
getChildrenList Selection VALID
node = case forall (s :: Stage). Selection s -> SelectionContent s
selectionContent Selection VALID
node of
    SelectionContent VALID
SelectionField -> forall a. Monoid a => a
mempty
    (SelectionSet SelectionSet VALID
deeperSel) -> forall (t :: * -> *) a. Foldable t => t a -> [a]
toList SelectionSet VALID
deeperSel
    (UnionSelection SelectionSet VALID
interfaceSelection UnionSelection VALID
sel) ->
      forall (t :: * -> *) a. Foldable t => t a -> [a]
toList SelectionSet VALID
interfaceSelection
        forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap
          (forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnionTag -> SelectionSet VALID
unionTagSelection)
          (forall (t :: * -> *) a. Foldable t => t a -> [a]
toList UnionSelection VALID
sel)

  getName :: forall name. IsString name => Selection VALID -> name
getName =
    forall a. IsString a => String -> a
fromString
      forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack
      forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a (t :: NAME). NamePacking a => Name t -> a
unpackName
      forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. KeyOf k a => a -> k
keyOf