module XmlParser.ElementDestructionState
  ( ElementDestructionContext (..),
    ElementDestructionState,
    new,
    resolveAttributeNames,
    resolveChildNames,
  )
where

import qualified Text.XML as Xml
import qualified XmlParser.NameMap as NameMap
import qualified XmlParser.NamespaceRegistry as NamespaceRegistry
import XmlParser.Prelude

-- |
-- Context needed for the reading by functions of this component.
-- They however do not change these values.
--
-- You can use this as a parameter to a reader monad.
data ElementDestructionContext
  = ElementDestructionContext
      NamespaceRegistry.NamespaceRegistry
      -- ^ Namespace registry as seen from the context of this node.
      Xml.Element
      -- ^ The node that we're in the context of.

-- |
-- Used for the state of a parser in the context of specifically element node.
--
-- It is basically the state of the context of the parser.
--
-- You can use this as a parameter to the state monad.
data ElementDestructionState
  = ElementDestructionState
      (Maybe (NameMap.NameMap Text))
      -- ^ Cached attribute by name lookup map.
      (Maybe (NameMap.NameMap Xml.Element))
      -- ^ Cached child element by name lookup map.

new :: ElementDestructionState
new :: ElementDestructionState
new = Maybe (NameMap Text)
-> Maybe (NameMap Element) -> ElementDestructionState
ElementDestructionState Maybe (NameMap Text)
forall a. Maybe a
Nothing Maybe (NameMap Element)
forall a. Maybe a
Nothing

-- |
-- Cache attribute names once and return them.
resolveAttributeNames :: ElementDestructionContext -> ElementDestructionState -> (NameMap.NameMap Text, ElementDestructionState)
resolveAttributeNames :: ElementDestructionContext
-> ElementDestructionState
-> (NameMap Text, ElementDestructionState)
resolveAttributeNames
  (ElementDestructionContext NamespaceRegistry
nreg (Xml.Element Name
_ Map Name Text
attributes [Node]
_))
  (ElementDestructionState Maybe (NameMap Text)
attributeByNameMap Maybe (NameMap Element)
childByNameMap) =
    let resolvedAttributeByNameMap :: NameMap Text
resolvedAttributeByNameMap = NameMap Text -> Maybe (NameMap Text) -> NameMap Text
forall a. a -> Maybe a -> a
fromMaybe (NamespaceRegistry -> Map Name Text -> NameMap Text
NameMap.fromAttributes NamespaceRegistry
nreg Map Name Text
attributes) Maybe (NameMap Text)
attributeByNameMap
     in (NameMap Text
resolvedAttributeByNameMap, Maybe (NameMap Text)
-> Maybe (NameMap Element) -> ElementDestructionState
ElementDestructionState (NameMap Text -> Maybe (NameMap Text)
forall a. a -> Maybe a
Just NameMap Text
resolvedAttributeByNameMap) Maybe (NameMap Element)
childByNameMap)

-- |
-- Cache child names once and return them.
resolveChildNames :: ElementDestructionContext -> ElementDestructionState -> (NameMap.NameMap Xml.Element, ElementDestructionState)
resolveChildNames :: ElementDestructionContext
-> ElementDestructionState
-> (NameMap Element, ElementDestructionState)
resolveChildNames
  (ElementDestructionContext NamespaceRegistry
nreg (Xml.Element Name
_ Map Name Text
_ [Node]
nodes))
  (ElementDestructionState Maybe (NameMap Text)
attributeByNameMap Maybe (NameMap Element)
childByNameMap) =
    let resolvedChildByNameMap :: NameMap Element
resolvedChildByNameMap = NameMap Element -> Maybe (NameMap Element) -> NameMap Element
forall a. a -> Maybe a -> a
fromMaybe (NamespaceRegistry -> [Node] -> NameMap Element
NameMap.fromNodes NamespaceRegistry
nreg [Node]
nodes) Maybe (NameMap Element)
childByNameMap
     in (NameMap Element
resolvedChildByNameMap, Maybe (NameMap Text)
-> Maybe (NameMap Element) -> ElementDestructionState
ElementDestructionState Maybe (NameMap Text)
attributeByNameMap (NameMap Element -> Maybe (NameMap Element)
forall a. a -> Maybe a
Just NameMap Element
resolvedChildByNameMap))