Lua: move getTag from StackInstances to Util
Change: minor
This commit is contained in:
parent
f0671bf4c7
commit
2e0bb77334
2 changed files with 17 additions and 13 deletions
|
@ -42,8 +42,7 @@ import Foreign.Lua (FromLuaStack (peek), Lua, LuaInteger, LuaNumber, StackIndex,
|
||||||
ToLuaStack (push), Type (..), throwLuaError, tryLua)
|
ToLuaStack (push), Type (..), throwLuaError, tryLua)
|
||||||
import Text.Pandoc.Definition
|
import Text.Pandoc.Definition
|
||||||
import Text.Pandoc.Extensions (Extensions)
|
import Text.Pandoc.Extensions (Extensions)
|
||||||
import Text.Pandoc.Lua.Util (adjustIndexBy, getTable, pushViaConstructor,
|
import Text.Pandoc.Lua.Util (getTable, getTag, pushViaConstructor, typeCheck)
|
||||||
typeCheck)
|
|
||||||
import Text.Pandoc.Options (ReaderOptions (..), TrackChanges)
|
import Text.Pandoc.Options (ReaderOptions (..), TrackChanges)
|
||||||
import Text.Pandoc.Shared (Element (Blk, Sec), safeRead)
|
import Text.Pandoc.Shared (Element (Blk, Sec), safeRead)
|
||||||
|
|
||||||
|
@ -300,14 +299,6 @@ peekInline idx = defineHowTo "get Inline value" $ do
|
||||||
elementContent :: FromLuaStack a => Lua a
|
elementContent :: FromLuaStack a => Lua a
|
||||||
elementContent = getTable idx "c"
|
elementContent = getTable idx "c"
|
||||||
|
|
||||||
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
|
|
||||||
|
|
||||||
withAttr :: (Attr -> a -> b) -> (LuaAttr, a) -> b
|
withAttr :: (Attr -> a -> b) -> (LuaAttr, a) -> b
|
||||||
withAttr f (attributes, x) = f (fromLuaAttr attributes) x
|
withAttr f (attributes, x) = f (fromLuaAttr attributes) x
|
||||||
|
|
||||||
|
|
|
@ -29,7 +29,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
||||||
Lua utility functions.
|
Lua utility functions.
|
||||||
-}
|
-}
|
||||||
module Text.Pandoc.Lua.Util
|
module Text.Pandoc.Lua.Util
|
||||||
( adjustIndexBy
|
( getTag
|
||||||
, getTable
|
, getTable
|
||||||
, addValue
|
, addValue
|
||||||
, addFunction
|
, addFunction
|
||||||
|
@ -47,6 +47,7 @@ module Text.Pandoc.Lua.Util
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Monad (when)
|
import Control.Monad (when)
|
||||||
|
import Control.Monad.Catch (finally)
|
||||||
import Data.ByteString.Char8 (unpack)
|
import Data.ByteString.Char8 (unpack)
|
||||||
import Foreign.Lua (FromLuaStack (..), NumResults, Lua, NumArgs, StackIndex,
|
import Foreign.Lua (FromLuaStack (..), NumResults, Lua, NumArgs, StackIndex,
|
||||||
ToLuaStack (..), ToHaskellFunction, getglobal')
|
ToLuaStack (..), ToHaskellFunction, getglobal')
|
||||||
|
@ -163,11 +164,23 @@ loadScriptFromDataDir datadir scriptFile = do
|
||||||
-- to @require@, the a new loader function was created which then become
|
-- 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
|
-- garbage. If that function is collected at an inopportune times, i.e. when the
|
||||||
-- Lua API is called via a function that doesn't allow calling back into Haskell
|
-- Lua API is called via a function that doesn't allow calling back into Haskell
|
||||||
-- (getraw, setraw, …). The function's finalizer, and the full program, hangs
|
-- (getraw, setraw, …), then the function's finalizer, and the full program,
|
||||||
-- when that happens.
|
-- will hang.
|
||||||
dostring' :: String -> Lua Status
|
dostring' :: String -> Lua Status
|
||||||
dostring' script = do
|
dostring' script = do
|
||||||
loadRes <- Lua.loadstring script
|
loadRes <- Lua.loadstring script
|
||||||
if loadRes == Lua.OK
|
if loadRes == Lua.OK
|
||||||
then Lua.pcall 0 1 Nothing <* Lua.gc Lua.GCCOLLECT 0
|
then Lua.pcall 0 1 Nothing <* Lua.gc Lua.GCCOLLECT 0
|
||||||
else return loadRes
|
else return loadRes
|
||||||
|
|
||||||
|
-- | Get the tag of a value. This is an optimized and specialized version of
|
||||||
|
-- @Lua.getfield idx "tag"@. It only checks for the field on the table at index
|
||||||
|
-- @idx@ and on its metatable, also ignoring any @__index@ value on the
|
||||||
|
-- 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
|
||||||
|
|
Loading…
Reference in a new issue