module Text.XML.Basic.Format where import qualified Text.XML.Basic.Name as Name import Prelude hiding (quot) class C object where run :: object -> ShowS instance C Char where run = showChar instance C object => C [object] where run = many run {- adapted from HXT import Text.XML.HXT.DOM.ShowXml (showBlank, showQuoteString, showEq, showLt, showGt, showSlash) -} nl, blank, eq, lt, gt, slash, amp, sharp, colon, semicolon, apos, quot, lpar, rpar, exclam, quest :: ShowS nl = showChar '\n' blank = showChar ' ' eq = showChar '=' lt = showChar '<' gt = showChar '>' slash = showChar '/' amp = showChar '&' sharp = showChar '#' colon = showChar ':' semicolon = showChar ';' apos = showChar '\'' quot = showChar '\"' lpar = showChar '(' rpar = showChar ')' exclam = showChar '!' quest = showChar '?' angle :: ShowS -> ShowS angle s = lt . s . gt {- | Internet Explorer does not recognize ' and thus we have to format it literally. -} stringQuoted :: String -> ShowS stringQuoted s = if elem '\'' s then quot . showString s . quot else apos . showString s . apos name :: Name.C name => name -> ShowS name n = showString (Name.toString n) many :: (a -> ShowS) -> [a] -> ShowS many s = foldr (.) id . map s