diff options
| author | Albert Krewinkel <[email protected]> | 2022-03-11 18:21:59 +0100 |
|---|---|---|
| committer | GitHub <[email protected]> | 2022-03-11 09:21:59 -0800 |
| commit | 517bceeba81cf645e428e217d1cc518a8fcd34d7 (patch) | |
| tree | 70c84ff4dade9b536ee217cac93c78e6c1aba263 /src/Text/Pandoc/Parsing/Math.hs | |
| parent | 168529f0a4b7f2208f7a6d817d3b972d8b387570 (diff) | |
Parsing: partition module into (internal) submodules (#7962)
Diffstat (limited to 'src/Text/Pandoc/Parsing/Math.hs')
| -rw-r--r-- | src/Text/Pandoc/Parsing/Math.hs | 96 |
1 files changed, 96 insertions, 0 deletions
diff --git a/src/Text/Pandoc/Parsing/Math.hs b/src/Text/Pandoc/Parsing/Math.hs new file mode 100644 index 000000000..f234f9123 --- /dev/null +++ b/src/Text/Pandoc/Parsing/Math.hs @@ -0,0 +1,96 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE OverloadedStrings #-} +{- | +Module : Text.Pandoc.Parsing.Math +Copyright : © 2006-2022 John MacFarlane +License : GPL-2.0-or-later +Maintainer : John MacFarlane <[email protected]> + +Parsing of LaTeX math. +-} + +module Text.Pandoc.Parsing.Math + ( mathDisplay + , mathInline + ) +where + +import Control.Monad (mzero, when) +import Data.Text (Text) +import Text.Parsec ((<|>), Stream(..), notFollowedBy, skipMany, try) +import Text.Pandoc.Options + ( Extension(Ext_tex_math_dollars, Ext_tex_math_single_backslash, + Ext_tex_math_double_backslash) ) +import Text.Pandoc.Parsing.Capabilities (HasReaderOptions, guardEnabled) +import Text.Pandoc.Parsing.Combinators +import Text.Pandoc.Parsing.Types (ParserT) +import Text.Pandoc.Shared (trimMath) +import Text.Pandoc.Sources + (UpdateSourcePos, anyChar, char, digit, newline, satisfy, space, string) + +import qualified Data.Text as T + +mathInlineWith :: (Stream s m Char, UpdateSourcePos s Char) => Text -> Text -> ParserT s st m Text +mathInlineWith op cl = try $ do + textStr op + when (op == "$") $ notFollowedBy space + words' <- many1Till ( + (T.singleton <$> + satisfy (\c -> not (isSpaceChar c || c == '\\'))) + <|> (char '\\' >> + -- This next clause is needed because \text{..} can + -- contain $, \(\), etc. + (try (string "text" >> + (("\\text" <>) <$> inBalancedBraces 0 "")) + <|> (\c -> T.pack ['\\',c]) <$> anyChar)) + <|> do (blankline <* notFollowedBy' blankline) <|> + (spaceChar <* skipMany spaceChar) + notFollowedBy (char '$') + return " " + ) (try $ textStr cl) + notFollowedBy digit -- to prevent capture of $5 + return $ trimMath $ T.concat words' + where + inBalancedBraces :: (Stream s m Char, UpdateSourcePos s Char) => Int -> Text -> ParserT s st m Text + inBalancedBraces n = fmap T.pack . inBalancedBraces' n . T.unpack + + inBalancedBraces' :: (Stream s m Char, UpdateSourcePos s Char) => Int -> String -> ParserT s st m String + inBalancedBraces' 0 "" = do + c <- anyChar + if c == '{' + then inBalancedBraces' 1 "{" + else mzero + inBalancedBraces' 0 s = return $ reverse s + inBalancedBraces' numOpen ('\\':xs) = do + c <- anyChar + inBalancedBraces' numOpen (c:'\\':xs) + inBalancedBraces' numOpen xs = do + c <- anyChar + case c of + '}' -> inBalancedBraces' (numOpen - 1) (c:xs) + '{' -> inBalancedBraces' (numOpen + 1) (c:xs) + _ -> inBalancedBraces' numOpen (c:xs) + +mathDisplayWith :: (Stream s m Char, UpdateSourcePos s Char) => Text -> Text -> ParserT s st m Text +mathDisplayWith op cl = try $ fmap T.pack $ do + textStr op + many1Till (satisfy (/= '\n') <|> (newline <* notFollowedBy' blankline)) + (try $ textStr cl) + +mathDisplay :: (HasReaderOptions st, Stream s m Char, UpdateSourcePos s Char) + => ParserT s st m Text +mathDisplay = + (guardEnabled Ext_tex_math_dollars >> mathDisplayWith "$$" "$$") + <|> (guardEnabled Ext_tex_math_single_backslash >> + mathDisplayWith "\\[" "\\]") + <|> (guardEnabled Ext_tex_math_double_backslash >> + mathDisplayWith "\\\\[" "\\\\]") + +mathInline :: (HasReaderOptions st, Stream s m Char, UpdateSourcePos s Char) + => ParserT s st m Text +mathInline = + (guardEnabled Ext_tex_math_dollars >> mathInlineWith "$" "$") + <|> (guardEnabled Ext_tex_math_single_backslash >> + mathInlineWith "\\(" "\\)") + <|> (guardEnabled Ext_tex_math_double_backslash >> + mathInlineWith "\\\\(" "\\\\)") |
