diff options
author | John MacFarlane <jgm@berkeley.edu> | 2011-07-15 21:14:57 -0700 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2011-07-15 21:16:49 -0700 |
commit | 934867f85829a75f38291cd694da32184252a305 (patch) | |
tree | 0945493dd5a6575b62f657d0dae4fab885bda689 | |
parent | b30afc2009bf22d49ceaadf1b7b94c298386c89a (diff) | |
download | pandoc-934867f85829a75f38291cd694da32184252a305.tar.gz |
HTML reader: Handle tbody, thead in simple tables.
Closes #274.
-rw-r--r-- | src/Text/Pandoc/Readers/HTML.hs | 24 |
1 files changed, 17 insertions, 7 deletions
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index ba25d8ad8..82ea560a8 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -47,7 +47,7 @@ import Text.Pandoc.Parsing import Data.Maybe ( fromMaybe, isJust ) import Data.List ( intercalate ) import Data.Char ( isSpace, isDigit ) -import Control.Monad ( liftM, guard ) +import Control.Monad ( liftM, guard, when ) -- | Convert HTML-formatted string to 'Pandoc' document. readHtml :: ParserState -- ^ Parser state @@ -211,9 +211,9 @@ pSimpleTable :: TagParser [Block] pSimpleTable = try $ do TagOpen _ _ <- pSatisfy (~== TagOpen "table" []) skipMany pBlank - head' <- option [] $ pInTags "th" pTd - rows <- many1 $ try $ - skipMany pBlank >> pInTags "tr" pTd + head' <- option [] $ pOptInTag "thead" $ pInTags "tr" (pCell "th") + rows <- pOptInTag "tbody" + $ many1 $ try $ skipMany pBlank >> pInTags "tr" (pCell "td") skipMany pBlank TagClose _ <- pSatisfy (~== TagClose "table") let cols = maximum $ map length rows @@ -221,10 +221,10 @@ pSimpleTable = try $ do let widths = replicate cols 0 return [Table [] aligns widths head' rows] -pTd :: TagParser [TableCell] -pTd = try $ do +pCell :: String -> TagParser [TableCell] +pCell celltype = try $ do skipMany pBlank - res <- pInTags "td" pPlain + res <- pInTags celltype pPlain skipMany pBlank return [res] @@ -378,6 +378,16 @@ pInTags tagtype parser = try $ do pSatisfy (~== TagOpen tagtype []) liftM concat $ manyTill parser (pCloses tagtype <|> eof) +pOptInTag :: String -> TagParser a + -> TagParser a +pOptInTag tagtype parser = try $ do + open <- option False (pSatisfy (~== TagOpen tagtype []) >> return True) + skipMany pBlank + x <- parser + skipMany pBlank + when open $ pCloses tagtype + return x + pCloses :: String -> TagParser () pCloses tagtype = try $ do t <- lookAhead $ pSatisfy $ \tag -> isTagClose tag || isTagOpen tag |