aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Org/Inlines.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers/Org/Inlines.hs')
-rw-r--r--src/Text/Pandoc/Readers/Org/Inlines.hs27
1 files changed, 17 insertions, 10 deletions
diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs
index 1055cd0db..d589dd042 100644
--- a/src/Text/Pandoc/Readers/Org/Inlines.hs
+++ b/src/Text/Pandoc/Readers/Org/Inlines.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Readers.Org.Inlines
@@ -788,15 +789,17 @@ simpleSubOrSuperText = try $ do
inlineLaTeX :: PandocMonad m => OrgParser m (F Inlines)
inlineLaTeX = try $ do
cmd <- inlineLaTeXCommand
- ils <- (lift . lift) $ parseAsInlineLaTeX cmd
+ texOpt <- getExportSetting exportWithLatex
+ ils <- parseAsInlineLaTeX cmd texOpt
maybe mzero returnF $
- parseAsMathMLSym cmd `mplus` parseAsMath cmd `mplus` ils
+ parseAsMathMLSym cmd `mplus` parseAsMath cmd texOpt `mplus` ils
where
- parseAsMath :: Text -> Maybe Inlines
- parseAsMath cs = B.fromList <$> texMathToPandoc cs
-
- parseAsInlineLaTeX :: PandocMonad m => Text -> m (Maybe Inlines)
- parseAsInlineLaTeX cs = maybeRight <$> runParserT inlineCommand state "" cs
+ parseAsInlineLaTeX :: PandocMonad m
+ => Text -> TeXExport -> OrgParser m (Maybe Inlines)
+ parseAsInlineLaTeX cs = \case
+ TeXExport -> maybeRight <$> runParserT inlineCommand state "" cs
+ TeXIgnore -> return (Just mempty)
+ TeXVerbatim -> return (Just $ B.str cs)
parseAsMathMLSym :: Text -> Maybe Inlines
parseAsMathMLSym cs = B.str <$> MathMLEntityMap.getUnicode (clean cs)
@@ -807,8 +810,12 @@ inlineLaTeX = try $ do
state = def{ stateOptions = def{ readerExtensions =
enableExtension Ext_raw_tex (readerExtensions def) } }
- texMathToPandoc :: Text -> Maybe [Inline]
- texMathToPandoc cs = maybeRight (readTeX cs) >>= writePandoc DisplayInline
+ parseAsMath :: Text -> TeXExport -> Maybe Inlines
+ parseAsMath cs = \case
+ TeXExport -> maybeRight (readTeX cs) >>=
+ fmap B.fromList . writePandoc DisplayInline
+ TeXIgnore -> Just mempty
+ TeXVerbatim -> Just $ B.str cs
maybeRight :: Either a b -> Maybe b
maybeRight = either (const Nothing) Just
@@ -820,7 +827,7 @@ inlineLaTeXCommand = try $ do
parsed <- (lift . lift) $ runParserT rawLaTeXInline st "source" rest
case parsed of
Right cs -> do
- -- drop any trailing whitespace, those are not be part of the command as
+ -- drop any trailing whitespace, those are not part of the command as
-- far as org mode is concerned.
let cmdNoSpc = T.dropWhileEnd isSpace cs
let len = T.length cmdNoSpc