HTML reader: Parse LaTeX math if appropriate options are set.

* Moved inlineMath, displayMath from Markdown reader to Parsing.
* Export them from Parsing.  (API change.)
* Generalize their types.
This commit is contained in:
John MacFarlane 2013-12-06 16:43:59 -08:00
parent 9b6f1fc495
commit def05d3504
4 changed files with 45 additions and 35 deletions

View file

@ -48,6 +48,8 @@ module Text.Pandoc.Parsing ( (>>~),
romanNumeral,
emailAddress,
uri,
mathInline,
mathDisplay,
withHorizDisplacement,
withRaw,
escaped,
@ -455,6 +457,39 @@ uri = try $ do
let uri' = scheme ++ ":" ++ fromEntities str'
return (uri', escapeURI uri')
mathInlineWith :: String -> String -> Parser [Char] st String
mathInlineWith op cl = try $ do
string op
notFollowedBy space
words' <- many1Till (count 1 (noneOf "\n\\")
<|> (char '\\' >> anyChar >>= \c -> return ['\\',c])
<|> count 1 newline <* notFollowedBy' blankline
*> return " ")
(try $ string cl)
notFollowedBy digit -- to prevent capture of $5
return $ concat words'
mathDisplayWith :: String -> String -> Parser [Char] st String
mathDisplayWith op cl = try $ do
string op
many1Till (noneOf "\n" <|> (newline >>~ notFollowedBy' blankline)) (try $ string cl)
mathDisplay :: Parser [Char] ParserState String
mathDisplay =
(guardEnabled Ext_tex_math_dollars >> mathDisplayWith "$$" "$$")
<|> (guardEnabled Ext_tex_math_single_backslash >>
mathDisplayWith "\\[" "\\]")
<|> (guardEnabled Ext_tex_math_double_backslash >>
mathDisplayWith "\\\\[" "\\\\]")
mathInline :: Parser [Char] ParserState String
mathInline =
(guardEnabled Ext_tex_math_dollars >> mathInlineWith "$" "$")
<|> (guardEnabled Ext_tex_math_single_backslash >>
mathInlineWith "\\(" "\\)")
<|> (guardEnabled Ext_tex_math_double_backslash >>
mathInlineWith "\\\\(" "\\\\)")
-- | Applies a parser, returns tuple of its results and its horizontal
-- displacement (the difference between the source column at the end
-- and the source column at the beginning). Vertical displacement

View file

@ -467,7 +467,13 @@ pBlank = try $ do
pTagContents :: Parser [Char] ParserState Inline
pTagContents =
pStr <|> pSpace <|> smartPunctuation pTagContents <|> pSymbol <|> pBad
Math InlineMath `fmap` mathInline
<|> Math DisplayMath `fmap` mathDisplay
<|> pStr
<|> pSpace
<|> smartPunctuation pTagContents
<|> pSymbol
<|> pBad
pStr :: Parser [Char] ParserState Inline
pStr = do
@ -482,6 +488,7 @@ isSpecial '"' = True
isSpecial '\'' = True
isSpecial '.' = True
isSpecial '-' = True
isSpecial '$' = True
isSpecial '\8216' = True
isSpecial '\8217' = True
isSpecial '\8220' = True

View file

@ -38,7 +38,8 @@ import Text.Pandoc.Definition
import Text.Pandoc.Walk
import Text.Pandoc.Shared
import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding ((<|>), many, optional, space)
import Text.Pandoc.Parsing hiding ((<|>), many, optional, space,
mathDisplay, mathInline)
import qualified Text.Pandoc.UTF8 as UTF8
import Data.Char ( chr, ord )
import Control.Monad

View file

@ -1408,39 +1408,6 @@ math :: MarkdownParser (F Inlines)
math = (return . B.displayMath <$> (mathDisplay >>= applyMacros'))
<|> (return . B.math <$> (mathInline >>= applyMacros'))
mathDisplay :: MarkdownParser String
mathDisplay =
(guardEnabled Ext_tex_math_dollars >> mathDisplayWith "$$" "$$")
<|> (guardEnabled Ext_tex_math_single_backslash >>
mathDisplayWith "\\[" "\\]")
<|> (guardEnabled Ext_tex_math_double_backslash >>
mathDisplayWith "\\\\[" "\\\\]")
mathDisplayWith :: String -> String -> MarkdownParser String
mathDisplayWith op cl = try $ do
string op
many1Till (noneOf "\n" <|> (newline >>~ notFollowedBy' blankline)) (try $ string cl)
mathInline :: MarkdownParser String
mathInline =
(guardEnabled Ext_tex_math_dollars >> mathInlineWith "$" "$")
<|> (guardEnabled Ext_tex_math_single_backslash >>
mathInlineWith "\\(" "\\)")
<|> (guardEnabled Ext_tex_math_double_backslash >>
mathInlineWith "\\\\(" "\\\\)")
mathInlineWith :: String -> String -> MarkdownParser String
mathInlineWith op cl = try $ do
string op
notFollowedBy space
words' <- many1Till (count 1 (noneOf "\n\\")
<|> (char '\\' >> anyChar >>= \c -> return ['\\',c])
<|> count 1 newline <* notFollowedBy' blankline
*> return " ")
(try $ string cl)
notFollowedBy digit -- to prevent capture of $5
return $ concat words'
-- Parses material enclosed in *s, **s, _s, or __s.
-- Designed to avoid backtracking.
enclosure :: Char