aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Org
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2020-06-25 20:04:09 +0200
committerAlbert Krewinkel <albert@zeitkraut.de>2020-06-25 20:31:33 +0200
commit9e6e9a72218e8c408e151bf8b169f44a8c55eb40 (patch)
treef23a3fbe465857e9d257aa8c092cc126236452dc /src/Text/Pandoc/Readers/Org
parentf1c678a97eef702bf37ddfdf5af977b4ba5b02a6 (diff)
downloadpandoc-9e6e9a72218e8c408e151bf8b169f44a8c55eb40.tar.gz
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
Diffstat (limited to 'src/Text/Pandoc/Readers/Org')
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs32
-rw-r--r--src/Text/Pandoc/Readers/Org/ExportSettings.hs36
-rw-r--r--src/Text/Pandoc/Readers/Org/Inlines.hs27
-rw-r--r--src/Text/Pandoc/Readers/Org/ParserState.hs10
4 files changed, 75 insertions, 30 deletions
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index b2cf3b3ec..2fbb26d31 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -34,7 +34,7 @@ import Text.Pandoc.Shared (compactify, compactifyDL, safeRead)
import Control.Monad (foldM, guard, mplus, mzero, void)
import Data.Char (isSpace)
import Data.Default (Default)
-import Data.List (foldl')
+import Data.List (foldl', intersperse)
import Data.Maybe (fromMaybe, isJust, isNothing)
import Data.Text (Text)
@@ -739,22 +739,26 @@ rowToContent tbl row =
--
-- LaTeX fragments
--
-latexFragment :: Monad m => OrgParser m (F Blocks)
+latexFragment :: PandocMonad m => OrgParser m (F Blocks)
latexFragment = try $ do
envName <- latexEnvStart
- content <- mconcat <$> manyTill anyLineNewline (latexEnd envName)
- returnF $ B.rawBlock "latex" (content `inLatexEnv` envName)
+ texOpt <- getExportSetting exportWithLatex
+ let envStart = "\\begin{" <> envName <> "}"
+ let envEnd = "\\end{" <> envName <> "}"
+ envLines <- do
+ content <- manyTill anyLine (latexEnd envName)
+ return $ envStart : content ++ [envEnd]
+ returnF $ case texOpt of
+ TeXExport -> B.rawBlock "latex" . T.unlines $ envLines
+ TeXIgnore -> mempty
+ TeXVerbatim -> B.para . mconcat . intersperse B.softbreak $
+ map B.str envLines
where
- c `inLatexEnv` e = mconcat [ "\\begin{", e, "}\n"
- , c
- , "\\end{", e, "}\n"
- ]
-
-latexEnd :: Monad m => Text -> OrgParser m ()
-latexEnd envName = try $
- () <$ skipSpaces
- <* textStr ("\\end{" <> envName <> "}")
- <* blankline
+ latexEnd :: Monad m => Text -> OrgParser m ()
+ latexEnd envName = try . void
+ $ skipSpaces
+ <* textStr ("\\end{" <> envName <> "}")
+ <* blankline
--
diff --git a/src/Text/Pandoc/Readers/Org/ExportSettings.hs b/src/Text/Pandoc/Readers/Org/ExportSettings.hs
index 9b293f880..ab402b8c9 100644
--- a/src/Text/Pandoc/Readers/Org/ExportSettings.hs
+++ b/src/Text/Pandoc/Readers/Org/ExportSettings.hs
@@ -20,7 +20,7 @@ import Text.Pandoc.Readers.Org.Parsing
import Control.Monad (mzero, void)
import Data.Char (toLower)
import Data.Maybe (listToMaybe)
-import Data.Text (Text)
+import Data.Text (Text, unpack)
-- | Read and handle space separated org-mode export settings.
exportSettings :: PandocMonad m => OrgParser m ()
@@ -59,7 +59,7 @@ exportSetting = choice
, ignoredSetting "stat"
, booleanSetting "tags" (\val es -> es { exportWithTags = val })
, ignoredSetting "tasks"
- , ignoredSetting "tex"
+ , texSetting "tex" (\val es -> es { exportWithLatex = val })
, ignoredSetting "timestamp"
, ignoredSetting "title"
, ignoredSetting "toc"
@@ -68,6 +68,8 @@ exportSetting = choice
, ignoreAndWarn
] <?> "export setting"
+-- | Generic handler for export settings. Takes a parser which converts
+-- the plain option text into a data structure.
genericExportSetting :: Monad m
=> OrgParser m a
-> Text
@@ -101,10 +103,8 @@ archivedTreeSetting :: Monad m
archivedTreeSetting =
genericExportSetting $ archivedTreesHeadlineSetting <|> archivedTreesBoolean
where
- archivedTreesHeadlineSetting = try $ do
- _ <- string "headline"
- lookAhead (newline <|> spaceChar)
- return ArchivedTreesHeadlineOnly
+ archivedTreesHeadlineSetting =
+ ArchivedTreesHeadlineOnly <$ optionString "headline"
archivedTreesBoolean = try $ do
exportBool <- elispBoolean
@@ -143,6 +143,22 @@ complementableListSetting = genericExportSetting $ choice
char '"'
*> manyTillChar alphaNum (char '"')
+-- | Parses either @t@, @nil@, or @verbatim@ into a 'TeXExport' value.
+texSetting :: Monad m
+ => Text
+ -> ExportSettingSetter TeXExport
+ -> OrgParser m ()
+texSetting = genericExportSetting $ texVerbatim <|> texBoolean
+ where
+ texVerbatim = TeXVerbatim <$ optionString "verbatim"
+
+ texBoolean = try $ do
+ exportBool <- elispBoolean
+ return $
+ if exportBool
+ then TeXExport
+ else TeXIgnore
+
-- | Read but ignore the export setting.
ignoredSetting :: Monad m => Text -> OrgParser m ()
ignoredSetting s = try (() <$ textStr s <* char ':' <* many1 nonspaceChar)
@@ -164,3 +180,11 @@ elispBoolean = try $ do
"{}" -> False
"()" -> False
_ -> True
+
+-- | Try to parse a literal string as the option value. Returns the
+-- string on success.
+optionString :: Monad m => Text -> OrgParser m Text
+optionString s = try $ do
+ _ <- string (unpack s)
+ lookAhead (newline <|> spaceChar)
+ return s
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
diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs
index 0e2175da9..289b64193 100644
--- a/src/Text/Pandoc/Readers/Org/ParserState.hs
+++ b/src/Text/Pandoc/Readers/Org/ParserState.hs
@@ -35,6 +35,7 @@ module Text.Pandoc.Readers.Org.ParserState
, returnF
, ExportSettings (..)
, ArchivedTreesOption (..)
+ , TeXExport (..)
, optionsToParserState
) where
@@ -231,6 +232,13 @@ data ArchivedTreesOption =
| ArchivedTreesNoExport -- ^ Exclude archived trees from exporting
| ArchivedTreesHeadlineOnly -- ^ Export only the headline, discard the contents
+-- | Options for the handling of LaTeX environments and fragments.
+-- Represents allowed values of Emacs variable @org-export-with-latex@.
+data TeXExport
+ = TeXExport -- ^ Include raw TeX in the output
+ | TeXIgnore -- ^ Ignore raw TeX
+ | TeXVerbatim -- ^ Keep everything in verbatim
+
-- | Export settings <http://orgmode.org/manual/Export-settings.html>
-- These settings can be changed via OPTIONS statements.
data ExportSettings = ExportSettings
@@ -249,6 +257,7 @@ data ExportSettings = ExportSettings
, exportWithAuthor :: Bool -- ^ Include author in final meta-data
, exportWithCreator :: Bool -- ^ Include creator in final meta-data
, exportWithEmail :: Bool -- ^ Include email in final meta-data
+ , exportWithLatex :: TeXExport -- ^ Handling of raw TeX commands
, exportWithPlanning :: Bool -- ^ Keep planning info after headlines
, exportWithTags :: Bool -- ^ Keep tags as part of headlines
, exportWithTodoKeywords :: Bool -- ^ Keep TODO keywords in headers
@@ -270,6 +279,7 @@ defaultExportSettings = ExportSettings
, exportWithAuthor = True
, exportWithCreator = True
, exportWithEmail = True
+ , exportWithLatex = TeXExport
, exportWithPlanning = False
, exportWithTags = True
, exportWithTodoKeywords = True