module HtmlParsOps where import Html import HtmlLex import ParsOps3 --import HtmlEntities(collapseSpace) tag = fmap htag . oneOf . map htmlTag tag1 = fmap htag . tok . htmlTag endtag = tok . htmlEndTag htag (HtmlTag tag) = tag anythingButCtx n = HtmlContext <$> tag1 n <*> many (anythingBut end) <* endtag n where end = htmlEndTag n anythingBut n = (HtmlChars . sh1) <$> oneOf [ t | t<-htmlAny,t/=n] cmd = fmap HtmlCommand . tag cmd1 = fmap HtmlCommand . tag1 ctx ns p = foldl1 (<|>) (map (flip ctx1 p) ns) ctx1 n p = HtmlContext <$> tag1 n <*> p <* endtag n ctx' ns p = foldl1 (<|>) (map (flip ctx1' p) ns) ctx1' n p = HtmlContext <$> tag1 n <*> p <* optendtag n where optendtag s = optional undefined (endtag s) impliedCtx t p = opttag t <*> p <* optendtag t where opttag s = HtmlContext <$> optional (s,noAttrs) (tag1 s) optendtag s = optional undefined (endtag s) --opttag s = HtmlContext <$> (tag1 s `err` ((s,[]),["Insert "++show s])) --optendtag s = endtag s `err` (undefined,[""]) --chars = htmlchars <$> entities chars = HtmlChars <$> entities --htmlchars = HtmlChars . collapseSpace --prechars = HtmlChars <$> entities entities = hchars <$> oneOf [htmlEntities,htmlSpace] --entities = (str1 . hchars) <$> tok htmlEntities <|> (str2 . hchars) <$> tok htmlSpace where hchars (HtmlSpace s) = s hchars (HtmlEntities s) = s comment = badtag badtag = fmap garb (tok htmlBadTag) where garb (HtmlBadTag t) = garbage t space = many space1 space1 = fmap space (tok htmlSpace) where space (HtmlSpace s) = HtmlChars s whitespace = many whitespace1 whitespace1 = comment <|> space1