{-# LANGUAGE OverloadedStrings #-} module Main(main) where import Text.XML.Hexml as X import qualified Data.ByteString.Char8 as BS import Control.Monad import Data.Monoid import Data.Char examples :: [(Bool, BS.ByteString)] examples = [(True, "herethere") ,(True, "") ,(True, "") ,(True, "here more text at the end") ,(False, "") ,(False, "\nHello, world!") ] main :: IO () main = do forM_ examples $ \(parses, src) -> do case parse src of Left err -> when parses $ fail $ "Unexpected parse failure, " ++ show err Right doc -> do unless parses $ fail "Unexpected parse success" checkFind doc let r = render doc r === rerender doc let Right d = parse r r === render d let Right doc = parse "\n" map name (children doc) === ["test","test","b","test","test"] location (children doc !! 2) === (2,16) length (childrenBy doc "test") === 4 length (childrenBy doc "b") === 1 length (childrenBy doc "extra") === 0 attributes (head $ children doc) === [Attribute "id" "1", Attribute "extra" "2"] map (`attributeBy` "id") (childrenBy doc "test") === map (fmap (Attribute "id")) [Just "1", Just "2", Just "4", Nothing] Right _ <- return $ parse $ " BS.unwords [BS.pack $ "x" ++ show i ++ "='value'" | i <- [1..10000]] <> " />" Right _ <- return $ parse $ BS.unlines $ replicate 10000 "" let attrs = ["usd:jpy","test","extra","more","stuff","jpy:usd","xxx","xxxx"] Right doc <- return $ parse $ " BS.unwords [x <> "='" <> x <> "'" | x <- attrs] <> ">middle" [c] <- return $ childrenBy doc "test" forM_ attrs $ \a -> attributeBy c a === Just (Attribute a a) forM_ ["missing","gone","nothing"] $ \a -> attributeBy c a === Nothing putStrLn "\nSuccess" checkFind :: Node -> IO () checkFind n = do forM_ (attributes n) $ \a -> attributeBy n (attributeName a) === Just a attributeBy n "xxx" === Nothing let cs = children n forM_ ("xxx":map name cs) $ \c -> map outer (filter ((==) c . name) cs) === map outer (childrenBy n c) mapM_ checkFind $ children n a === b = if a == b then putChar '.' else fail $ "mismatch, " ++ show a ++ " /= " ++ show b rerender :: Node -> BS.ByteString rerender = inside where inside x = BS.concat $ map (either validStr node) $ contents x node x = "<" <> BS.unwords (validName (name x) : map attr (attributes x)) <> ">" <> inside x <> " name x <> ">" attr (Attribute a b) = validName a <> "=\"" <> validAttr b <> "\"" validName x | BS.all (\x -> isAlphaNum x || x `elem` ("-:_" :: String)) x = x | otherwise = error "Invalid name" validAttr x | BS.notElem '\"' x = x | otherwise = error "Invalid attribute" validStr x | BS.notElem '<' x || BS.isInfixOf "