aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2019-05-13 22:25:04 +0200
committerAlbert Krewinkel <albert@zeitkraut.de>2019-05-13 22:25:04 +0200
commit00ef03827e4ab77a1213b2adf261c818ddae076d (patch)
tree2c8036d1236e3b184278bf9400bdab6e31ce91d9
parent1d033a26918e1117bef6fe1629571179a27c861c (diff)
downloadpandoc-00ef03827e4ab77a1213b2adf261c818ddae076d.tar.gz
Org reader: omit, but warn about unknown export options
Unknown export options are properly ignored and omitted from the output.
-rw-r--r--src/Text/Pandoc/Logging.hs6
-rw-r--r--src/Text/Pandoc/Readers/Org/ExportSettings.hs16
-rw-r--r--src/Text/Pandoc/Readers/Org/Meta.hs2
-rw-r--r--test/Tests/Readers/Org/Directive.hs18
4 files changed, 38 insertions, 4 deletions
diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs
index e0a76a076..2fb648b12 100644
--- a/src/Text/Pandoc/Logging.hs
+++ b/src/Text/Pandoc/Logging.hs
@@ -86,6 +86,7 @@ data LogMessage =
| NoTranslation String
| CouldNotLoadTranslations String String
| UnexpectedXmlElement String String
+ | UnknownOrgExportOption String
deriving (Show, Eq, Data, Ord, Typeable, Generic)
instance ToJSON LogMessage where
@@ -201,6 +202,8 @@ instance ToJSON LogMessage where
UnexpectedXmlElement element parent ->
["element" .= Text.pack element,
"parent" .= Text.pack parent]
+ UnknownOrgExportOption option ->
+ ["option" .= Text.pack option]
showPos :: SourcePos -> String
@@ -300,6 +303,8 @@ showLogMessage msg =
if null m then "" else '\n' : m
UnexpectedXmlElement element parent ->
"Unexpected XML element " ++ element ++ " in " ++ parent
+ UnknownOrgExportOption option ->
+ "Ignoring unknown Org export option: " ++ option
messageVerbosity:: LogMessage -> Verbosity
messageVerbosity msg =
@@ -339,3 +344,4 @@ messageVerbosity msg =
NoTranslation{} -> WARNING
CouldNotLoadTranslations{} -> WARNING
UnexpectedXmlElement {} -> WARNING
+ UnknownOrgExportOption {} -> WARNING
diff --git a/src/Text/Pandoc/Readers/Org/ExportSettings.hs b/src/Text/Pandoc/Readers/Org/ExportSettings.hs
index 467c5339d..f783eaa0f 100644
--- a/src/Text/Pandoc/Readers/Org/ExportSettings.hs
+++ b/src/Text/Pandoc/Readers/Org/ExportSettings.hs
@@ -13,6 +13,8 @@ module Text.Pandoc.Readers.Org.ExportSettings
) where
import Prelude
+import Text.Pandoc.Class (PandocMonad, report)
+import Text.Pandoc.Logging (LogMessage (UnknownOrgExportOption))
import Text.Pandoc.Readers.Org.ParserState
import Text.Pandoc.Readers.Org.Parsing
@@ -21,14 +23,14 @@ import Data.Char (toLower)
import Data.Maybe (listToMaybe)
-- | Read and handle space separated org-mode export settings.
-exportSettings :: Monad m => OrgParser m ()
-exportSettings = void $ sepBy spaces exportSetting
+exportSettings :: PandocMonad m => OrgParser m ()
+exportSettings = void $ sepBy skipSpaces exportSetting
-- | Setter function for export settings.
type ExportSettingSetter a = a -> ExportSettings -> ExportSettings
-- | Read and process a single org-mode export option.
-exportSetting :: Monad m => OrgParser m ()
+exportSetting :: PandocMonad m => OrgParser m ()
exportSetting = choice
[ booleanSetting "^" (\val es -> es { exportSubSuperscripts = val })
, booleanSetting "'" (\val es -> es { exportSmartQuotes = val })
@@ -63,6 +65,7 @@ exportSetting = choice
, ignoredSetting "toc"
, booleanSetting "todo" (\val es -> es { exportWithTodoKeywords = val })
, ignoredSetting "|"
+ , ignoreAndWarn
] <?> "export setting"
genericExportSetting :: Monad m
@@ -144,6 +147,13 @@ complementableListSetting = genericExportSetting $ choice
ignoredSetting :: Monad m => String -> OrgParser m ()
ignoredSetting s = try (() <$ string s <* char ':' <* many1 nonspaceChar)
+-- | Read any setting string, but ignore it and emit a warning.
+ignoreAndWarn :: PandocMonad m => OrgParser m ()
+ignoreAndWarn = try $ do
+ opt <- many1 nonspaceChar
+ report (UnknownOrgExportOption opt)
+ return ()
+
-- | Read an elisp boolean. Only NIL is treated as false, non-NIL values are
-- interpreted as true.
elispBoolean :: Monad m => OrgParser m Bool
diff --git a/src/Text/Pandoc/Readers/Org/Meta.hs b/src/Text/Pandoc/Readers/Org/Meta.hs
index bcbc2edab..0a388403e 100644
--- a/src/Text/Pandoc/Readers/Org/Meta.hs
+++ b/src/Text/Pandoc/Readers/Org/Meta.hs
@@ -131,7 +131,7 @@ accumulatingList key p = do
--
-- export options
--
-optionLine :: Monad m => OrgParser m ()
+optionLine :: PandocMonad m => OrgParser m ()
optionLine = try $ do
key <- metaKey
case key of
diff --git a/test/Tests/Readers/Org/Directive.hs b/test/Tests/Readers/Org/Directive.hs
index 6d6609d4e..d8a8a8733 100644
--- a/test/Tests/Readers/Org/Directive.hs
+++ b/test/Tests/Readers/Org/Directive.hs
@@ -184,6 +184,24 @@ tests =
] =?>
headerWith ("wichtig", mempty, mempty) 1 "Wichtig"
]
+
+ , testGroup "unknown options"
+ [ "unknown options are ignored" =:
+ T.unlines [ "#+OPTIONS: does-not-exist:t "] =?>
+ (mempty :: Pandoc)
+
+ , "highlighting after unknown option" =:
+ T.unlines [ "#+OPTIONS: nope"
+ , "/yup/"
+ ] =?>
+ para (emph "yup")
+
+ , "unknown option interleaved with known" =:
+ T.unlines [ "#+OPTIONS: tags:nil foo:bar todo:nil"
+ , "* DONE ignore things :easy:"
+ ] =?>
+ headerWith ("ignore-things", [], mempty) 1 "ignore things"
+ ]
]
, testGroup "Include"