{-# LANGUAGE RecordWildCards, PatternGuards #-}
module Text.HTML.TagSoup.Specification(parse) where
import Text.HTML.TagSoup.Implementation
import Data.Char (isAlpha, isAlphaNum, isDigit, toLower)
data TypeTag = TypeNormal 
             | TypeXml    
             | TypeDecl   
             | TypeScript 
               deriving Eq
white x = x `elem` " \t\n\f\r"
type Parser = S -> [Out]
parse :: String -> [Out]
parse = dat . state
dat :: Parser
dat S{..} = pos $ case hd of
    '&' -> charReference tl
    '<' -> tagOpen tl
    _ | eof -> []
    _ -> hd & dat tl
charReference s = charRef dat False Nothing s
tagOpen S{..} = case hd of
    '!' -> markupDeclOpen tl
    '/' -> closeTagOpen tl
    _ | isAlpha hd -> Tag & hd & tagName (if isScript s then TypeScript else TypeNormal) tl
    '>' -> errSeen "<>" & '<' & '>' & dat tl
    '?' -> neilXmlTagOpen tl 
    _ -> errSeen  "<" & '<' & dat s
isScript = f "script"
    where
        f (c:cs) S{..} = toLower hd == c && f cs tl
        f [] S{..} = white hd || hd == '/' || hd == '>' || hd == '?' || eof
neilXmlTagOpen S{..} = case hd of
    _ | isAlpha hd -> Tag & '?' & hd & tagName TypeXml tl
    _ -> errSeen "<?" & '<' & '?' & dat s
neilXmlTagClose S{..} = pos $ case hd of
    '>' -> TagEnd & dat tl
    _ -> errSeen "?" & beforeAttName TypeXml s
neilTagEnd typ S{..}
    | typ == TypeXml = pos $ errWant "?>" & TagEnd & dat s
    | typ == TypeScript = pos $ TagEnd & neilScriptBody s
    | otherwise = pos $ TagEnd & dat s
neilScriptBody o@S{..}
    | hd == '<', S{..} <- tl
    , hd == '/', S{..} <- tl
    , isScript s
    = dat o
    | eof = []
    | otherwise =  pos $ hd & neilScriptBody tl
closeTagOpen S{..} = case hd of
    _ | isAlpha hd || hd `elem` "?!" -> TagShut & hd & tagName TypeNormal tl
    '>' -> errSeen "</>" & '<' & '/' & '>' & dat tl
    _ | eof -> '<' & '/' & dat s
    _ -> errWant "tag name" & bogusComment s
tagName typ S{..} = pos $ case hd of
    _ | white hd -> beforeAttName typ tl
    '/' -> selfClosingStartTag typ tl
    '>' -> neilTagEnd typ tl
    '?' | typ == TypeXml -> neilXmlTagClose tl
    _ | isAlpha hd -> hd & tagName typ tl
    _ | eof -> errWant (if typ == TypeXml then "?>" else ">") & dat s
    _ -> hd & tagName typ tl
beforeAttName typ S{..} = pos $ case hd of
    _ | white hd -> beforeAttName typ tl
    '/' -> selfClosingStartTag typ tl
    '>' -> neilTagEnd typ tl
    '?' | typ == TypeXml -> neilXmlTagClose tl
    _ | typ /= TypeNormal && hd `elem` "\'\"" -> beforeAttValue typ s 
    _ | hd `elem` "\"'<=" -> errSeen [hd] & AttName & hd & attName typ tl
    _ | eof -> errWant (if typ == TypeXml then "?>" else ">") & dat s
    _ -> AttName & hd & attName typ tl
attName typ S{..} = pos $ case hd of
    _ | white hd -> afterAttName typ tl
    '/' -> selfClosingStartTag typ tl
    '=' -> beforeAttValue typ tl
    '>' -> neilTagEnd typ tl
    '?' | typ == TypeXml -> neilXmlTagClose tl
    _ | hd `elem` "\"'<" -> errSeen [hd] & def
    _ | eof -> errWant (if typ == TypeXml then "?>" else ">") & dat s
    _ -> def
    where def = hd & attName typ tl
afterAttName typ S{..} = pos $ case hd of
    _ | white hd -> afterAttName typ tl
    '/' -> selfClosingStartTag typ tl
    '=' -> beforeAttValue typ tl
    '>' -> neilTagEnd typ tl
    '?' | typ == TypeXml -> neilXmlTagClose tl
    _ | typ /= TypeNormal && hd `elem` "\"'" -> AttVal & beforeAttValue typ s 
    _ | hd `elem` "\"'<" -> errSeen [hd] & def
    _ | eof -> errWant (if typ == TypeXml then "?>" else ">") & dat s
    _ -> def
    where def = AttName & hd & attName typ tl
beforeAttValue typ S{..} = pos $ case hd of
    _ | white hd -> beforeAttValue typ tl
    '\"' -> AttVal & attValueDQuoted typ tl
    '&' -> AttVal & attValueUnquoted typ s
    '\'' -> AttVal & attValueSQuoted typ tl
    '>' -> errSeen "=" & neilTagEnd typ tl
    '?' | typ == TypeXml -> neilXmlTagClose tl
    _ | hd `elem` "<=" -> errSeen [hd] & def
    _ | eof -> errWant (if typ == TypeXml then "?>" else ">") & dat s
    _ -> def
    where def = AttVal & hd & attValueUnquoted typ tl
attValueDQuoted typ S{..} = pos $ case hd of
    '\"' -> afterAttValueQuoted typ tl
    '&' -> charRefAttValue (attValueDQuoted typ) (Just '\"') tl
    _ | eof -> errWant "\"" & dat s
    _ -> hd & attValueDQuoted typ tl
attValueSQuoted typ S{..} = pos $ case hd of
    '\'' -> afterAttValueQuoted typ tl
    '&' -> charRefAttValue (attValueSQuoted typ) (Just '\'') tl
    _ | eof -> errWant "\'" & dat s
    _ -> hd & attValueSQuoted typ tl
attValueUnquoted typ S{..} = pos $ case hd of
    _ | white hd -> beforeAttName typ tl
    '&' -> charRefAttValue (attValueUnquoted typ) Nothing tl
    '>' -> neilTagEnd typ tl
    '?' | typ == TypeXml -> neilXmlTagClose tl
    _ | hd `elem` "\"'<=" -> errSeen [hd] & def
    _ | eof -> errWant (if typ == TypeXml then "?>" else ">") & dat s
    _ -> def
    where def = hd & attValueUnquoted typ tl
charRefAttValue :: Parser -> Maybe Char -> Parser
charRefAttValue resume c s = charRef resume True c s
afterAttValueQuoted typ S{..} = pos $ case hd of
    _ | white hd -> beforeAttName typ tl
    '/' -> selfClosingStartTag typ tl
    '>' -> neilTagEnd typ tl
    '?' | typ == TypeXml -> neilXmlTagClose tl
    _ | eof -> dat s
    _ -> errSeen [hd] & beforeAttName typ s
selfClosingStartTag typ S{..} = pos $ case hd of
    _ | typ == TypeXml -> errSeen "/" & beforeAttName typ s
    '>' -> TagEndClose & dat tl
    _ | eof -> errWant ">" & dat s
    _ -> errSeen "/" & beforeAttName typ s
bogusComment S{..} = Comment & bogusComment1 s
bogusComment1 S{..} = pos $ case hd of
    '>' -> CommentEnd & dat tl
    _ | eof -> CommentEnd & dat s
    _ -> hd & bogusComment1 tl
markupDeclOpen S{..} = case hd of
    _ | Just s <- next "--" -> Comment & commentStart s
    _ | isAlpha hd -> Tag & '!' & hd & tagName TypeDecl tl 
    _ | Just s <- next "[CDATA[" -> cdataSection s
    _ -> errWant "tag name" & bogusComment s
commentStart S{..} = pos $ case hd of
    '-' -> commentStartDash tl
    '>' -> errSeen "<!-->" & CommentEnd & dat tl
    _ | eof -> errWant "-->" & CommentEnd & dat s
    _ -> hd & comment tl
commentStartDash S{..} = pos $ case hd of
    '-' -> commentEnd tl
    '>' -> errSeen "<!--->" & CommentEnd & dat tl
    _ | eof -> errWant "-->" & CommentEnd & dat s
    _ -> '-' & hd & comment tl
comment S{..} = pos $ case hd of
    '-' -> commentEndDash tl
    _ | eof -> errWant "-->" & CommentEnd & dat s
    _ -> hd & comment tl
commentEndDash S{..} = pos $ case hd of
    '-' -> commentEnd tl
    _ | eof -> errWant "-->" & CommentEnd & dat s
    _ -> '-' & hd & comment tl
commentEnd S{..} = pos $ case hd of
    '>' -> CommentEnd & dat tl
    '-' -> errWant "-->" & '-' & commentEnd tl
    _ | white hd -> errSeen "--" & '-' & '-' & hd & commentEndSpace tl
    '!' -> errSeen "!" & commentEndBang tl
    _ | eof -> errWant "-->" & CommentEnd & dat s
    _ -> errSeen "--" & '-' & '-' & hd & comment tl
commentEndBang S{..} = pos $ case hd of
    '>' -> CommentEnd & dat tl
    '-' -> '-' & '-' & '!' & commentEndDash tl
    _ | eof -> errWant "-->" & CommentEnd & dat s
    _ -> '-' & '-' & '!' & hd & comment tl
commentEndSpace S{..} = pos $ case hd of
    '>' -> CommentEnd & dat tl
    '-' -> commentEndDash tl
    _ | white hd -> hd & commentEndSpace tl
    _ | eof -> errWant "-->" & CommentEnd & dat s
    _ -> hd & comment tl
cdataSection S{..} = pos $ case hd of
    _ | Just s <- next "]]>" -> dat s
    _ | eof -> dat s
    _ | otherwise -> hd & cdataSection tl
charRef :: Parser -> Bool -> Maybe Char -> S -> [Out]
charRef resume att end S{..} = case hd of
    _ | eof || hd `elem` "\t\n\f <&" || maybe False (== hd) end -> '&' & resume s
    '#' -> charRefNum resume s tl
    _ -> charRefAlpha resume att s
charRefNum resume o S{..} = case hd of
    _ | hd `elem` "xX" -> charRefNum2 resume o True tl
    _ -> charRefNum2 resume o False s
charRefNum2 resume o hex S{..} = case hd of
    _ | hexChar hex hd -> (if hex then EntityHex else EntityNum) & hd & charRefNum3 resume hex tl
    _ -> errSeen "&" & '&' & resume o
charRefNum3 resume hex S{..} = case hd of
    _ | hexChar hex hd -> hd & charRefNum3 resume hex tl
    ';' -> EntityEnd True & resume tl
    _ -> EntityEnd False & errWant ";" & resume s
charRefAlpha resume att S{..} = case hd of
    _ | isAlpha hd -> EntityName & hd & charRefAlpha2 resume att tl
    _ -> errSeen "&" & '&' & resume s
charRefAlpha2 resume att S{..} = case hd of
    _ | alphaChar hd -> hd & charRefAlpha2 resume att tl
    ';' -> EntityEnd True & resume tl
    _ | att -> EntityEnd False & resume s
    _ -> EntityEnd False & errWant ";" & resume s
alphaChar x = isAlphaNum x || x `elem` ":-_"
hexChar False x = isDigit x
hexChar True  x = isDigit x || (x >= 'a' && x <= 'f') || (x >= 'A' && x <= 'F')