aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Module
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Lua/Module')
-rw-r--r--src/Text/Pandoc/Lua/Module/MediaBag.hs6
-rw-r--r--src/Text/Pandoc/Lua/Module/Pandoc.hs19
-rw-r--r--src/Text/Pandoc/Lua/Module/Utils.hs18
3 files changed, 22 insertions, 21 deletions
diff --git a/src/Text/Pandoc/Lua/Module/MediaBag.hs b/src/Text/Pandoc/Lua/Module/MediaBag.hs
index 261785665..951571ddd 100644
--- a/src/Text/Pandoc/Lua/Module/MediaBag.hs
+++ b/src/Text/Pandoc/Lua/Module/MediaBag.hs
@@ -15,7 +15,6 @@ module Text.Pandoc.Lua.Module.MediaBag
import Prelude
import Control.Monad (zipWithM_)
-import Data.Maybe (fromMaybe)
import Foreign.Lua (Lua, NumResults, Optional, liftIO)
import Text.Pandoc.Class (CommonState (..), fetchItem, putCommonState,
runIOorExplode, setMediaBag)
@@ -25,6 +24,7 @@ import Text.Pandoc.Lua.Util (addFunction)
import Text.Pandoc.MIME (MimeType)
import qualified Data.ByteString.Lazy as BL
+import qualified Data.Text as T
import qualified Foreign.Lua as Lua
import qualified Text.Pandoc.MediaBag as MB
@@ -113,7 +113,7 @@ mediaDirectoryFn = do
Lua.push "length" *> Lua.push contentLength *> Lua.rawset (-3)
Lua.rawseti (-2) idx
-fetch :: String
+fetch :: T.Text
-> Lua NumResults
fetch src = do
commonState <- getCommonState
@@ -122,6 +122,6 @@ fetch src = do
putCommonState commonState
setMediaBag mediaBag
fetchItem src
- Lua.push $ fromMaybe "" mimeType
+ Lua.push $ maybe "" T.unpack mimeType
Lua.push bs
return 2 -- returns 2 values: contents, mimetype
diff --git a/src/Text/Pandoc/Lua/Module/Pandoc.hs b/src/Text/Pandoc/Lua/Module/Pandoc.hs
index 182008da7..36d6f4009 100644
--- a/src/Text/Pandoc/Lua/Module/Pandoc.hs
+++ b/src/Text/Pandoc/Lua/Module/Pandoc.hs
@@ -1,5 +1,6 @@
-{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua.Module.Pandoc
Copyright : Copyright © 2017-2019 Albert Krewinkel
@@ -19,7 +20,6 @@ import Control.Monad (when)
import Control.Monad.Except (throwError)
import Data.Default (Default (..))
import Data.Maybe (fromMaybe)
-import Data.Text (pack)
import Foreign.Lua (Lua, NumResults, Optional, Peekable, Pushable)
import System.Exit (ExitCode (..))
import Text.Pandoc.Class (runIO)
@@ -33,6 +33,7 @@ import Text.Pandoc.Readers (Reader (..), getReader)
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BSL
+import qualified Data.Text as T
import qualified Foreign.Lua as Lua
import qualified Text.Pandoc.Lua.Util as LuaUtil
import Text.Pandoc.Error
@@ -59,22 +60,22 @@ walkInline = walkElement
walkBlock :: Block -> LuaFilter -> Lua Block
walkBlock = walkElement
-readDoc :: String -> Optional String -> Lua NumResults
+readDoc :: T.Text -> Optional T.Text -> Lua NumResults
readDoc content formatSpecOrNil = do
let formatSpec = fromMaybe "markdown" (Lua.fromOptional formatSpecOrNil)
res <- Lua.liftIO . runIO $
getReader formatSpec >>= \(rdr,es) ->
case rdr of
TextReader r ->
- r def{ readerExtensions = es } (pack content)
+ r def{ readerExtensions = es } content
_ -> throwError $ PandocSomeError $
"Only textual formats are supported"
case res of
Right pd -> (1 :: NumResults) <$ Lua.push pd -- success, push Pandoc
Left (PandocUnknownReaderError f) -> Lua.raiseError $
- "Unknown reader: " ++ f
+ "Unknown reader: " <> f
Left (PandocUnsupportedExtensionError e f) -> Lua.raiseError $
- "Extension " ++ e ++ " not supported for " ++ f
+ "Extension " <> e <> " not supported for " <> f
Left e -> Lua.raiseError $ show e
-- | Pipes input through a command.
@@ -86,10 +87,10 @@ pipeFn command args input = do
(ec, output) <- Lua.liftIO $ pipeProcess Nothing command args input
case ec of
ExitSuccess -> 1 <$ Lua.push output
- ExitFailure n -> Lua.raiseError (PipeError command n output)
+ ExitFailure n -> Lua.raiseError (PipeError (T.pack command) n output)
data PipeError = PipeError
- { pipeErrorCommand :: String
+ { pipeErrorCommand :: T.Text
, pipeErrorCode :: Int
, pipeErrorOutput :: BL.ByteString
}
@@ -118,7 +119,7 @@ instance Pushable PipeError where
pipeErrorMessage :: PipeError -> Lua BL.ByteString
pipeErrorMessage (PipeError cmd errorCode output) = return $ mconcat
[ BSL.pack "Error running "
- , BSL.pack cmd
+ , BSL.pack $ T.unpack cmd
, BSL.pack " (error code "
, BSL.pack $ show errorCode
, BSL.pack "): "
diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs
index 057e6580b..7d6dd0fab 100644
--- a/src/Text/Pandoc/Lua/Module/Utils.hs
+++ b/src/Text/Pandoc/Lua/Module/Utils.hs
@@ -15,7 +15,6 @@ module Text.Pandoc.Lua.Module.Utils
import Prelude
import Control.Applicative ((<|>))
-import Data.Char (toLower)
import Data.Default (def)
import Data.Version (Version)
import Foreign.Lua (Peekable, Lua, NumResults)
@@ -27,6 +26,7 @@ import Text.Pandoc.Lua.Util (addFunction)
import qualified Data.Digest.Pure.SHA as SHA
import qualified Data.ByteString.Lazy as BSL
+import qualified Data.Text as T
import qualified Foreign.Lua as Lua
import qualified Text.Pandoc.Builder as B
import qualified Text.Pandoc.Filter.JSON as JSONFilter
@@ -64,7 +64,7 @@ makeSections number baselevel =
-- limit years to the range 1601-9999 (ISO 8601 accepts greater than
-- or equal to 1583, but MS Word only accepts dates starting 1601).
-- Returns nil instead of a string if the conversion failed.
-normalizeDate :: String -> Lua (Lua.Optional String)
+normalizeDate :: T.Text -> Lua (Lua.Optional T.Text)
normalizeDate = return . Lua.Optional . Shared.normalizeDate
-- | Run a JSON filter on the given document.
@@ -88,13 +88,13 @@ runJSONFilter mbDatadir doc filterFile optArgs = do
-- | Calculate the hash of the given contents.
sha1 :: BSL.ByteString
- -> Lua String
-sha1 = return . SHA.showDigest . SHA.sha1
+ -> Lua T.Text
+sha1 = return . T.pack . SHA.showDigest . SHA.sha1
-- | Convert pandoc structure to a string with formatting removed.
-- Footnotes are skipped (since we don't want their contents in link
-- labels).
-stringify :: AstElement -> Lua String
+stringify :: AstElement -> Lua T.Text
stringify el = return $ case el of
PandocElement pd -> Shared.stringify pd
InlineElement i -> Shared.stringify i
@@ -102,11 +102,11 @@ stringify el = return $ case el of
MetaElement m -> Shared.stringify m
CitationElement c -> Shared.stringify c
MetaValueElement m -> stringifyMetaValue m
- _ -> ""
+ _ -> mempty
-stringifyMetaValue :: MetaValue -> String
+stringifyMetaValue :: MetaValue -> T.Text
stringifyMetaValue mv = case mv of
- MetaBool b -> map toLower (show b)
+ MetaBool b -> T.toLower $ T.pack (show b)
MetaString s -> s
_ -> Shared.stringify mv
@@ -139,5 +139,5 @@ instance Peekable AstElement where
"Expected an AST element, but could not parse value as such."
-- | Convert a number < 4000 to uppercase roman numeral.
-toRomanNumeral :: Lua.Integer -> Lua String
+toRomanNumeral :: Lua.Integer -> Lua T.Text
toRomanNumeral = return . Shared.toRomanNumeral . fromIntegral