{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}

-- | XML back and forth!
--
-- @xmlbf@ provides high-level tools for encoding and decoding XML.
--
-- @xmlbf@ provides tools like 'dfpos' and 'dfposM' for finding a fixpoint
-- of an XML fragment.
--
-- @xmlbf@ provides 'FromXml' and 'ToXml' typeclasses intended to be used as the
-- familiar 'Data.Aeson.FromJSON' and 'Data.Aeson.ToXml' from the @aeson@
-- package.
--
-- @xmlbf@ doesn't do any parsing of raw XML on its own. Instead, one should
-- use @xmlbf@ together with libraries like
-- [xmlbf-xeno](https://hackage.haskell.org/package/xmlbf-xeno) or
-- [xmlbf-xmlhtml](https://hackage.haskell.org/package/xmlbf-xmlhtml) for
-- this.
module Xmlbf {--}
 ( -- * Parsing
   runParser
 , Parser
   -- * Parsers
 , pElement
 , pAnyElement
 , pName
 , pAttr
 , pAttrs
 , pChildren
 , pText
 , pEndOfInput

    -- * Rendering
 , encode

   -- * Nodes
 , Node
 , node

 , pattern Element
 , element
 , element'

 , pattern Text
 , text
 , text'

   -- * Fixpoints
 , dfpos
 , dfposM
 , dfpre
 , dfpreM

   -- * Typeclasses
 , FromXml(fromXml)
 , ToXml(toXml)
 ) --}
 where

import Control.Applicative (Alternative(empty, (<|>)), liftA2)
import Control.DeepSeq (NFData(rnf))
import Control.Monad (MonadPlus(mplus, mzero), join, when)
import qualified Control.Monad.Fail
import Control.Monad.Fix (MonadFix(mfix))
import Control.Monad.Zip (MonadZip(mzipWith))
import Control.Selective (Selective(select))
import qualified Data.ByteString.Builder as BB
import qualified Data.ByteString.Builder.Prim as BBP
import qualified Data.Char as Char
import Data.Foldable (for_, toList)
import Data.Function (fix)
import Data.Functor.Identity (Identity(Identity), runIdentity)
import qualified Data.HashMap.Strict as HM
import qualified Data.Map.Strict as Map
import Data.Sequence (Seq)
import qualified Data.Sequence as Seq
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import Data.Traversable (for)
import Data.Word (Word8)

--------------------------------------------------------------------------------

-- | Either a text or an element node in an XML fragment body.
--
-- Construct with 'text' or 'element'. Destruct with 'Text' or 'Element'.
data Node
  = Element' !T.Text !(HM.HashMap T.Text T.Text) ![Node]
  | Text' !TL.Text
  deriving (Node -> Node -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Node -> Node -> Bool
$c/= :: Node -> Node -> Bool
== :: Node -> Node -> Bool
$c== :: Node -> Node -> Bool
Eq)

instance NFData Node where
  rnf :: Node -> ()
rnf = \case
    Element' Text
n HashMap Text Text
as [Node]
cs -> forall a. NFData a => a -> ()
rnf Text
n seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf HashMap Text Text
as seq :: forall a b. a -> b -> b
`seq` forall a. NFData a => a -> ()
rnf [Node]
cs seq :: forall a b. a -> b -> b
`seq` ()
    Text' Text
t -> forall a. NFData a => a -> ()
rnf Text
t seq :: forall a b. a -> b -> b
`seq` ()
  {-# INLINABLE rnf #-}

instance Show Node where
  showsPrec :: Int -> Node -> ShowS
showsPrec Int
n = \Node
x -> Bool -> ShowS -> ShowS
showParen (Int
n forall a. Ord a => a -> a -> Bool
> Int
10) forall a b. (a -> b) -> a -> b
$ case Node
x of
    Text' Text
t -> String -> ShowS
showString String
"Text " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => Int -> a -> ShowS
showsPrec Int
0 Text
t
    Element' Text
t HashMap Text Text
as [Node]
cs ->
      String -> ShowS
showString String
"Element " forall b c a. (b -> c) -> (a -> b) -> a -> c
.
      forall a. Show a => Int -> a -> ShowS
showsPrec Int
0 Text
t forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' ' forall b c a. (b -> c) -> (a -> b) -> a -> c
.
      forall a. Show a => Int -> a -> ShowS
showsPrec Int
0 (forall k v. HashMap k v -> [(k, v)]
HM.toList HashMap Text Text
as) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' ' forall b c a. (b -> c) -> (a -> b) -> a -> c
.
      forall a. Show a => Int -> a -> ShowS
showsPrec Int
0 [Node]
cs

-- | Destruct an element 'Node'.
pattern Element :: T.Text -> HM.HashMap T.Text T.Text -> [Node] -> Node
pattern $mElement :: forall {r}.
Node
-> (Text -> HashMap Text Text -> [Node] -> r) -> ((# #) -> r) -> r
Element t as cs <- Element' t as cs
{-# COMPLETE Element #-} -- TODO this leads to silly pattern matching warnings

-- | Destruct a text 'Node'.
pattern Text :: TL.Text -> Node
pattern $mText :: forall {r}. Node -> (Text -> r) -> ((# #) -> r) -> r
Text t <- Text' t
{-# COMPLETE Text #-} -- TODO this leads to silly pattern matching warnings

-- | Case analysis for a 'Node'.
node
  :: (T.Text -> HM.HashMap T.Text T.Text -> [Node] -> a)
  -- ^ Transform an 'Element' node.
  -> (TL.Text -> a)
  -- ^ Transform a 'Text' node.
  -> Node
  -> a
{-# INLINE node #-}
node :: forall a.
(Text -> HashMap Text Text -> [Node] -> a)
-> (Text -> a) -> Node -> a
node Text -> HashMap Text Text -> [Node] -> a
fe Text -> a
ft = \case
  Text' Text
t -> Text -> a
ft Text
t
  Element' Text
t HashMap Text Text
as [Node]
cs -> Text -> HashMap Text Text -> [Node] -> a
fe Text
t HashMap Text Text
as [Node]
cs

-- | Normalizes 'Node's by concatenating consecutive 'Text' nodes.
normalize :: [Node] -> [Node]
{-# INLINE normalize #-}
normalize :: [Node] -> [Node]
normalize = \case
   -- Note that @'Text' ""@ is forbidden by construction, actually. But we do
   -- take care of it in case the 'Node' was constructed unsafely somehow.
   Text' Text
"" : [Node]
ns -> [Node] -> [Node]
normalize [Node]
ns
   Text' Text
a : Text' Text
b : [Node]
ns -> [Node] -> [Node]
normalize (Text -> [Node]
text (Text
a forall a. Semigroup a => a -> a -> a
<> Text
b) forall a. Semigroup a => a -> a -> a
<> [Node]
ns)
   Text' Text
a : [Node]
ns -> Text -> Node
Text' Text
a forall a. a -> [a] -> [a]
: [Node] -> [Node]
normalize [Node]
ns
   Element' Text
t HashMap Text Text
as [Node]
cs : [Node]
ns -> Text -> HashMap Text Text -> [Node] -> Node
Element' Text
t HashMap Text Text
as ([Node] -> [Node]
normalize [Node]
cs) forall a. a -> [a] -> [a]
: [Node] -> [Node]
normalize [Node]
ns
   [] -> []

-- | Construct a XML fragment body containing a single 'Text' 'Node', if
-- possible.
--
-- This function will return empty list if it is not possible to construct the
-- 'Text' with the given input. To learn more about /why/ it was not possible to
-- construct it, use 'text'' instead.
--
-- Using 'text'' rather than 'text' is recommended, so that you are forced to
-- acknowledge a failing situation in case it happens. However, 'text' is at
-- times more convenient to use. For example, when you know statically the input
-- is valid.
text
  :: TL.Text  -- ^ Lazy 'TL.Text'.
  -> [Node]
{-# INLINE text #-}
text :: Text -> [Node]
text Text
t = case Text -> Either String Node
text' Text
t of
  Right Node
x -> [Node
x]
  Left String
_  -> []

-- | Construct a 'Text' 'Node', if possible.
--
-- Returns 'Left' if the 'Text' 'Node' can't be created, with an explanation
-- of why.
text'
  :: TL.Text  -- ^ Lazy 'TL.Text'.
  -> Either String Node
{-# INLINE text' #-}
text' :: Text -> Either String Node
text' = \case
  Text
"" -> forall a b. a -> Either a b
Left String
"Empty text"
  Text
t  -> forall a b. b -> Either a b
Right (Text -> Node
Text' Text
t)

-- | Construct a XML fragment body containing a single 'Element' 'Node', if
-- possible.
--
-- This function will return empty list if it is not possible to construct the
-- 'Element' with the given input. To learn more about /why/ it was not possible
-- to construct it, use 'element' instead.
--
-- Using 'element'' rather than 'element' is recommended, so that you are forced
-- to acknowledge a failing situation in case it happens. However, 'element' is
-- at times more convenient to use, whenever you know the input is valid.
element
  :: T.Text                   -- ^ Element' name as a strict 'T.Text'.
  -> HM.HashMap T.Text T.Text -- ^ Attributes as strict 'T.Text' pairs.
  -> [Node]                   -- ^ Children.
  -> [Node]
{-# INLINE element #-}
element :: Text -> HashMap Text Text -> [Node] -> [Node]
element Text
t HashMap Text Text
hm [Node]
ns = case Text -> HashMap Text Text -> [Node] -> Either String Node
element' Text
t HashMap Text Text
hm [Node]
ns of
  Right Node
x -> [Node
x]
  Left  String
_ -> []

-- | Construct an 'Element' 'Node'.
--
-- Returns 'Left' if the 'Element' 'Node' can't be created, with an explanation
-- of why.
element'
  :: T.Text                   -- ^ Element' name as a strict 'T.Text'.
  -> HM.HashMap T.Text T.Text -- ^ Attributes as strict 'T.Text' pairs.
  -> [Node]                   -- ^ Children.
  -> Either String Node
element' :: Text -> HashMap Text Text -> [Node] -> Either String Node
element' Text
t0 HashMap Text Text
hm0 [Node]
ns0 = do
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Text
t0 forall a. Eq a => a -> a -> Bool
/= Text -> Text
T.strip Text
t0)
     (forall a b. a -> Either a b
Left (String
"Element name has surrounding whitespace: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Text
t0))
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Text -> Bool
T.null Text
t0)
     (forall a b. a -> Either a b
Left (String
"Element name is blank: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Text
t0))
  forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ (forall k v. HashMap k v -> [k]
HM.keys HashMap Text Text
hm0) forall a b. (a -> b) -> a -> b
$ \Text
k -> do
     forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Text
k forall a. Eq a => a -> a -> Bool
/= Text -> Text
T.strip Text
k)
        (forall a b. a -> Either a b
Left (String
"Attribute name has surrounding whitespace: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Text
k))
     forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Text -> Bool
T.null Text
k)
        (forall a b. a -> Either a b
Left (String
"Attribute name is blank: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Text
k))
  forall a b. b -> Either a b
Right (Text -> HashMap Text Text -> [Node] -> Node
Element' Text
t0 HashMap Text Text
hm0 ([Node] -> [Node]
normalize [Node]
ns0))

--------------------------------------------------------------------------------
--------------------------------------------------------------------------------
-- Parsing

class FromXml a where
  -- | Parses an XML fragment body into a value of type @a@.
  --
  -- If a 'ToXml' instance for @a@ exists, then:
  --
  -- @
  -- 'runParser' 'fromXml' ('toXml' a) == pure ('Right' a)
  -- @
  fromXml :: Parser a

-- | Internal parser state.
data S
  = STop ![Node]
    -- ^ Parsing the top-level nodes.
  | SReg !T.Text !(HM.HashMap T.Text T.Text) ![Node]
    -- ^ Parsing a particular root element.

-- | Construct an initial parser state to use with 'unParser' from zero or
-- more top-level 'Node's.
initialS :: [Node] -> S
initialS :: [Node] -> S
initialS = [Node] -> S
STop forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Node] -> [Node]
normalize
{-# INLINE initialS #-}

-- | XML parser for a value of type @a@.
--
-- You can build a 'Parser' using 'pElement', 'pAnyElement', 'pName',
-- 'pAttr', 'pAttrs', 'pChildren', 'pText', 'pEndOfInput', any of the
-- 'Applicative', 'Alternative', 'Monad' or related combinators.
--
-- Run a 'Parser' using 'runParser'.
newtype Parser a = Parser { forall a. Parser a -> S -> Either String (S, a)
unParser :: S -> Either String (S, a) }

-- | Run a 'Parser' on an XML fragment body.
--
-- Notice that this function doesn't enforce that all input is consumed. If you
-- want that behavior, then please use 'pEndOfInput' in the given 'Parser'.
runParser
  :: Parser a
  -- ^ Parser to run.
  -> [Node]
  -- ^ XML fragment body to parse. That is, top-level XML 'Node's.
  -> Either String a
  -- ^ If parsing fails, a 'String' with an error message is returned.
  -- Otherwise, we the parser output @a@ is returned.
runParser :: forall a. Parser a -> [Node] -> Either String a
runParser Parser a
p = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Parser a -> S -> Either String (S, a)
unParser Parser a
p forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Node] -> S
initialS
{-# INLINE runParser #-}

#if MIN_VERSION_base(4,9,0)
instance Semigroup a => Semigroup (Parser a) where
  <> :: Parser a -> Parser a -> Parser a
(<>) = forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall a. Semigroup a => a -> a -> a
(<>)
  {-# INLINE (<>) #-}
#endif

instance Monoid a => Monoid (Parser a) where
  mempty :: Parser a
mempty = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Monoid a => a
mempty
  {-# INLINE mempty #-}
#if MIN_VERSION_base(4,9,0)
  mappend :: Parser a -> Parser a -> Parser a
mappend = forall a. Semigroup a => a -> a -> a
(<>)
#else
  mappend = liftA2 mappend
#endif
  {-# INLINE mappend #-}

instance Functor Parser where
  fmap :: forall a b. (a -> b) -> Parser a -> Parser b
fmap a -> b
f = \Parser a
pa -> forall a. (S -> Either String (S, a)) -> Parser a
Parser (\S
s -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) (forall a. Parser a -> S -> Either String (S, a)
unParser Parser a
pa S
s))
  {-# INLINE fmap #-}

instance Applicative Parser where
  pure :: forall a. a -> Parser a
pure = \a
a -> forall a. (S -> Either String (S, a)) -> Parser a
Parser (\S
s -> forall a b. b -> Either a b
Right (S
s, a
a))
  {-# INLINE pure #-}
  Parser (a -> b)
pf <*> :: forall a b. Parser (a -> b) -> Parser a -> Parser b
<*> Parser a
pa = forall a. (S -> Either String (S, a)) -> Parser a
Parser (\S
s0 -> do
    (S
s1, a -> b
f) <- forall a. Parser a -> S -> Either String (S, a)
unParser Parser (a -> b)
pf S
s0
    (S
s2, a
a) <- forall a. Parser a -> S -> Either String (S, a)
unParser Parser a
pa S
s1
    forall a b. b -> Either a b
Right (S
s2, a -> b
f a
a))
  {-# INLINABLE (<*>) #-}

-- | @ma '<|>' mb@ backtracks the internal parser state before running @mb@.
instance Alternative Parser where
  empty :: forall a. Parser a
empty = forall a. String -> Parser a
pFail String
"empty"
  {-# INLINE empty #-}
  Parser a
pa <|> :: forall a. Parser a -> Parser a -> Parser a
<|> Parser a
pb = forall a. (S -> Either String (S, a)) -> Parser a
Parser (\S
s0 ->
    case forall a. Parser a -> S -> Either String (S, a)
unParser Parser a
pa S
s0 of
      Right (S
s1, a
a) -> forall a b. b -> Either a b
Right (S
s1, a
a)
      Left String
_ -> forall a. Parser a -> S -> Either String (S, a)
unParser Parser a
pb S
s0)
  {-# INLINABLE (<|>) #-}

instance Selective Parser where
  select :: forall a b. Parser (Either a b) -> Parser (a -> b) -> Parser b
select Parser (Either a b)
pe Parser (a -> b)
pf = forall a. (S -> Either String (S, a)) -> Parser a
Parser (\S
s0 -> do
    (S
s1, Either a b
ea) <- forall a. Parser a -> S -> Either String (S, a)
unParser Parser (Either a b)
pe S
s0
    case Either a b
ea of
      Right b
b -> forall a b. b -> Either a b
Right (S
s1, b
b)
      Left a
a -> do
        (S
s2, a -> b
f) <- forall a. Parser a -> S -> Either String (S, a)
unParser Parser (a -> b)
pf S
s1
        forall a b. b -> Either a b
Right (S
s2, a -> b
f a
a))
  {-# INLINABLE select #-}

instance Monad Parser where
  return :: forall a. a -> Parser a
return = forall (f :: * -> *) a. Applicative f => a -> f a
pure
  {-# INLINE return #-}
  Parser a
pa >>= :: forall a b. Parser a -> (a -> Parser b) -> Parser b
>>= a -> Parser b
kpb = forall a. (S -> Either String (S, a)) -> Parser a
Parser (\S
s0 -> do
    (S
s1, a
a) <- forall a. Parser a -> S -> Either String (S, a)
unParser Parser a
pa S
s0
    forall a. Parser a -> S -> Either String (S, a)
unParser (a -> Parser b
kpb a
a) S
s1)
  {-# INLINABLE (>>=) #-}
#if !MIN_VERSION_base(4,13,0)
  fail = pFail
  {-# INLINE fail #-}
#endif

#if MIN_VERSION_base(4,9,0)
instance Control.Monad.Fail.MonadFail Parser where
  fail :: forall a. String -> Parser a
fail = forall a. String -> Parser a
pFail
  {-# INLINE fail #-}
#endif

-- | A 'Parser' that always fails with the given error message.
pFail :: String -> Parser a
pFail :: forall a. String -> Parser a
pFail = \String
msg -> forall a. (S -> Either String (S, a)) -> Parser a
Parser (\S
_ -> forall a b. a -> Either a b
Left String
msg)
{-# INLINE pFail #-}

-- | @'mplus' ma mb@ backtracks the internal parser state before running @mb@.
instance MonadPlus Parser where
  mzero :: forall a. Parser a
mzero = forall (f :: * -> *) a. Alternative f => f a
empty
  {-# INLINE mzero #-}
  mplus :: forall a. Parser a -> Parser a -> Parser a
mplus = forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>)
  {-# INLINE mplus #-}

instance MonadFix Parser where
  mfix :: forall a. (a -> Parser a) -> Parser a
mfix a -> Parser a
f =
    let die :: String -> a
die = \String
msg -> forall a. HasCallStack => String -> a
error (String
"mfix (Parser): " forall a. Semigroup a => a -> a -> a
<> String
msg)
    in forall a. (S -> Either String (S, a)) -> Parser a
Parser (\S
s0 -> forall a. (a -> a) -> a
fix (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Parser a -> S -> Either String (S, a)
unParser S
s0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Parser a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall {a}. String -> a
die forall a b. (a, b) -> b
snd))
  {-# INLINABLE mfix #-}

instance MonadZip Parser where
  mzipWith :: forall a b c. (a -> b -> c) -> Parser a -> Parser b -> Parser c
mzipWith = forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2
  {-# INLINE mzipWith #-}

--------------------------------------------------------------------------------
-- Some parsers

-- | @'pElement' "foo" p@ runs a 'Parser @p@ inside a 'Element' node named
-- @"foo"@. This parser __fails__ if such element does not exist at the current
-- position.
--
-- Leading whitespace is ignored. If you need to preserve that whitespace for
-- some reason, capture it using 'pText' before using 'pElement'.
--
-- __Consumes the matched element__ from the parser state.
pElement
  :: T.Text    -- ^ Element name as strict 'T.Text'.
  -> Parser a  -- ^ 'Parser' to run /inside/ the matched 'Element'.
  -> Parser a
pElement :: forall a. Text -> Parser a -> Parser a
pElement Text
t0 Parser a
p0 = forall a. (S -> Either String (S, a)) -> Parser a
Parser forall a b. (a -> b) -> a -> b
$ \case
  SReg Text
t1 HashMap Text Text
as0 (Element' Text
t HashMap Text Text
as [Node]
cs : [Node]
cs0) | Text
t forall a. Eq a => a -> a -> Bool
== Text
t0 ->
    case forall a. Parser a -> S -> Either String (S, a)
unParser Parser a
p0 (Text -> HashMap Text Text -> [Node] -> S
SReg Text
t HashMap Text Text
as [Node]
cs) of
      Right (S
_, a
a) -> forall a b. b -> Either a b
Right (Text -> HashMap Text Text -> [Node] -> S
SReg Text
t1 HashMap Text Text
as0 [Node]
cs0, a
a)
      Left String
msg -> forall a b. a -> Either a b
Left String
msg
  STop (Element' Text
t HashMap Text Text
as [Node]
cs : [Node]
cs0) | Text
t forall a. Eq a => a -> a -> Bool
== Text
t0 ->
    case forall a. Parser a -> S -> Either String (S, a)
unParser Parser a
p0 (Text -> HashMap Text Text -> [Node] -> S
SReg Text
t HashMap Text Text
as [Node]
cs) of
      Right (S
_, a
a) -> forall a b. b -> Either a b
Right ([Node] -> S
STop [Node]
cs0, a
a)
      Left String
msg -> forall a b. a -> Either a b
Left String
msg
  -- skip leading whitespace
  SReg Text
t HashMap Text Text
as (Text' Text
x : [Node]
cs) | (Char -> Bool) -> Text -> Bool
TL.all Char -> Bool
Char.isSpace Text
x ->
    forall a. Parser a -> S -> Either String (S, a)
unParser (forall a. Text -> Parser a -> Parser a
pElement Text
t0 Parser a
p0) (Text -> HashMap Text Text -> [Node] -> S
SReg Text
t HashMap Text Text
as [Node]
cs)
  STop (Text' Text
x : [Node]
cs) | (Char -> Bool) -> Text -> Bool
TL.all Char -> Bool
Char.isSpace Text
x ->
    forall a. Parser a -> S -> Either String (S, a)
unParser (forall a. Text -> Parser a -> Parser a
pElement Text
t0 Parser a
p0) ([Node] -> S
STop [Node]
cs)
  S
_ -> forall a b. a -> Either a b
Left (String
"Missing element " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show Text
t0)
{-# INLINABLE pElement #-}

-- | @'pAnyElement' p@ runs a 'Parser' @p@ inside the 'Element' node at the
-- current position, if any. Otherwise, if no such element exists, this parser
-- __fails__.
--
-- You can recover the name of the matched element using 'pName' inside the
-- given 'Parser'. However, if you already know beforehand the name of the
-- element that you want to match, it's better to use 'pElement' rather than
-- 'pAnyElement'.
--
-- Leading whitespace is ignored. If you need to preserve that whitespace for
-- some reason, capture it using 'pText' before using 'pAnyElement'.
--
-- __Consumes the matched element__ from the parser state.
pAnyElement
  :: Parser a  -- ^ 'Parser' to run /inside/ any matched 'Element'.
  -> Parser a
pAnyElement :: forall a. Parser a -> Parser a
pAnyElement Parser a
p0 = forall a. (S -> Either String (S, a)) -> Parser a
Parser forall a b. (a -> b) -> a -> b
$ \case
  SReg Text
t0 HashMap Text Text
as0 (Element' Text
t HashMap Text Text
as [Node]
cs : [Node]
cs0) ->
    case forall a. Parser a -> S -> Either String (S, a)
unParser Parser a
p0 (Text -> HashMap Text Text -> [Node] -> S
SReg Text
t HashMap Text Text
as [Node]
cs) of
      Right (S
_, a
a) -> forall a b. b -> Either a b
Right (Text -> HashMap Text Text -> [Node] -> S
SReg Text
t0 HashMap Text Text
as0 [Node]
cs0, a
a)
      Left String
msg -> forall a b. a -> Either a b
Left String
msg
  STop (Element' Text
t HashMap Text Text
as [Node]
cs : [Node]
cs0) ->
    case forall a. Parser a -> S -> Either String (S, a)
unParser Parser a
p0 (Text -> HashMap Text Text -> [Node] -> S
SReg Text
t HashMap Text Text
as [Node]
cs) of
      Right (S
_, a
a) -> forall a b. b -> Either a b
Right ([Node] -> S
STop [Node]
cs0, a
a)
      Left String
msg -> forall a b. a -> Either a b
Left String
msg
  -- skip leading whitespace
  SReg Text
t HashMap Text Text
as (Text' Text
x : [Node]
cs) | (Char -> Bool) -> Text -> Bool
TL.all Char -> Bool
Char.isSpace Text
x ->
    forall a. Parser a -> S -> Either String (S, a)
unParser (forall a. Parser a -> Parser a
pAnyElement Parser a
p0) (Text -> HashMap Text Text -> [Node] -> S
SReg Text
t HashMap Text Text
as [Node]
cs)
  STop (Text' Text
x : [Node]
cs) | (Char -> Bool) -> Text -> Bool
TL.all Char -> Bool
Char.isSpace Text
x ->
    forall a. Parser a -> S -> Either String (S, a)
unParser (forall a. Parser a -> Parser a
pAnyElement Parser a
p0) ([Node] -> S
STop [Node]
cs)
  S
_ -> forall a b. a -> Either a b
Left String
"Missing element"
{-# INLINABLE pAnyElement #-}

-- | Returns the name of the currently selected 'Element'.
--
-- This parser __fails__ if there's no currently selected 'Element' (see
-- 'pElement', 'pAnyElement').
--
-- Doesn't modify the parser state.
pName :: Parser T.Text -- ^ Element name as strict 'T.Text'.
pName :: Parser Text
pName = forall a. (S -> Either String (S, a)) -> Parser a
Parser (\case
  s :: S
s@(SReg Text
t HashMap Text Text
_ [Node]
_) -> forall a b. b -> Either a b
Right (S
s, Text
t)
  S
_ -> forall a b. a -> Either a b
Left String
"Before selecting an name, you must select an element")
{-# INLINABLE pName #-}

-- | Return the value of the requested attribute, if defined. Returns an
-- 'T.empty' 'T.Text' in case the attribute is defined but no value was given to
-- it.
--
-- This parser __fails__ if there's no currently selected 'Element' (see
-- 'pElement', 'pAnyElement').
--
-- __Consumes the matched attribute__ from the parser state.
pAttr
  :: T.Text
  -- ^ Attribute name as strict 'T.Text'.
  -> Parser T.Text
  -- ^ Attribute value as strict 'T.Text', possibly 'T.empty'.
pAttr :: Text -> Parser Text
pAttr Text
n = forall a. (S -> Either String (S, a)) -> Parser a
Parser (\case
  SReg Text
t HashMap Text Text
as [Node]
cs -> case forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HM.lookup Text
n HashMap Text Text
as of
    Just Text
x -> forall a b. b -> Either a b
Right (Text -> HashMap Text Text -> [Node] -> S
SReg Text
t (forall k v. (Eq k, Hashable k) => k -> HashMap k v -> HashMap k v
HM.delete Text
n HashMap Text Text
as) [Node]
cs, Text
x)
    Maybe Text
Nothing -> forall a b. a -> Either a b
Left (String
"Missing attribute " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show Text
n)
  S
_ -> forall a b. a -> Either a b
Left String
"Before selecting an attribute, you must select an element")
{-# INLINABLE pAttr #-}

-- | Returns all of the available element attributes.
--
-- Returns 'T.empty' 'T.Text' as values in case an attribute is defined but no
-- value was given to it.
--
-- This parser __fails__ if there's no currently selected 'Element' (see
-- 'pElement', 'pAnyElement').
--
-- __Consumes all the attributes__ for this element from the parser state.
pAttrs
  :: Parser (HM.HashMap T.Text T.Text)
  -- ^ Pairs of attribute names and possibly 'T.empty' values, as strict
  -- 'T.Text'.
pAttrs :: Parser (HashMap Text Text)
pAttrs = forall a. (S -> Either String (S, a)) -> Parser a
Parser (\case
  SReg Text
t HashMap Text Text
as [Node]
cs -> forall a b. b -> Either a b
Right (Text -> HashMap Text Text -> [Node] -> S
SReg Text
t forall a. Monoid a => a
mempty [Node]
cs, HashMap Text Text
as)
  S
_ -> forall a b. a -> Either a b
Left String
"Before selecting an attribute, you must select an element")
{-# INLINABLE pAttrs #-}

-- | Returns all of the immediate children of the current element.
--
-- If parsing top-level nodes rather than a particular element (that is, if
-- 'pChildren' is /not/ being run inside 'pElement'), then all of the top level
-- 'Node's will be returned.
--
-- __Consumes all the returned nodes__ from the parser state.
pChildren
  :: Parser [Node]
  -- ^ 'Node's in their original order.
pChildren :: Parser [Node]
pChildren = forall a. (S -> Either String (S, a)) -> Parser a
Parser (\case
  STop [Node]
cs -> forall a b. b -> Either a b
Right ([Node] -> S
STop forall a. Monoid a => a
mempty, [Node]
cs)
  SReg Text
t HashMap Text Text
as [Node]
cs -> forall a b. b -> Either a b
Right (Text -> HashMap Text Text -> [Node] -> S
SReg Text
t HashMap Text Text
as forall a. Monoid a => a
mempty, [Node]
cs))
{-# INLINABLE pChildren #-}

-- | Returns the contents of a 'Text' node.
--
-- Surrounidng whitespace is not removed, as it is considered to be part of the
-- text node.
--
-- If there is no text node at the current position, then this parser __fails__.
-- This implies that 'pText' /never/ returns an empty 'TL.Text', since there is
-- no such thing as a text node without text.
--
-- Please note that consecutive text nodes are always concatenated and returned
-- together.
--
-- @
-- 'runParser' 'pText' ('text' \"Ha\" <> 'text' \"sk\" <> 'text' \"ell\")
--     == 'Right' ('text' \"Haskell\")
-- @
--
-- __Consumes the text__ from the parser state. This implies that if you
-- perform two consecutive 'pText' calls, the second will always fail.
--
-- @
-- 'runParser' ('pText' >> 'pText') ('text' \"Ha\" <> 'text' \"sk\" <> 'text' \"ell\")
--     == 'Left' \"Missing text node\"
-- @
pText
  :: Parser TL.Text
  -- ^ Content of the text node as a lazy 'TL.Text'.
pText :: Parser Text
pText = forall a. (S -> Either String (S, a)) -> Parser a
Parser (\case
  -- Note: this works only because we asume 'normalize' has been used.
  STop (Text Text
x : [Node]
ns) -> forall a b. b -> Either a b
Right ([Node] -> S
STop [Node]
ns, Text
x)
  SReg Text
t HashMap Text Text
as (Text Text
x : [Node]
cs) -> forall a b. b -> Either a b
Right (Text -> HashMap Text Text -> [Node] -> S
SReg Text
t HashMap Text Text
as [Node]
cs, Text
x)
  S
_ -> forall a b. a -> Either a b
Left String
"Missing text node")
{-# INLINABLE pText #-}

-- | Succeeds if all of the elements, attributes and text nodes have
-- been consumed.
pEndOfInput :: Parser ()
pEndOfInput :: Parser ()
pEndOfInput = forall a. (S -> Either String (S, a)) -> Parser a
Parser (\S
s -> case S -> Bool
isEof S
s of
  Bool
True -> forall a b. b -> Either a b
Right (S
s, ())
  Bool
False -> forall a b. a -> Either a b
Left String
"Not end of input yet")
{-# INLINABLE pEndOfInput #-}

isEof :: S -> Bool
isEof :: S -> Bool
isEof = \case
  SReg Text
_ HashMap Text Text
as [Node]
cs -> forall k v. HashMap k v -> Bool
HM.null HashMap Text Text
as Bool -> Bool -> Bool
&& forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Node]
cs
  STop [Node]
ns -> forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Node]
ns
{-# INLINE isEof #-}

--------------------------------------------------------------------------------
-- Rendering

class ToXml a where
  -- | Renders a value of type @a@ into an XML fragment body.
  --
  -- If a 'FromXml' instance for @a@ exists, then:
  --
  -- @
  -- 'runParser' 'fromXml' ('toXml' a) == 'Right' a
  -- @
  toXml :: a -> [Node]

-- | Encodes a list of XML 'Node's, representing an XML fragment body, to an
-- UTF8-encoded and XML-escaped bytestring.
--
-- This function doesn't render self-closing elements. Instead, all
-- elements have a corresponding closing tag.
--
-- Also, it doesn't render CDATA sections. Instead, all text is escaped as
-- necessary.
--
-- Element attributes are rendered in alphabetical order.
encode :: [Node] -> BB.Builder
encode :: [Node] -> Builder
encode [Node]
xs = forall a. Monoid a => [a] -> a
mconcat (forall a b. (a -> b) -> [a] -> [b]
map Node -> Builder
encodeNode [Node]
xs)
  where
    encodeNode :: Node -> BB.Builder
    encodeNode :: Node -> Builder
encodeNode = \case
      Text Text
x -> Text -> Builder
encodeXmlUtf8Lazy Text
x
      Element Text
t HashMap Text Text
as [Node]
cs ->
         -- This ugly code is so that we make sure we always bind concatenation
         -- to the right with as little effort as possible, using (<>).
         Builder
"<" forall a. Semigroup a => a -> a -> a
<> Text -> Builder
encodeUtf8 Text
t
             forall a. Semigroup a => a -> a -> a
<> Builder -> Map Text Text -> Builder
encodeAttrs (Builder
">" forall a. Semigroup a => a -> a -> a
<> [Node] -> Builder
encode [Node]
cs forall a. Semigroup a => a -> a -> a
<> Builder
"</" forall a. Semigroup a => a -> a -> a
<> Text -> Builder
encodeUtf8 Text
t forall a. Semigroup a => a -> a -> a
<> Builder
">")
                            (forall k v. Ord k => HashMap k v -> Map k v
mapFromHashMap HashMap Text Text
as)
    {-# INLINE encodeNode #-}
    encodeAttrs :: BB.Builder -> Map.Map T.Text T.Text -> BB.Builder
    encodeAttrs :: Builder -> Map Text Text -> Builder
encodeAttrs = forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
Map.foldrWithKey
      (\Text
k Text
v Builder
o -> Builder
" " forall a. Semigroup a => a -> a -> a
<> Text -> Builder
encodeUtf8 Text
k forall a. Semigroup a => a -> a -> a
<> Builder
"=\"" forall a. Semigroup a => a -> a -> a
<> Text -> Builder
encodeXmlUtf8 Text
v forall a. Semigroup a => a -> a -> a
<> Builder
"\"" forall a. Semigroup a => a -> a -> a
<> Builder
o)
    {-# INLINE encodeAttrs #-}


--------------------------------------------------------------------------------
--------------------------------------------------------------------------------
-- Node fixpoint

-- | Post-order depth-first replacement of 'Node' and all of its children.
--
-- This function works like 'Data.Function.fix', but the given function is
-- trying to find a fixpoint for the individual children nodes, not for the root
-- node.
--
-- For example, the following function renames every node named @"w"@ to @"y"@,
-- and every node named @"y"@ to @"z"@. It accomplishes this by first renaming
-- @"w"@ nodes to @"x"@, and then, by using @k@ recursively to further rename
-- all @"x"@ nodes (including the ones that were just created) to @"y"@ in a
-- post-order depth-first manner. After renaming an @"x"@ node to @"y"@, the
-- recursion stops (i.e., @k@ is not used), so our new @"y"@ nodes won't be
-- further renamed to @"z"@. However, nodes that were named @"y"@ initially will
-- be renamed to @"z"@.
--
-- In our example we only replace one node with another, but a node can be
-- replaced with zero or more nodes, depending on the length of the resulting
-- list.
--
-- @
-- foo :: 'Node' -> ['Node']
-- foo = 'dfpos' $ \\k -> \\case
--     'Element' "w" as cs -> 'element' "x" as cs >>= k
--     'Element' "x" as cs -> 'element' "y" as cs
--     'Element' "y" as cs -> 'element' "z" as cs >>= k
-- @
--
-- See 'dfpre' for pre-orderd depth-first replacement.
--
-- /WARNING/ If you call @k@ in every branch, then 'dfpos' will never terminate.
-- Make sure the recursion stops at some point by simply returning a list of
-- nodes instead of calling @k@.
dfpos :: ((Node -> [Node]) -> Node -> [Node]) -> Node -> [Node]
dfpos :: ((Node -> [Node]) -> Node -> [Node]) -> Node -> [Node]
dfpos (Node -> [Node]) -> Node -> [Node]
f = forall a. Identity a -> a
runIdentity forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *).
Monad m =>
((Node -> m [Node]) -> Node -> m [Node]) -> Node -> m [Node]
dfposM (\Node -> Identity [Node]
k -> forall a. a -> Identity a
Identity forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> [Node]) -> Node -> [Node]
f (forall a. Identity a -> a
runIdentity forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node -> Identity [Node]
k))

-- | Monadic version of 'dfpos'.
dfposM :: Monad m => ((Node -> m [Node]) -> Node -> m [Node]) -> Node -> m [Node]
dfposM :: forall (m :: * -> *).
Monad m =>
((Node -> m [Node]) -> Node -> m [Node]) -> Node -> m [Node]
dfposM (Node -> m [Node]) -> Node -> m [Node]
f = \Node
n0 -> do
  Cursor
c1 <- forall (m :: * -> *).
Monad m =>
(Node -> m [Node]) -> Cursor -> m Cursor
traverseChildren (forall (m :: * -> *).
Monad m =>
((Node -> m [Node]) -> Node -> m [Node]) -> Node -> m [Node]
dfposM (Node -> m [Node]) -> Node -> m [Node]
f) (Node -> Cursor
cursorFromNode Node
n0)
  Cursor
c2 <- forall (m :: * -> *).
Monad m =>
(Node -> m [Node]) -> Cursor -> m Cursor
traverseRightSiblings (forall (m :: * -> *).
Monad m =>
((Node -> m [Node]) -> Node -> m [Node]) -> Node -> m [Node]
dfposM (Node -> m [Node]) -> Node -> m [Node]
f) Cursor
c1
  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Node] -> [Node]
normalize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => m (m a) -> m a
join)
       (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((Node -> m [Node]) -> Node -> m [Node]
f (forall (m :: * -> *).
Monad m =>
((Node -> m [Node]) -> Node -> m [Node]) -> Node -> m [Node]
dfposM (Node -> m [Node]) -> Node -> m [Node]
f)) (Cursor -> [Node]
cursorSiblings Cursor
c2))


-- | Pre-order depth-first replacement of 'Node' and all of its children.
--
-- This is just like 'dfpos' but the search proceeds in a different order.
dfpre :: ((Node -> [Node]) -> Node -> [Node]) -> Node -> [Node]
dfpre :: ((Node -> [Node]) -> Node -> [Node]) -> Node -> [Node]
dfpre (Node -> [Node]) -> Node -> [Node]
f = forall a. Identity a -> a
runIdentity forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *).
Monad m =>
((Node -> m [Node]) -> Node -> m [Node]) -> Node -> m [Node]
dfpreM (\Node -> Identity [Node]
k -> forall a. a -> Identity a
Identity forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> [Node]) -> Node -> [Node]
f (forall a. Identity a -> a
runIdentity forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node -> Identity [Node]
k))

-- | Monadic version of 'dfpre'.
dfpreM :: Monad m => ((Node -> m [Node]) -> Node -> m [Node]) -> Node -> m [Node]
dfpreM :: forall (m :: * -> *).
Monad m =>
((Node -> m [Node]) -> Node -> m [Node]) -> Node -> m [Node]
dfpreM (Node -> m [Node]) -> Node -> m [Node]
f = \Node
n0 -> do
  [Node]
ns <- (Node -> m [Node]) -> Node -> m [Node]
f (forall (m :: * -> *).
Monad m =>
((Node -> m [Node]) -> Node -> m [Node]) -> Node -> m [Node]
dfpreM (Node -> m [Node]) -> Node -> m [Node]
f) Node
n0
  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Node] -> [Node]
normalize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => m (m a) -> m a
join) forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for [Node]
ns forall a b. (a -> b) -> a -> b
$ \Node
n -> do
     Cursor
c1 <- forall (m :: * -> *).
Monad m =>
(Node -> m [Node]) -> Cursor -> m Cursor
traverseChildren (forall (m :: * -> *).
Monad m =>
((Node -> m [Node]) -> Node -> m [Node]) -> Node -> m [Node]
dfpreM (Node -> m [Node]) -> Node -> m [Node]
f) (Node -> Cursor
cursorFromNode Node
n)
     Cursor -> [Node]
cursorSiblings forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *).
Monad m =>
(Node -> m [Node]) -> Cursor -> m Cursor
traverseRightSiblings (forall (m :: * -> *).
Monad m =>
((Node -> m [Node]) -> Node -> m [Node]) -> Node -> m [Node]
dfpreM (Node -> m [Node]) -> Node -> m [Node]
f) Cursor
c1


--------------------------------------------------------------------------------
--------------------------------------------------------------------------------
-- INTERNAL: Cursor
--
-- Most of this comes from Chris Smith's xmlhtml, BSD3 licensed
-- https://hackage.haskell.org/package/xmlhtml

-- | Zipper into a 'Node' tree.
data Cursor = Cursor
  { Cursor -> Node
_cursorCurrent :: !Node
    -- ^ Retrieves the current node of a 'Cursor'.
  , Cursor -> Seq Node
_cursorLefts :: !(Seq Node)
    -- ^ Nodes to the left (ordered right to left).
  , Cursor -> Seq Node
_cursorRights :: !(Seq Node)
    -- ^ Nodes to the right (ordered left to right).
  , Cursor -> Seq (Seq Node, Text, HashMap Text Text, Seq Node)
_cursorParents :: !(Seq (Seq Node, T.Text, HM.HashMap T.Text T.Text, Seq Node))
    -- ^ Parents' name, attributes, and siblings.
  }

------------------------------------------------------------------------------

-- | The cursor if left where it starts.
traverseChildren :: Monad m => (Node -> m [Node]) -> Cursor -> m Cursor
{-# INLINABLE traverseChildren #-}
traverseChildren :: forall (m :: * -> *).
Monad m =>
(Node -> m [Node]) -> Cursor -> m Cursor
traverseChildren Node -> m [Node]
f Cursor
c0 = case Cursor -> Node
_cursorCurrent Cursor
c0 of
  Text Text
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Cursor
c0
  Element Text
t HashMap Text Text
as [Node]
cs -> do
     [Node]
n1s <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Node] -> [Node]
normalize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => m (m a) -> m a
join) (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Node -> m [Node]
f [Node]
cs)
     forall (f :: * -> *) a. Applicative f => a -> f a
pure (Cursor
c0 {_cursorCurrent :: Node
_cursorCurrent = Text -> HashMap Text Text -> [Node] -> Node
Element' Text
t HashMap Text Text
as [Node]
n1s})

-- | The cursor if left in the rightmost sibling.
traverseRightSiblings :: Monad m => (Node -> m [Node]) -> Cursor -> m Cursor
{-# INLINABLE traverseRightSiblings #-}
traverseRightSiblings :: forall (m :: * -> *).
Monad m =>
(Node -> m [Node]) -> Cursor -> m Cursor
traverseRightSiblings Node -> m [Node]
f Cursor
c0 = case Cursor -> Maybe (Node, Cursor)
cursorRemoveRight Cursor
c0 of
   Maybe (Node, Cursor)
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Cursor
c0
   Just (Node
n1, Cursor
c1) -> do
      [Node]
n2s <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Node] -> [Node]
normalize (Node -> m [Node]
f Node
n1)
      forall (m :: * -> *).
Monad m =>
(Node -> m [Node]) -> Cursor -> m Cursor
traverseRightSiblings Node -> m [Node]
f ([Node] -> Cursor -> Cursor
cursorInsertManyRight [Node]
n2s Cursor
c1)

-- | Builds a 'Cursor' for navigating a tree. That is, a forest with a single
-- root 'Node'.
cursorFromNode :: Node -> Cursor
{-# INLINE cursorFromNode #-}
cursorFromNode :: Node -> Cursor
cursorFromNode Node
n = Node
-> Seq Node
-> Seq Node
-> Seq (Seq Node, Text, HashMap Text Text, Seq Node)
-> Cursor
Cursor Node
n forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty

-- | Retrieves a list of the 'Node's at the same level as the current position
-- of a cursor, including the current node.
cursorSiblings :: Cursor -> [Node]
{-# INLINE cursorSiblings #-}
cursorSiblings :: Cursor -> [Node]
cursorSiblings (Cursor Node
cur Seq Node
ls Seq Node
rs Seq (Seq Node, Text, HashMap Text Text, Seq Node)
_) =
  forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (forall a. Seq a -> Seq a
Seq.reverse Seq Node
ls forall a. Semigroup a => a -> a -> a
<> (Node
cur forall a. a -> Seq a -> Seq a
Seq.<| Seq Node
rs))

-- | Removes the node to the right and return it.
cursorRemoveRight :: Cursor -> Maybe (Node, Cursor)
{-# INLINABLE cursorRemoveRight #-}
cursorRemoveRight :: Cursor -> Maybe (Node, Cursor)
cursorRemoveRight = \case
  Cursor Node
n Seq Node
ls Seq Node
rs0 Seq (Seq Node, Text, HashMap Text Text, Seq Node)
ps | Bool -> Bool
not (forall a. Seq a -> Bool
Seq.null Seq Node
rs0) ->
     case forall a. Seq a -> ViewL a
Seq.viewl Seq Node
rs0 of
        Node
r Seq.:< Seq Node
rs -> forall a. a -> Maybe a
Just (Node
r, Node
-> Seq Node
-> Seq Node
-> Seq (Seq Node, Text, HashMap Text Text, Seq Node)
-> Cursor
Cursor Node
n Seq Node
ls Seq Node
rs Seq (Seq Node, Text, HashMap Text Text, Seq Node)
ps)
        ViewL Node
_ -> forall a. HasCallStack => a
undefined -- unreachable, rs0 is not empty
  Cursor
_ -> forall a. Maybe a
Nothing

-- | Inserts a list of new 'Node's to the right of the current position.
cursorInsertManyRight :: [Node] -> Cursor -> Cursor
{-# INLINE cursorInsertManyRight #-}
cursorInsertManyRight :: [Node] -> Cursor -> Cursor
cursorInsertManyRight [Node]
ns (Cursor Node
nn Seq Node
ls Seq Node
rs Seq (Seq Node, Text, HashMap Text Text, Seq Node)
ps) =
  Node
-> Seq Node
-> Seq Node
-> Seq (Seq Node, Text, HashMap Text Text, Seq Node)
-> Cursor
Cursor Node
nn Seq Node
ls (forall a. [a] -> Seq a
Seq.fromList [Node]
ns forall a. Semigroup a => a -> a -> a
<> Seq Node
rs) Seq (Seq Node, Text, HashMap Text Text, Seq Node)
ps

--------------------------------------------------------------------------------
--------------------------------------------------------------------------------
-- Miscellaneous

encodeUtf8 :: T.Text -> BB.Builder
{-# INLINE encodeUtf8 #-}
encodeUtf8 :: Text -> Builder
encodeUtf8 = Text -> Builder
T.encodeUtf8Builder

encodeXmlUtf8 :: T.Text -> BB.Builder
{-# INLINE encodeXmlUtf8 #-}
encodeXmlUtf8 :: Text -> Builder
encodeXmlUtf8 = BoundedPrim Word8 -> Text -> Builder
T.encodeUtf8BuilderEscaped BoundedPrim Word8
xmlEscaped

encodeXmlUtf8Lazy :: TL.Text -> BB.Builder
{-# INLINE encodeXmlUtf8Lazy #-}
encodeXmlUtf8Lazy :: Text -> Builder
encodeXmlUtf8Lazy = BoundedPrim Word8 -> Text -> Builder
TL.encodeUtf8BuilderEscaped BoundedPrim Word8
xmlEscaped

xmlEscaped :: BBP.BoundedPrim Word8
{-# INLINE xmlEscaped #-}
xmlEscaped :: BoundedPrim Word8
xmlEscaped =
   forall a.
(a -> Bool) -> BoundedPrim a -> BoundedPrim a -> BoundedPrim a
BBP.condB (forall a. Eq a => a -> a -> Bool
== Word8
38) ((Word8, (Word8, (Word8, (Word8, Word8)))) -> BoundedPrim Word8
fixed5 (Word8
38,(Word8
97,(Word8
109,(Word8
112,Word8
59))))) forall a b. (a -> b) -> a -> b
$  -- '&'  ->  "&amp;"
   forall a.
(a -> Bool) -> BoundedPrim a -> BoundedPrim a -> BoundedPrim a
BBP.condB (forall a. Eq a => a -> a -> Bool
== Word8
60) ((Word8, (Word8, (Word8, Word8))) -> BoundedPrim Word8
fixed4 (Word8
38,(Word8
108,(Word8
116,Word8
59)))) forall a b. (a -> b) -> a -> b
$       -- '<'  ->  "&lt;"
   forall a.
(a -> Bool) -> BoundedPrim a -> BoundedPrim a -> BoundedPrim a
BBP.condB (forall a. Eq a => a -> a -> Bool
== Word8
62) ((Word8, (Word8, (Word8, Word8))) -> BoundedPrim Word8
fixed4 (Word8
38,(Word8
103,(Word8
116,Word8
59)))) forall a b. (a -> b) -> a -> b
$       -- '>'  ->  "&gt;"
   forall a.
(a -> Bool) -> BoundedPrim a -> BoundedPrim a -> BoundedPrim a
BBP.condB (forall a. Eq a => a -> a -> Bool
== Word8
34) ((Word8, (Word8, (Word8, (Word8, Word8)))) -> BoundedPrim Word8
fixed5 (Word8
38,(Word8
35,(Word8
51,(Word8
52,Word8
59))))) forall a b. (a -> b) -> a -> b
$    -- '"'  ->  "&#34;"
   forall a. FixedPrim a -> BoundedPrim a
BBP.liftFixedToBounded FixedPrim Word8
BBP.word8
 where
   {-# INLINE fixed4 #-}
   fixed4 :: (Word8, (Word8, (Word8, Word8))) -> BBP.BoundedPrim Word8
   fixed4 :: (Word8, (Word8, (Word8, Word8))) -> BoundedPrim Word8
fixed4 (Word8, (Word8, (Word8, Word8)))
x = forall a. FixedPrim a -> BoundedPrim a
BBP.liftFixedToBounded
     (forall a b. a -> b -> a
const (Word8, (Word8, (Word8, Word8)))
x forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
BBP.>$< FixedPrim Word8
BBP.word8 forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
BBP.>*< FixedPrim Word8
BBP.word8
              forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
BBP.>*< FixedPrim Word8
BBP.word8 forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
BBP.>*< FixedPrim Word8
BBP.word8)
   {-# INLINE fixed5 #-}
   fixed5 :: (Word8, (Word8, (Word8, (Word8, Word8)))) -> BBP.BoundedPrim Word8
   fixed5 :: (Word8, (Word8, (Word8, (Word8, Word8)))) -> BoundedPrim Word8
fixed5 (Word8, (Word8, (Word8, (Word8, Word8))))
x = forall a. FixedPrim a -> BoundedPrim a
BBP.liftFixedToBounded
     (forall a b. a -> b -> a
const (Word8, (Word8, (Word8, (Word8, Word8))))
x forall (f :: * -> *) b a. Contravariant f => (b -> a) -> f a -> f b
BBP.>$< FixedPrim Word8
BBP.word8 forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
BBP.>*< FixedPrim Word8
BBP.word8
              forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
BBP.>*< FixedPrim Word8
BBP.word8 forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
BBP.>*< FixedPrim Word8
BBP.word8 forall (f :: * -> *) a b. Monoidal f => f a -> f b -> f (a, b)
BBP.>*< FixedPrim Word8
BBP.word8)

mapFromHashMap :: Ord k => HM.HashMap k v -> Map.Map k v
mapFromHashMap :: forall k v. Ord k => HashMap k v -> Map k v
mapFromHashMap = forall k v a. (k -> v -> a -> a) -> a -> HashMap k v -> a
HM.foldrWithKey' forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert forall k a. Map k a
Map.empty
{-# INLINE mapFromHashMap #-}

--}