{-# LANGUAGE FlexibleInstances #-}
{- |
   Module      : Text.Pandoc.XML.Light.Proc
   Copyright   : Copyright (C) 2007 Galois, Inc., 2021 John MacFarlane
   License     : GNU GPL, version 2 or above

   Maintainer  : John MacFarlane <jgm@berkeley.edu>
   Stability   : alpha
   Portability : portable

   This code is taken from xml-light, released under the BSD3 license.
-}
module Text.Pandoc.XML.Light.Proc
  ( 
    -- * Replacement for xml-light's Text.XML.Proc
    strContent
  , onlyElems
  , elChildren
  , onlyText
  , findChildren
  , filterChildren
  , filterChildrenName
  , findChild
  , filterChild
  , filterChildName
  , findElement
  , filterElement
  , filterElementName
  , findElements
  , filterElements
  , filterElementsName
  , findAttr
  , lookupAttr
  , lookupAttrBy
  , findAttrBy
  ) where

import Data.Text (Text)
import Data.Maybe (listToMaybe)
import Data.List(find)
import Text.Pandoc.XML.Light.Types

--
-- copied from xml-light Text.XML.Proc
--

-- | Get the text value of an XML element.  This function
-- ignores non-text elements, and concatenates all text elements.
strContent         :: Element -> Text
strContent :: Element -> Text
strContent          = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text) -> (Element -> [Text]) -> Element -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CData -> Text) -> [CData] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map CData -> Text
cdData ([CData] -> [Text]) -> (Element -> [CData]) -> Element -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Content] -> [CData]
onlyText ([Content] -> [CData])
-> (Element -> [Content]) -> Element -> [CData]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> [Content]
elContent

-- | Select only the elements from a list of XML content.
onlyElems          :: [Content] -> [Element]
onlyElems :: [Content] -> [Element]
onlyElems [Content]
xs        = [ Element
x | Elem Element
x <- [Content]
xs ]

-- | Select only the elements from a parent.
elChildren         :: Element -> [Element]
elChildren :: Element -> [Element]
elChildren Element
e        = [ Element
x | Elem Element
x <- Element -> [Content]
elContent Element
e ]

-- | Select only the text from a list of XML content.
onlyText           :: [Content] -> [CData]
onlyText :: [Content] -> [CData]
onlyText [Content]
xs         = [ CData
x | Text CData
x <- [Content]
xs ]

-- | Find all immediate children with the given name.
findChildren       :: QName -> Element -> [Element]
findChildren :: QName -> Element -> [Element]
findChildren QName
q Element
e    = (Element -> Bool) -> Element -> [Element]
filterChildren ((QName
q QName -> QName -> Bool
forall a. Eq a => a -> a -> Bool
==) (QName -> Bool) -> (Element -> QName) -> Element -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> QName
elName) Element
e

-- | Filter all immediate children wrt a given predicate.
filterChildren       :: (Element -> Bool) -> Element -> [Element]
filterChildren :: (Element -> Bool) -> Element -> [Element]
filterChildren Element -> Bool
p Element
e    = (Element -> Bool) -> [Element] -> [Element]
forall a. (a -> Bool) -> [a] -> [a]
filter Element -> Bool
p ([Content] -> [Element]
onlyElems (Element -> [Content]
elContent Element
e))


-- | Filter all immediate children wrt a given predicate over their names.
filterChildrenName      :: (QName -> Bool) -> Element -> [Element]
filterChildrenName :: (QName -> Bool) -> Element -> [Element]
filterChildrenName QName -> Bool
p Element
e   = (Element -> Bool) -> [Element] -> [Element]
forall a. (a -> Bool) -> [a] -> [a]
filter (QName -> Bool
p(QName -> Bool) -> (Element -> QName) -> Element -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Element -> QName
elName) ([Content] -> [Element]
onlyElems (Element -> [Content]
elContent Element
e))


-- | Find an immediate child with the given name.
findChild          :: QName -> Element -> Maybe Element
findChild :: QName -> Element -> Maybe Element
findChild QName
q Element
e       = [Element] -> Maybe Element
forall a. [a] -> Maybe a
listToMaybe (QName -> Element -> [Element]
findChildren QName
q Element
e)

-- | Find an immediate child with the given name.
filterChild          :: (Element -> Bool) -> Element -> Maybe Element
filterChild :: (Element -> Bool) -> Element -> Maybe Element
filterChild Element -> Bool
p Element
e       = [Element] -> Maybe Element
forall a. [a] -> Maybe a
listToMaybe ((Element -> Bool) -> Element -> [Element]
filterChildren Element -> Bool
p Element
e)

-- | Find an immediate child with name matching a predicate.
filterChildName      :: (QName -> Bool) -> Element -> Maybe Element
filterChildName :: (QName -> Bool) -> Element -> Maybe Element
filterChildName QName -> Bool
p Element
e   = [Element] -> Maybe Element
forall a. [a] -> Maybe a
listToMaybe ((QName -> Bool) -> Element -> [Element]
filterChildrenName QName -> Bool
p Element
e)

-- | Find the left-most occurrence of an element matching given name.
findElement        :: QName -> Element -> Maybe Element
findElement :: QName -> Element -> Maybe Element
findElement QName
q Element
e     = [Element] -> Maybe Element
forall a. [a] -> Maybe a
listToMaybe (QName -> Element -> [Element]
findElements QName
q Element
e)

-- | Filter the left-most occurrence of an element wrt. given predicate.
filterElement        :: (Element -> Bool) -> Element -> Maybe Element
filterElement :: (Element -> Bool) -> Element -> Maybe Element
filterElement Element -> Bool
p Element
e     = [Element] -> Maybe Element
forall a. [a] -> Maybe a
listToMaybe ((Element -> Bool) -> Element -> [Element]
filterElements Element -> Bool
p Element
e)

-- | Filter the left-most occurrence of an element wrt. given predicate.
filterElementName     :: (QName -> Bool) -> Element -> Maybe Element
filterElementName :: (QName -> Bool) -> Element -> Maybe Element
filterElementName QName -> Bool
p Element
e  = [Element] -> Maybe Element
forall a. [a] -> Maybe a
listToMaybe ((QName -> Bool) -> Element -> [Element]
filterElementsName QName -> Bool
p Element
e)

-- | Find all non-nested occurances of an element.
-- (i.e., once we have found an element, we do not search
-- for more occurances among the element's children).
findElements       :: QName -> Element -> [Element]
findElements :: QName -> Element -> [Element]
findElements QName
qn Element
e = (QName -> Bool) -> Element -> [Element]
filterElementsName (QName
qnQName -> QName -> Bool
forall a. Eq a => a -> a -> Bool
==) Element
e

-- | Find all non-nested occurrences of an element wrt. given predicate.
-- (i.e., once we have found an element, we do not search
-- for more occurances among the element's children).
filterElements       :: (Element -> Bool) -> Element -> [Element]
filterElements :: (Element -> Bool) -> Element -> [Element]
filterElements Element -> Bool
p Element
e
 | Element -> Bool
p Element
e        = [Element
e]
 | Bool
otherwise  = (Element -> [Element]) -> [Element] -> [Element]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((Element -> Bool) -> Element -> [Element]
filterElements Element -> Bool
p) ([Element] -> [Element]) -> [Element] -> [Element]
forall a b. (a -> b) -> a -> b
$ [Content] -> [Element]
onlyElems ([Content] -> [Element]) -> [Content] -> [Element]
forall a b. (a -> b) -> a -> b
$ Element -> [Content]
elContent Element
e

-- | Find all non-nested occurences of an element wrt a predicate over element names.
-- (i.e., once we have found an element, we do not search
-- for more occurances among the element's children).
filterElementsName       :: (QName -> Bool) -> Element -> [Element]
filterElementsName :: (QName -> Bool) -> Element -> [Element]
filterElementsName QName -> Bool
p Element
e = (Element -> Bool) -> Element -> [Element]
filterElements (QName -> Bool
p(QName -> Bool) -> (Element -> QName) -> Element -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Element -> QName
elName) Element
e

-- | Lookup the value of an attribute.
findAttr          :: QName -> Element -> Maybe Text
findAttr :: QName -> Element -> Maybe Text
findAttr QName
x Element
e       = QName -> [Attr] -> Maybe Text
lookupAttr QName
x (Element -> [Attr]
elAttribs Element
e)

-- | Lookup attribute name from list.
lookupAttr        :: QName -> [Attr] -> Maybe Text
lookupAttr :: QName -> [Attr] -> Maybe Text
lookupAttr QName
x       = (QName -> Bool) -> [Attr] -> Maybe Text
lookupAttrBy (QName
x QName -> QName -> Bool
forall a. Eq a => a -> a -> Bool
==)

-- | Lookup the first attribute whose name satisfies the given predicate.
lookupAttrBy       :: (QName -> Bool) -> [Attr] -> Maybe Text
lookupAttrBy :: (QName -> Bool) -> [Attr] -> Maybe Text
lookupAttrBy QName -> Bool
p [Attr]
as   = Attr -> Text
attrVal (Attr -> Text) -> Maybe Attr -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` (Attr -> Bool) -> [Attr] -> Maybe Attr
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (QName -> Bool
p (QName -> Bool) -> (Attr -> QName) -> Attr -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> QName
attrKey) [Attr]
as

-- | Lookup the value of the first attribute whose name
-- satisfies the given predicate.
findAttrBy         :: (QName -> Bool) -> Element -> Maybe Text
findAttrBy :: (QName -> Bool) -> Element -> Maybe Text
findAttrBy QName -> Bool
p Element
e      = (QName -> Bool) -> [Attr] -> Maybe Text
lookupAttrBy QName -> Bool
p (Element -> [Attr]
elAttribs Element
e)