aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/Custom.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/Custom.hs')
-rw-r--r--src/Text/Pandoc/Writers/Custom.hs13
1 files changed, 7 insertions, 6 deletions
diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs
index 6c4f92db0..733b29ac7 100644
--- a/src/Text/Pandoc/Writers/Custom.hs
+++ b/src/Text/Pandoc/Writers/Custom.hs
@@ -1,5 +1,6 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Writers.Custom
Copyright : Copyright (C) 2012-2019 John MacFarlane
@@ -17,9 +18,9 @@ import Prelude
import Control.Arrow ((***))
import Control.Exception
import Control.Monad (when)
-import Data.Char (toLower)
import Data.List (intersperse)
import qualified Data.Map as M
+import qualified Data.Text as T
import Data.Text (Text, pack)
import Data.Typeable
import Foreign.Lua (Lua, Pushable)
@@ -36,16 +37,16 @@ import Text.Pandoc.Writers.Shared
import qualified Foreign.Lua as Lua
-attrToMap :: Attr -> M.Map String String
+attrToMap :: Attr -> M.Map T.Text T.Text
attrToMap (id',classes,keyvals) = M.fromList
$ ("id", id')
- : ("class", unwords classes)
+ : ("class", T.unwords classes)
: keyvals
newtype Stringify a = Stringify a
instance Pushable (Stringify Format) where
- push (Stringify (Format f)) = Lua.push (map toLower f)
+ push (Stringify (Format f)) = Lua.push (T.toLower f)
instance Pushable (Stringify [Inline]) where
push (Stringify ils) = Lua.push =<< inlineListToCustom ils
@@ -82,7 +83,7 @@ instance (Pushable a, Pushable b) => Pushable (KeyValue a b) where
Lua.push v
Lua.rawset (Lua.nthFromTop 3)
-data PandocLuaException = PandocLuaException String
+data PandocLuaException = PandocLuaException Text
deriving (Show, Typeable)
instance Exception PandocLuaException
@@ -99,7 +100,7 @@ writeCustom luaFile opts doc@(Pandoc meta _) = do
-- check for error in lua script (later we'll change the return type
-- to handle this more gracefully):
when (stat /= Lua.OK) $
- Lua.tostring' (-1) >>= throw . PandocLuaException . UTF8.toString
+ Lua.tostring' (-1) >>= throw . PandocLuaException . UTF8.toText
rendered <- docToCustom opts doc
context <- metaToContext opts
(fmap (literal . pack) . blockListToCustom)