module Air.Heavy where import Data.Char import Air.Light import Prelude hiding ((.), (^), (>), (<), (/), elem, foldl) import qualified Prelude as P import Text.ParserCombinators.Parsec (many, char, many1, digit, (<|>), Parser, anyChar, try) import qualified Data.ByteString.Lazy.Char8 as B import qualified Text.ParserCombinators.Parsec as P -- compress -- Parser parse :: P.GenParser tok () a -> [tok] -> Either P.ParseError a parse p s = P.parse p "" s -- XML unescape_xml :: String -> Maybe String unescape_xml s = case parse unescape_parser s of Right r -> Just r Left _ -> Nothing where unicode_char :: Parser Char unicode_char = do char '&' char '#' word <- many1 digit char ';' return $ chr (read word) unescape_parser :: Parser String unescape_parser = many (try unicode_char <|> anyChar) escape_xml :: String -> String escape_xml = concatMap fixChar where fixChar '<' = "<" fixChar '>' = ">" fixChar '&' = "&" fixChar '"' = "\"" fixChar c | ord c P.< 0x80 = [c] fixChar c = "&#" ++ show (ord c) ++ ";" -- backward compatible unescape_unicode_xml :: String -> Maybe String unescape_unicode_xml = unescape_xml escape_unicode_xml :: String -> String escape_unicode_xml = escape_xml