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

{- |
   Module     : Text.XML.HXT.DOM.FormatXmlTree
   Copyright  : Copyright (C) 2008 Uwe Schmidt
   License    : MIT

   Maintainer : Uwe Schmidt (uwe@fh-wedel.de)
   Stability  : stable
   Portability: portable

   Format a xml tree in tree representation

-}

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

module Text.XML.HXT.DOM.FormatXmlTree
    ( formatXmlTree
    , formatXmlContents
    )
where

import Data.Maybe

import Text.XML.HXT.DOM.Interface
import Text.XML.HXT.DOM.ShowXml
import Text.XML.HXT.DOM.XmlNode

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


formatXmlContents       :: XmlTree -> XmlTrees
formatXmlContents :: XmlTree -> XmlTrees
formatXmlContents XmlTree
t
    = [String -> XmlTree
forall a. XmlNode a => String -> a
mkText (XmlTree -> String
formatXmlTree XmlTree
t)]

formatXmlTree           :: XmlTree  -> String
formatXmlTree :: XmlTree -> String
formatXmlTree
    = (XNode -> String) -> XmlTree -> String
forall (t :: * -> *) a. Tree t => (a -> String) -> t a -> String
formatTree XNode -> String
xnode2String

xnode2String    :: XNode -> String
xnode2String :: XNode -> String
xnode2String XNode
n
    | XNode -> Bool
forall a. XmlNode a => a -> Bool
isElem XNode
n
        = String
"XTag " String -> String -> String
forall a. [a] -> [a] -> [a]
++ XNode -> String
showName XNode
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ XNode -> String
showAtts XNode
n
    | XNode -> Bool
forall a. XmlNode a => a -> Bool
isPi XNode
n
        = String
"XPi "  String -> String -> String
forall a. [a] -> [a] -> [a]
++ XNode -> String
showName XNode
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ XNode -> String
showAtts XNode
n
    | Bool
otherwise
        = XNode -> String
forall a. Show a => a -> String
show XNode
n
    where

showName        :: XNode -> String
showName :: XNode -> String
showName        = String -> (QName -> String) -> Maybe QName -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" QName -> String
forall a. Show a => a -> String
show (Maybe QName -> String)
-> (XNode -> Maybe QName) -> XNode -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XNode -> Maybe QName
forall a. XmlNode a => a -> Maybe QName
getName

showAtts        :: XNode -> String
showAtts :: XNode -> String
showAtts        = (XmlTree -> String) -> XmlTrees -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap XmlTree -> String
showAl (XmlTrees -> String) -> (XNode -> XmlTrees) -> XNode -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XmlTrees -> Maybe XmlTrees -> XmlTrees
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe XmlTrees -> XmlTrees)
-> (XNode -> Maybe XmlTrees) -> XNode -> XmlTrees
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XNode -> Maybe XmlTrees
forall a. XmlNode a => a -> Maybe XmlTrees
getAttrl

showAl          :: XmlTree -> String
showAl :: XmlTree -> String
showAl XmlTree
t        -- (NTree (XAttr an) av)
    | XmlTree -> Bool
forall a. XmlNode a => a -> Bool
isAttr XmlTree
t
        = String
"\n|   " String -> String -> String
forall a. [a] -> [a] -> [a]
++ (String -> (QName -> String) -> Maybe QName -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" QName -> String
forall a. Show a => a -> String
show (Maybe QName -> String)
-> (XmlTree -> Maybe QName) -> XmlTree -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XmlTree -> Maybe QName
forall a. XmlNode a => a -> Maybe QName
getName (XmlTree -> String) -> XmlTree -> String
forall a b. (a -> b) -> a -> b
$ XmlTree
t) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"=" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show (XmlTrees -> String
xshow (XmlTrees -> String) -> (XmlTree -> XmlTrees) -> XmlTree -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. XmlTree -> XmlTrees
forall (t :: * -> *) a. Tree t => t a -> [t a]
getChildren (XmlTree -> String) -> XmlTree -> String
forall a b. (a -> b) -> a -> b
$ XmlTree
t)
    | Bool
otherwise
        = XmlTree -> String
forall a. Show a => a -> String
show XmlTree
t

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