aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Util.hs
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2018-08-12 00:38:43 +0200
committerAlbert Krewinkel <albert@zeitkraut.de>2018-08-12 12:28:06 +0200
commitacf6df1aef337f71612f6d05c8aaa526255b3942 (patch)
tree1964c4b4a4bb6f423d7cca693b07afd925b6b25f /src/Text/Pandoc/Lua/Util.hs
parentfb3ee947aa288af31d76369ab380bf68d3024752 (diff)
downloadpandoc-acf6df1aef337f71612f6d05c8aaa526255b3942.tar.gz
Lua: cleanup Lua utils, remove unused functions.
Diffstat (limited to 'src/Text/Pandoc/Lua/Util.hs')
-rw-r--r--src/Text/Pandoc/Lua/Util.hs84
1 files changed, 28 insertions, 56 deletions
diff --git a/src/Text/Pandoc/Lua/Util.hs b/src/Text/Pandoc/Lua/Util.hs
index ea9ec2554..c12884a10 100644
--- a/src/Text/Pandoc/Lua/Util.hs
+++ b/src/Text/Pandoc/Lua/Util.hs
@@ -31,14 +31,11 @@ Lua utility functions.
-}
module Text.Pandoc.Lua.Util
( getTag
- , getTable
- , addValue
+ , rawField
+ , addField
, addFunction
- , getRawInt
- , setRawInt
- , addRawInt
+ , addValue
, typeCheck
- , raiseError
, popValue
, PushViaCall
, pushViaCall
@@ -51,34 +48,30 @@ import Prelude
import Control.Monad (when)
import Control.Monad.Catch (finally)
import Data.ByteString.Char8 (unpack)
-import Foreign.Lua (FromLuaStack (..), NumResults, Lua, NumArgs, StackIndex,
- ToLuaStack (..), ToHaskellFunction)
-import Foreign.Lua.Api (Status, call, pop, rawget, rawgeti, rawset, rawseti)
+import Foreign.Lua (FromLuaStack, Lua, NumArgs, StackIndex, Status,
+ ToLuaStack, ToHaskellFunction)
import Text.Pandoc.Class (readDataFile, runIOorExplode, setUserDataDir)
import qualified Foreign.Lua as Lua
--- | Adjust the stack index, assuming that @n@ new elements have been pushed on
--- the stack.
-adjustIndexBy :: StackIndex -> StackIndex -> StackIndex
-adjustIndexBy idx n =
- if idx < 0
- then idx - n
- else idx
-
-- | Get value behind key from table at given index.
-getTable :: (ToLuaStack a, FromLuaStack b) => StackIndex -> a -> Lua b
-getTable idx key = do
- push key
- rawget (idx `adjustIndexBy` 1)
+rawField :: FromLuaStack a => StackIndex -> String -> Lua a
+rawField idx key = do
+ absidx <- Lua.absindex idx
+ Lua.push key
+ Lua.rawget absidx
popValue
+-- | Add a value to the table at the top of the stack at a string-index.
+addField :: ToLuaStack a => String -> a -> Lua ()
+addField = addValue
+
-- | Add a key-value pair to the table at the top of the stack.
addValue :: (ToLuaStack a, ToLuaStack b) => a -> b -> Lua ()
addValue key value = do
- push key
- push value
- rawset (-3)
+ Lua.push key
+ Lua.push value
+ Lua.rawset (Lua.nthFromTop 3)
-- | Add a function to the table at the top of the stack, using the given name.
addFunction :: ToHaskellFunction a => String -> a -> Lua ()
@@ -88,22 +81,6 @@ addFunction name fn = do
Lua.wrapHaskellFunction
Lua.rawset (-3)
--- | Get value behind key from table at given index.
-getRawInt :: FromLuaStack a => StackIndex -> Int -> Lua a
-getRawInt idx key = do
- rawgeti idx key
- popValue
-
--- | Set numeric key/value in table at the given index
-setRawInt :: ToLuaStack a => StackIndex -> Int -> a -> Lua ()
-setRawInt idx key value = do
- push value
- rawseti (idx `adjustIndexBy` 1) key
-
--- | Set numeric key/value in table at the top of the stack.
-addRawInt :: ToLuaStack a => Int -> a -> Lua ()
-addRawInt = setRawInt (-1)
-
typeCheck :: StackIndex -> Lua.Type -> Lua ()
typeCheck idx expected = do
actual <- Lua.ltype idx
@@ -112,16 +89,11 @@ typeCheck idx expected = do
actName <- Lua.typename actual
Lua.throwLuaError $ "expected " ++ expName ++ " but got " ++ actName ++ "."
-raiseError :: ToLuaStack a => a -> Lua NumResults
-raiseError e = do
- Lua.push e
- fromIntegral <$> Lua.lerror
-
-- | Get, then pop the value at the top of the stack.
popValue :: FromLuaStack a => Lua a
popValue = do
resOrError <- Lua.peekEither (-1)
- pop 1
+ Lua.pop 1
case resOrError of
Left err -> Lua.throwLuaError err
Right x -> return x
@@ -136,11 +108,11 @@ instance PushViaCall (Lua ()) where
Lua.push fn
Lua.rawget Lua.registryindex
pushArgs
- call num 1
+ Lua.call num 1
instance (ToLuaStack a, PushViaCall b) => PushViaCall (a -> b) where
pushViaCall' fn pushArgs num x =
- pushViaCall' fn (pushArgs *> push x) (num + 1)
+ pushViaCall' fn (pushArgs *> Lua.push x) (num + 1)
-- | Push an value to the stack via a lua function. The lua function is called
-- with all arguments that are passed to this function and is expected to return
@@ -163,9 +135,9 @@ loadScriptFromDataDir datadir scriptFile = do
"Couldn't load '" ++ scriptFile ++ "'.\n" ++ msg
-- | Load a string and immediately perform a full garbage collection. This is
--- important to keep the program from hanging: If the program contained a call
--- to @require@, the a new loader function was created which then become
--- garbage. If that function is collected at an inopportune times, i.e. when the
+-- important to keep the program from hanging: If the program containes a call
+-- to @require@, then a new loader function is created which then becomes
+-- garbage. If that function is collected at an inopportune time, i.e. when the
-- Lua API is called via a function that doesn't allow calling back into Haskell
-- (getraw, setraw, …), then the function's finalizer, and the full program,
-- will hang.
@@ -182,8 +154,8 @@ dostring' script = do
-- metatable.
getTag :: StackIndex -> Lua String
getTag idx = do
- top <- Lua.gettop
- hasMT <- Lua.getmetatable idx
- push "tag"
- if hasMT then Lua.rawget (-2) else Lua.rawget (idx `adjustIndexBy` 1)
- peek Lua.stackTop `finally` Lua.settop top
+ -- push metatable or just the table
+ Lua.getmetatable idx >>= \hasMT -> when (not hasMT) (Lua.pushvalue idx)
+ Lua.push "tag"
+ Lua.rawget (Lua.nthFromTop 2)
+ Lua.peek Lua.stackTop `finally` Lua.pop 2