aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Lua')
-rw-r--r--src/Text/Pandoc/Lua/Module/Utils.hs41
-rw-r--r--src/Text/Pandoc/Lua/Util.hs16
2 files changed, 47 insertions, 10 deletions
diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs
index 496fdbc0a..3a3727355 100644
--- a/src/Text/Pandoc/Lua/Module/Utils.hs
+++ b/src/Text/Pandoc/Lua/Module/Utils.hs
@@ -29,22 +29,51 @@ module Text.Pandoc.Lua.Module.Utils
( pushModule
) where
-import Data.Digest.Pure.SHA (sha1, showDigest)
-import Foreign.Lua (Lua, NumResults)
+import Control.Applicative ((<|>))
+import Foreign.Lua (FromLuaStack, Lua, NumResults)
+import Text.Pandoc.Definition (Pandoc, Meta, Block, Inline)
import Text.Pandoc.Lua.StackInstances ()
import Text.Pandoc.Lua.Util (addFunction)
+import qualified Data.Digest.Pure.SHA as SHA
import qualified Data.ByteString.Lazy as BSL
import qualified Foreign.Lua as Lua
+import qualified Text.Pandoc.Shared as Shared
-- | Push the "pandoc.utils" module to the lua stack.
pushModule :: Lua NumResults
pushModule = do
Lua.newtable
- addFunction "sha1" sha1HashFn
+ addFunction "sha1" sha1
+ addFunction "stringify" stringify
return 1
-- | Calculate the hash of the given contents.
-sha1HashFn :: BSL.ByteString
- -> Lua String
-sha1HashFn = return . showDigest . sha1
+sha1 :: BSL.ByteString
+ -> Lua String
+sha1 = return . SHA.showDigest . SHA.sha1
+
+stringify :: AstElement -> Lua String
+stringify el = return $ case el of
+ PandocElement pd -> Shared.stringify pd
+ InlineElement i -> Shared.stringify i
+ BlockElement b -> Shared.stringify b
+ MetaElement m -> Shared.stringify m
+
+data AstElement
+ = PandocElement Pandoc
+ | MetaElement Meta
+ | BlockElement Block
+ | InlineElement Inline
+ deriving (Show)
+
+instance FromLuaStack AstElement where
+ peek idx = do
+ res <- Lua.tryLua $ (PandocElement <$> Lua.peek idx)
+ <|> (InlineElement <$> Lua.peek idx)
+ <|> (BlockElement <$> Lua.peek idx)
+ <|> (MetaElement <$> Lua.peek idx)
+ case res of
+ Right x -> return x
+ Left _ -> Lua.throwLuaError
+ "Expected an AST element, but could not parse value as such."
diff --git a/src/Text/Pandoc/Lua/Util.hs b/src/Text/Pandoc/Lua/Util.hs
index e688ad255..28d09d339 100644
--- a/src/Text/Pandoc/Lua/Util.hs
+++ b/src/Text/Pandoc/Lua/Util.hs
@@ -67,7 +67,7 @@ getTable :: (ToLuaStack a, FromLuaStack b) => StackIndex -> a -> Lua b
getTable idx key = do
push key
rawget (idx `adjustIndexBy` 1)
- peek (-1) <* pop 1
+ popValue
-- | Add a key-value pair to the table at the top of the stack.
addValue :: (ToLuaStack a, ToLuaStack b) => a -> b -> Lua ()
@@ -86,10 +86,9 @@ addFunction name fn = do
-- | Get value behind key from table at given index.
getRawInt :: FromLuaStack a => StackIndex -> Int -> Lua a
-getRawInt idx key =
+getRawInt idx key = do
rawgeti idx key
- *> peek (-1)
- <* pop 1
+ popValue
-- | Set numeric key/value in table at the given index
setRawInt :: ToLuaStack a => StackIndex -> Int -> a -> Lua ()
@@ -106,6 +105,15 @@ 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
+ case resOrError of
+ Left err -> Lua.throwLuaError err
+ Right x -> return x
+
-- | Newtype wrapper intended to be used for optional Lua values. Nesting this
-- type is strongly discouraged and will likely lead to a wrong result.
newtype OrNil a = OrNil { toMaybe :: Maybe a }