@@ -28,11 +28,13 @@ import Data.Proxy (Proxy (Proxy))
2828import Data.Text.Encoding.Error (UnicodeException )
2929import HsLua
3030import System.Exit (ExitCode (.. ))
31+ import Text.Pandoc.Class (PandocMonad (putCommonState ))
3132import Text.Pandoc.Definition
3233import Text.Pandoc.Error (PandocError (.. ))
3334import Text.Pandoc.Format (parseFlavoredFormat )
3435import Text.Pandoc.Lua.Orphans ()
3536import Text.Pandoc.Lua.Marshal.AST
37+ import Text.Pandoc.Lua.Marshal.CommonState (peekCommonStateFromTable )
3638import Text.Pandoc.Lua.Marshal.Format (peekFlavoredFormat )
3739import Text.Pandoc.Lua.Marshal.Filter (peekFilter )
3840import Text.Pandoc.Lua.Marshal.ReaderOptions ( peekReaderOptions
@@ -194,7 +196,28 @@ stringConstants =
194196
195197functions :: [DocumentedFunction PandocError ]
196198functions =
197- [ defun " pipe"
199+ [ defun " init"
200+ ### (\ newCommonState -> do
201+ getfield registryindex " PANDOC_STATE" >>= \ case
202+ TypeNil -> True <$ unPandocLua (putCommonState newCommonState)
203+ _ -> pure False )
204+ <#> parameter peekCommonStateFromTable " table" " props"
205+ " pandoc state properties"
206+ =#> boolResult " Whether the initialization succeeded."
207+ #? T. unlines
208+ [ " Initialize the pandoc state. This function should be called at most"
209+ , " once, as further invocations won't have any effect. The state is set"
210+ , " only if it hasn't been initialized yet."
211+ , " "
212+ , " Note that the state is always already initialized in filters and in"
213+ , " custom readers or writers. The function is most useful in standalone"
214+ , " pandoc Lua programs."
215+ , " "
216+ , " Returns `true` if the initialization succeeded, and `false` if the Lua"
217+ , " state had been initialized before."
218+ ]
219+
220+ , defun " pipe"
198221 ### (\ command args input -> do
199222 (ec, output) <- Lua. liftIO $ pipeProcess Nothing command args input
200223 `catch` (throwM . PandocIOError " pipe" )
0 commit comments