aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2017-08-16 15:47:05 +0200
committerAlbert Krewinkel <albert@zeitkraut.de>2017-08-16 15:47:05 +0200
commit9b318355300ca43aadede728c179785f40326d5c (patch)
tree1fc440cda2961e6fcb4f90e0f3f162970cd55c42 /src/Text/Pandoc
parentf8b6a224aec780785baf3112f24c44f6c424e6ba (diff)
downloadpandoc-9b318355300ca43aadede728c179785f40326d5c.tar.gz
Update to hslua-0.8.0
hslua no longer provides lua stack instances for Int and Double, the necessary instances are added to the Custom writer and the lua filtering system.
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Lua/StackInstances.hs14
-rw-r--r--src/Text/Pandoc/Writers/Custom.hs6
2 files changed, 18 insertions, 2 deletions
diff --git a/src/Text/Pandoc/Lua/StackInstances.hs b/src/Text/Pandoc/Lua/StackInstances.hs
index da9c33183..15a7cdd84 100644
--- a/src/Text/Pandoc/Lua/StackInstances.hs
+++ b/src/Text/Pandoc/Lua/StackInstances.hs
@@ -33,8 +33,8 @@ StackValue instances for pandoc types.
module Text.Pandoc.Lua.StackInstances () where
import Control.Applicative ((<|>))
-import Foreign.Lua (Lua, Type (..), FromLuaStack (peek), ToLuaStack (push),
- StackIndex, throwLuaError, tryLua)
+import Foreign.Lua (Lua, LuaInteger, LuaNumber, Type (..), FromLuaStack (peek),
+ ToLuaStack (push), StackIndex, throwLuaError, tryLua)
import Foreign.Lua.Api (getmetatable, ltype, newtable, pop, rawget, rawlen)
import Text.Pandoc.Definition
import Text.Pandoc.Lua.Util (addValue, adjustIndexBy, getTable, pushViaConstructor)
@@ -125,6 +125,16 @@ instance ToLuaStack QuoteType where
instance FromLuaStack QuoteType where
peek idx = safeRead' =<< peek idx
+instance ToLuaStack Double where
+ push = push . (realToFrac :: Double -> LuaNumber)
+instance FromLuaStack Double where
+ peek = fmap (realToFrac :: LuaNumber -> Double) . peek
+
+instance ToLuaStack Int where
+ push = push . (fromIntegral :: Int -> LuaInteger)
+instance FromLuaStack Int where
+ peek = fmap (fromIntegral :: LuaInteger-> Int) . peek
+
safeRead' :: Read a => String -> Lua a
safeRead' s = case safeRead s of
Nothing -> throwLuaError ("Could not read: " ++ s)
diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs
index 63725bb60..d7dff6d19 100644
--- a/src/Text/Pandoc/Writers/Custom.hs
+++ b/src/Text/Pandoc/Writers/Custom.hs
@@ -60,6 +60,12 @@ attrToMap (id',classes,keyvals) = M.fromList
: ("class", unwords classes)
: keyvals
+instance ToLuaStack Double where
+ push = push . (realToFrac :: Double -> LuaNumber)
+
+instance ToLuaStack Int where
+ push = push . (fromIntegral :: Int -> LuaInteger)
+
instance ToLuaStack Format where
push (Format f) = push (map toLower f)