From 9e6e9a72218e8c408e151bf8b169f44a8c55eb40 Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Thu, 25 Jun 2020 20:04:09 +0200 Subject: Org reader: honor tex export option The `tex` export option can be set with `#+OPTION: tex:nil` and allows three settings: - `t` causes LaTeX fragments to be parsed as TeX or added as raw TeX, - `nil` removes all LaTeX fragments from the document, and - `verbatim` treats LaTeX as text. The default is `t`. Closes: #4070 --- src/Text/Pandoc/Readers/Org/Inlines.hs | 27 +++++++++++++++++---------- 1 file changed, 17 insertions(+), 10 deletions(-) (limited to 'src/Text/Pandoc/Readers/Org/Inlines.hs') 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 -- cgit v1.2.3