aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2019-09-28 14:47:41 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2019-09-29 11:43:17 -0700
commit746c92a41a4f1df5ac97246fe69555cef5419d00 (patch)
tree4a300c58e87d1cf65cc5a55a5ef440b0bd71f1af /src/Text/Pandoc/Readers.hs
parent03d4e6b9ef87d4e6ed018c93b358f8557f8f7388 (diff)
downloadpandoc-746c92a41a4f1df5ac97246fe69555cef5419d00.tar.gz
Raise error on unsupported extensions. Closes #4338.
+ An error is now raised if you try to specify (enable or disable) an extension that does not affect the given format, e.g. `docx+pipe_tables`. + The `--list-extensions[=FORMAT]` option now lists only extensions that affect the given FORMAT. + Text.Pandoc.Error: Add constructors `PandocUnknownReaderError`, `PandocUnknownWriterError`, `PandocUnsupportedExtensionError`. [API change] + Text.Pandoc.Extensions now exports `getAllExtensions`, which returns the extensions that affect a given format (whether enabled by default or not). [API change] + Text.Pandoc.Extensions: change type of `parseFormatSpec` from `Either ParseError (String, Extensions -> Extensions)` to `Either ParseError (String, [Extension], [Extension])` [API change]. + Text.Pandoc.Readers: change type of `getReader` so it returns a value in the PandocMonad instance rather than an Either [API change]. Exceptions for unknown formats and unsupported extensions are now raised by this function and need not be handled by the calling function. + Text.Pandoc.Writers: change type of `getWriter` so it returns a value in the PandocMonad instance rather than an Either [API change]. Exceptions for unknown formats and unsupported extensions are now raised by this function and need not be handled by the calling function.
Diffstat (limited to 'src/Text/Pandoc/Readers.hs')
-rw-r--r--src/Text/Pandoc/Readers.hs26
1 files changed, 20 insertions, 6 deletions
diff --git a/src/Text/Pandoc/Readers.hs b/src/Text/Pandoc/Readers.hs
index 1e2f16d43..3ad479287 100644
--- a/src/Text/Pandoc/Readers.hs
+++ b/src/Text/Pandoc/Readers.hs
@@ -55,6 +55,7 @@ module Text.Pandoc.Readers
) where
import Prelude
+import Control.Monad (unless)
import Control.Monad.Except (throwError)
import Data.Aeson
import qualified Data.ByteString.Lazy as BL
@@ -134,15 +135,28 @@ readers = [ ("native" , TextReader readNative)
]
-- | Retrieve reader, extensions based on formatSpec (format+extensions).
-getReader :: PandocMonad m => String -> Either String (Reader m, Extensions)
+getReader :: PandocMonad m => String -> m (Reader m, Extensions)
getReader s =
case parseFormatSpec s of
- Left e -> Left $ intercalate "\n" [m | Message m <- errorMessages e]
- Right (readerName, setExts) ->
+ Left e -> throwError $ PandocAppError
+ $ intercalate "\n" [m | Message m <- errorMessages e]
+ Right (readerName, extsToEnable, extsToDisable) ->
case lookup readerName readers of
- Nothing -> Left $ "Unknown reader: " ++ readerName
- Just r -> Right (r, setExts $
- getDefaultExtensions readerName)
+ Nothing -> throwError $ PandocUnknownReaderError
+ readerName
+ Just r -> do
+ let allExts = getAllExtensions readerName
+ let exts = foldr disableExtension
+ (foldr enableExtension
+ (getDefaultExtensions readerName)
+ extsToEnable) extsToDisable
+ mapM_ (\ext ->
+ unless (extensionEnabled ext allExts) $
+ throwError $
+ PandocUnsupportedExtensionError
+ (drop 4 $ show ext) readerName)
+ (extsToEnable ++ extsToDisable)
+ return (r, exts)
-- | Read pandoc document from JSON format.
readJSON :: PandocMonad m