aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers.hs')
-rw-r--r--src/Text/Pandoc/Readers.hs11
1 files changed, 6 insertions, 5 deletions
diff --git a/src/Text/Pandoc/Readers.hs b/src/Text/Pandoc/Readers.hs
index 3ad479287..461f7f4d9 100644
--- a/src/Text/Pandoc/Readers.hs
+++ b/src/Text/Pandoc/Readers.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Readers
Copyright : Copyright (C) 2006-2019 John MacFarlane
@@ -59,8 +60,8 @@ import Control.Monad (unless)
import Control.Monad.Except (throwError)
import Data.Aeson
import qualified Data.ByteString.Lazy as BL
-import Data.List (intercalate)
import Data.Text (Text)
+import qualified Data.Text as T
import Text.Pandoc.Class
import Text.Pandoc.Definition
import Text.Pandoc.Error
@@ -99,7 +100,7 @@ data Reader m = TextReader (ReaderOptions -> Text -> m Pandoc)
| ByteStringReader (ReaderOptions -> BL.ByteString -> m Pandoc)
-- | Association list of formats and readers.
-readers :: PandocMonad m => [(String, Reader m)]
+readers :: PandocMonad m => [(Text, Reader m)]
readers = [ ("native" , TextReader readNative)
,("json" , TextReader readJSON)
,("markdown" , TextReader readMarkdown)
@@ -135,11 +136,11 @@ readers = [ ("native" , TextReader readNative)
]
-- | Retrieve reader, extensions based on formatSpec (format+extensions).
-getReader :: PandocMonad m => String -> m (Reader m, Extensions)
+getReader :: PandocMonad m => Text -> m (Reader m, Extensions)
getReader s =
case parseFormatSpec s of
Left e -> throwError $ PandocAppError
- $ intercalate "\n" [m | Message m <- errorMessages e]
+ $ T.intercalate "\n" [T.pack m | Message m <- errorMessages e]
Right (readerName, extsToEnable, extsToDisable) ->
case lookup readerName readers of
Nothing -> throwError $ PandocUnknownReaderError
@@ -154,7 +155,7 @@ getReader s =
unless (extensionEnabled ext allExts) $
throwError $
PandocUnsupportedExtensionError
- (drop 4 $ show ext) readerName)
+ (T.drop 4 $ T.pack $ show ext) readerName)
(extsToEnable ++ extsToDisable)
return (r, exts)