{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Lua.Module.Types
( pushModule
) where
import HsLua (LuaE, NumResults, Peeker, Pusher)
import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.ErrorConversion ()
import Text.Pandoc.Lua.Marshaling.AST
import Text.Pandoc.Lua.Util (addFunction)
import qualified HsLua as Lua
import qualified HsLua.Module.Version as Version
pushModule :: LuaE PandocError NumResults
pushModule :: LuaE PandocError NumResults
pushModule = do
LuaE PandocError ()
forall e. LuaE e ()
Lua.newtable
Name -> LuaE PandocError ()
forall e. Name -> LuaE e ()
Lua.pushName Name
"Version" LuaE PandocError () -> LuaE PandocError () -> LuaE PandocError ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Module PandocError -> LuaE PandocError ()
forall e. LuaError e => Module e -> LuaE e ()
Lua.pushModule Module PandocError
forall e. LuaError e => Module e
Version.documentedModule
LuaE PandocError () -> LuaE PandocError () -> LuaE PandocError ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StackIndex -> LuaE PandocError ()
forall e. LuaError e => StackIndex -> LuaE e ()
Lua.rawset (CInt -> StackIndex
Lua.nth CInt
3)
LuaE PandocError NumResults
pushCloneTable
StackIndex -> Name -> LuaE PandocError ()
forall e. LuaError e => StackIndex -> Name -> LuaE e ()
Lua.setfield (CInt -> StackIndex
Lua.nth CInt
2) Name
"clone"
NumResults -> LuaE PandocError NumResults
forall (m :: * -> *) a. Monad m => a -> m a
return NumResults
1
pushCloneTable :: LuaE PandocError NumResults
pushCloneTable :: LuaE PandocError NumResults
pushCloneTable = do
LuaE PandocError ()
forall e. LuaE e ()
Lua.newtable
String -> LuaE PandocError NumResults -> LuaE PandocError ()
forall e a. Exposable e a => String -> a -> LuaE e ()
addFunction String
"Attr" (LuaE PandocError NumResults -> LuaE PandocError ())
-> LuaE PandocError NumResults -> LuaE PandocError ()
forall a b. (a -> b) -> a -> b
$ Peeker PandocError Attr
-> Pusher PandocError Attr -> LuaE PandocError NumResults
forall a.
Peeker PandocError a
-> Pusher PandocError a -> LuaE PandocError NumResults
cloneWith Peeker PandocError Attr
forall e. LuaError e => Peeker e Attr
peekAttr Pusher PandocError Attr
forall e. LuaError e => Pusher e Attr
pushAttr
String -> LuaE PandocError NumResults -> LuaE PandocError ()
forall e a. Exposable e a => String -> a -> LuaE e ()
addFunction String
"Block" (LuaE PandocError NumResults -> LuaE PandocError ())
-> LuaE PandocError NumResults -> LuaE PandocError ()
forall a b. (a -> b) -> a -> b
$ Peeker PandocError Block
-> Pusher PandocError Block -> LuaE PandocError NumResults
forall a.
Peeker PandocError a
-> Pusher PandocError a -> LuaE PandocError NumResults
cloneWith Peeker PandocError Block
forall e. LuaError e => Peeker e Block
peekBlock Pusher PandocError Block
forall e. LuaError e => Block -> LuaE e ()
pushBlock
String -> LuaE PandocError NumResults -> LuaE PandocError ()
forall e a. Exposable e a => String -> a -> LuaE e ()
addFunction String
"Citation" (LuaE PandocError NumResults -> LuaE PandocError ())
-> LuaE PandocError NumResults -> LuaE PandocError ()
forall a b. (a -> b) -> a -> b
$ Peeker PandocError Citation
-> Pusher PandocError Citation -> LuaE PandocError NumResults
forall a.
Peeker PandocError a
-> Pusher PandocError a -> LuaE PandocError NumResults
cloneWith Peeker PandocError Citation
forall e. LuaError e => Peeker e Citation
peekCitation Pusher PandocError Citation
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
Lua.push
String -> LuaE PandocError NumResults -> LuaE PandocError ()
forall e a. Exposable e a => String -> a -> LuaE e ()
addFunction String
"Inline" (LuaE PandocError NumResults -> LuaE PandocError ())
-> LuaE PandocError NumResults -> LuaE PandocError ()
forall a b. (a -> b) -> a -> b
$ Peeker PandocError Inline
-> Pusher PandocError Inline -> LuaE PandocError NumResults
forall a.
Peeker PandocError a
-> Pusher PandocError a -> LuaE PandocError NumResults
cloneWith Peeker PandocError Inline
forall e. LuaError e => Peeker e Inline
peekInline Pusher PandocError Inline
forall e. LuaError e => Inline -> LuaE e ()
pushInline
String -> LuaE PandocError NumResults -> LuaE PandocError ()
forall e a. Exposable e a => String -> a -> LuaE e ()
addFunction String
"Meta" (LuaE PandocError NumResults -> LuaE PandocError ())
-> LuaE PandocError NumResults -> LuaE PandocError ()
forall a b. (a -> b) -> a -> b
$ Peeker PandocError Meta
-> Pusher PandocError Meta -> LuaE PandocError NumResults
forall a.
Peeker PandocError a
-> Pusher PandocError a -> LuaE PandocError NumResults
cloneWith Peeker PandocError Meta
forall e. LuaError e => Peeker e Meta
peekMeta Pusher PandocError Meta
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
Lua.push
String -> LuaE PandocError NumResults -> LuaE PandocError ()
forall e a. Exposable e a => String -> a -> LuaE e ()
addFunction String
"MetaValue" (LuaE PandocError NumResults -> LuaE PandocError ())
-> LuaE PandocError NumResults -> LuaE PandocError ()
forall a b. (a -> b) -> a -> b
$ Peeker PandocError MetaValue
-> Pusher PandocError MetaValue -> LuaE PandocError NumResults
forall a.
Peeker PandocError a
-> Pusher PandocError a -> LuaE PandocError NumResults
cloneWith Peeker PandocError MetaValue
forall e. LuaError e => Peeker e MetaValue
peekMetaValue Pusher PandocError MetaValue
forall e. LuaError e => MetaValue -> LuaE e ()
pushMetaValue
String -> LuaE PandocError NumResults -> LuaE PandocError ()
forall e a. Exposable e a => String -> a -> LuaE e ()
addFunction String
"ListAttributes" (LuaE PandocError NumResults -> LuaE PandocError ())
-> LuaE PandocError NumResults -> LuaE PandocError ()
forall a b. (a -> b) -> a -> b
$ Peeker PandocError ListAttributes
-> Pusher PandocError ListAttributes -> LuaE PandocError NumResults
forall a.
Peeker PandocError a
-> Pusher PandocError a -> LuaE PandocError NumResults
cloneWith Peeker PandocError ListAttributes
forall e. LuaError e => Peeker e ListAttributes
peekListAttributes Pusher PandocError ListAttributes
forall e. LuaError e => ListAttributes -> LuaE e ()
pushListAttributes
String -> LuaE PandocError NumResults -> LuaE PandocError ()
forall e a. Exposable e a => String -> a -> LuaE e ()
addFunction String
"Pandoc" (LuaE PandocError NumResults -> LuaE PandocError ())
-> LuaE PandocError NumResults -> LuaE PandocError ()
forall a b. (a -> b) -> a -> b
$ Peeker PandocError Pandoc
-> Pusher PandocError Pandoc -> LuaE PandocError NumResults
forall a.
Peeker PandocError a
-> Pusher PandocError a -> LuaE PandocError NumResults
cloneWith Peeker PandocError Pandoc
forall e. LuaError e => Peeker e Pandoc
peekPandoc Pusher PandocError Pandoc
forall e. LuaError e => Pusher e Pandoc
pushPandoc
NumResults -> LuaE PandocError NumResults
forall (m :: * -> *) a. Monad m => a -> m a
return NumResults
1
cloneWith :: Peeker PandocError a
-> Pusher PandocError a
-> LuaE PandocError NumResults
cloneWith :: Peeker PandocError a
-> Pusher PandocError a -> LuaE PandocError NumResults
cloneWith Peeker PandocError a
peeker Pusher PandocError a
pusher = do
a
x <- Peek PandocError a -> LuaE PandocError a
forall e a. LuaError e => Peek e a -> LuaE e a
Lua.forcePeek (Peek PandocError a -> LuaE PandocError a)
-> Peek PandocError a -> LuaE PandocError a
forall a b. (a -> b) -> a -> b
$ Peeker PandocError a
peeker (CInt -> StackIndex
Lua.nthBottom CInt
1)
Pusher PandocError a
pusher a
x
NumResults -> LuaE PandocError NumResults
forall (m :: * -> *) a. Monad m => a -> m a
return (CInt -> NumResults
Lua.NumResults CInt
1)