{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards   #-}
module Text.XML.Output
  ( serializeXML
  , serializeXMLDoc
  , serializeXMLRoot
  , SerializeXMLOptions(..), defaultSerializeXMLOptions
  ) where
import           Common
import qualified Data.Text              as T
import qualified Data.Text.Lazy         as TL
import qualified Data.Text.Lazy.Builder as TLB
import qualified Data.Text.Short        as TS
import           Text.XML.Types
import           Utils
serializeXMLDoc :: Element -> TL.Text
serializeXMLDoc el
  = serializeXMLRoot defaultSerializeXMLOptions
    (Root (Just (XmlDeclaration Nothing Nothing)) [] Nothing el [])
serializeXML :: [Content] -> TL.Text
serializeXML = TL.pack . foldr (ppContentS defaultSerializeXMLOptions) ""
defaultSerializeXMLOptions :: SerializeXMLOptions
defaultSerializeXMLOptions = SerializeXMLOptions
  { serializeAllowEmptyTag     = const True
  , serializeProEpilogAddNLs   = False
  }
data SerializeXMLOptions = SerializeXMLOptions
  { serializeAllowEmptyTag   :: QName -> Bool
  , serializeProEpilogAddNLs :: Bool
  }
serializeXMLRoot :: SerializeXMLOptions -> Root -> TL.Text
serializeXMLRoot sopts Root{..} = TLB.toLazyText $
    (if serializeProEpilogAddNLs sopts then bUnlines else mconcat) $
    maybeToList xmldecl ++
    map bMisc rootPreElem ++
    (case rootDoctype of
       Nothing -> []
       Just (dtd,moreMisc) -> ("<!DOCTYPE" <+> TLB.fromText dtd <+> ">") : map bMisc moreMisc
    ) ++
    [TLB.fromString (ppElementS sopts rootElement "")] ++
    map bMisc rootPostElem
  where
    xmldecl = case rootXmlDeclaration of
                Nothing -> Nothing
                Just (XmlDeclaration Nothing Nothing) -> Just "<?xml version=\"1.0\"?>"
                Just (XmlDeclaration menc mstand) -> Just $
                  ("<?xml version=\"1.0\"" <+>) $
                  (maybe id (\enc cont -> " encoding=\"" <+> bFromShortText enc <+> "\"" <+> cont) menc) $
                  (maybe id (\b cont -> " standalone=\"" <+> (if b then "yes" else "no") <+> "\"" <+> cont) mstand) $
                  "?>"
    bMisc (Left (Comment t)) = "<!--" <+> TLB.fromText (T.replace "--" "-~" t) <+> "-->"
    bMisc (Right (PI tgt dat)) = "<?" <+> bFromShortText tgt <+> (if T.null dat then mempty else " ") <+> TLB.fromText dat <+> "?>"
ppContentS :: SerializeXMLOptions -> Content -> ShowS
ppContentS c x xs = case x of
    Elem e -> ppElementS c e xs
    Text t -> showCDataS t xs
    CRef r -> showCRefS r xs
    Proc p -> ppProcS p xs
    Comm t -> ppCommS t xs
ppElementS :: SerializeXMLOptions -> Element -> ShowS
ppElementS c e xs = tagStart (elName e) (elAttribs e) $ case elContent e of
    [] | allowEmpty -> "/>" ++ xs
    [Text t]        -> ">" ++ showCDataS t (tagEnd name xs)
    cs              -> '>' : foldr (ppContentS c) (tagEnd name xs) cs
  where
    name = elName e
    allowEmpty = serializeAllowEmptyTag c name
ppCommS :: Comment -> ShowS
ppCommS (Comment t) xs = "<!--" ++ T.unpack (T.replace "--" "-~" t) ++ "-->" ++ xs
ppProcS :: PI -> ShowS
ppProcS (PI tgt dat) xs = "<?" ++ TS.unpack tgt ++ (if T.null dat then mempty else " ") ++ T.unpack dat ++ "?>" ++ xs
showCRefS          :: ShortText -> ShowS
showCRefS r xs      = '&' : TS.unpack r ++ ';' : xs
showCDataS         :: CData -> ShowS
showCDataS cd =
 case cdVerbatim cd of
   CDataText     -> escStr (T.unpack $ cdData cd)
   CDataVerbatim -> showString "<![CDATA[" . escCData (T.unpack $ cdData cd)
                                           . showString "]]>"
   CDataRaw      -> \ xs -> T.unpack (cdData cd) ++ xs
escCData :: String -> ShowS
escCData (']' : ']' : '>' : cs) = showString "]]]]><![CDATA[>" . escCData cs
escCData (c : cs)               = showChar c . escCData cs
escCData []                     = id
escChar :: Char -> ShowS
escChar c = case c of
  '<'    -> showString "<"   
  '>'    -> showString ">"   
  '&'    -> showString "&"  
  '\x0D' -> showString "
"  
  _      -> showChar c
escCharAttr :: Char -> ShowS
escCharAttr c = case c of
  '<'    -> showString "<"   
  '&'    -> showString "&"  
  '"'    -> showString """ 
  '\x09' -> showString "	"  
  '\x0A' -> showString "
"  
  '\x0D' -> showString "
"  
  _      -> showChar c
escStr             :: String -> ShowS
escStr cs rs        = foldr escChar rs cs
escStrAttr         :: String -> ShowS
escStrAttr cs rs    = foldr escCharAttr rs cs
tagEnd             :: QName -> ShowS
tagEnd qn rs        = '<':'/':showQName qn ++ '>':rs
tagStart           :: QName -> [Attr] -> ShowS
tagStart qn as rs   = '<':showQName qn ++ as_str ++ rs
 where as_str       = if null as then "" else ' ' : unwords (map showAttr as)
showAttr           :: Attr -> String
showAttr (Attr qn v) = showQName qn ++ '=' : '"' : escStrAttr (T.unpack v) "\""
showQName          :: QName -> String
showQName q         = pre ++ showLName (qLName q)
  where pre = case qPrefix q of
                Nothing -> ""
                Just p  -> TS.unpack p ++ ":"
showLName :: LName -> String
showLName = TS.unpack . unLName