{-# LANGUAGE OverloadedStrings #-} {-| Description: Token processing rules for a @\@ data point in a table. Copyright: (c) 2020 Sam May License: MPL-2.0 Maintainer: ag.eitilt@gmail.com Stability: stable Portability: portable -} module Web.Mangrove.Parse.Tree.InCell ( treeInCell ) where import Web.Mangrove.Parse.Common.Error import Web.Mangrove.Parse.Tokenize.Common import Web.Mangrove.Parse.Tree.Common import Web.Mangrove.Parse.Tree.InBody import Web.Mangrove.Parse.Tree.Patch import Web.Willow.Common.Parser import Web.Willow.Common.Parser.Switch -- | __HTML:__ -- @[the "in cell" insertion mode] -- (https://html.spec.whatwg.org/multipage/parsing.html#parsing-main-intd)@ -- -- The parsing instructions corresponding to the 'InCell' section of the state -- machine. treeInCell :: TreeBuilder TreeOutput treeInCell = next >>= switch [ If (isEndTag ["td", "th"]) $ \t' -> do let d = tokenTag t' hasMatch <- hasInTableScope [tagName d] if hasMatch then do generate <- generateEndTags impliedEndTags current <- currentNode let unexpected = if maybe True (nodeIsElement $ tagName d) current then id else consTreeError_ UnexpectedElementWithImpliedEndTag close <- closeElement $ tagName d clearFormattingElements switchMode InRow packTree t' $ generate ++ unexpected close else packTreeErrors [UnmatchedEndTag $ tokenElement t'] t' , If (isStartTag [ "caption" , "col" , "colgroup" , "tbody" , "td" , "tfoot" , "th" , "thead" , "tr"]) $ \t' -> do hasMatch <- hasInTableScope ["td", "th"] if hasMatch then do push t' close <- closeCell packTree_ close else packTreeErrors [MalformedTableStructure $ tokenElement t'] t' , If (isEndTag [ "body" , "caption" , "col" , "colgroup" , "html" ]) $ \t' -> packTreeErrors [UnexpectedEndTag $ tokenElement t'] t' , If (isEndTag [ "table" , "tbody" , "tfoot" , "thead" , "tr" ]) $ \t' -> do hasMatch <- hasInTableScope [tagName $ tokenTag t'] if hasMatch then do push t' close <- closeCell packTree_ close else packTreeErrors [UnmatchedEndTag $ tokenElement t'] t' , Else $ \t' -> push t' *> treeInBody ] where closeCell = do generate <- generateEndTags impliedEndTags current <- currentNode let errF = if elem (fmap elementName current) [Just "td", Just "th"] then consTreeError_ UnexpectedElementWithImpliedEndTag else id close <- closeElements ["td", "th"] clearFormattingElements switchMode InRow return $ generate ++ errF close