aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Module/Utils.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Lua/Module/Utils.hs')
-rw-r--r--src/Text/Pandoc/Lua/Module/Utils.hs18
1 files changed, 9 insertions, 9 deletions
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