Skip to content

Commit 5d2cb92

Browse files
committed
[WIP] Lua: add function pandoc.init
1 parent 042eb17 commit 5d2cb92

File tree

9 files changed

+85
-12
lines changed

9 files changed

+85
-12
lines changed

pandoc-lua-engine/src/Text/Pandoc/Lua.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,12 +17,14 @@ module Text.Pandoc.Lua
1717
, setGlobals
1818
, runLua
1919
, runLuaNoEnv
20+
, userInit
2021
-- * Engine
2122
, getEngine
2223
) where
2324

2425
import Text.Pandoc.Lua.Custom (loadCustom)
2526
import Text.Pandoc.Lua.Engine (getEngine, applyFilter)
2627
import Text.Pandoc.Lua.Global (Global (..), setGlobals)
28+
import Text.Pandoc.Lua.Init (userInit)
2729
import Text.Pandoc.Lua.Run (runLua, runLuaNoEnv)
2830
import Text.Pandoc.Lua.Orphans ()

pandoc-lua-engine/src/Text/Pandoc/Lua/Custom.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,7 @@ import HsLua as Lua hiding (Operation (Div))
1818
import Text.Pandoc.Class (PandocMonad, findFileWithDataFallback)
1919
import Text.Pandoc.Error (PandocError)
2020
import Text.Pandoc.Lua.Global (Global (..), setGlobals)
21+
import Text.Pandoc.Lua.Init (userInit)
2122
import Text.Pandoc.Lua.Marshal.Format (peekExtensionsConfig)
2223
import Text.Pandoc.Lua.Marshal.Pandoc (peekPandoc)
2324
import Text.Pandoc.Lua.Marshal.WriterOptions (pushWriterOptions)
@@ -34,10 +35,12 @@ import qualified Text.Pandoc.Class as PandocMonad
3435
loadCustom :: (PandocMonad m, MonadIO m)
3536
=> FilePath -> m (CustomComponents m)
3637
loadCustom luaFile = do
38+
initialState <- PandocMonad.getCommonState
3739
luaState <- liftIO newGCManagedState
3840
luaFile' <- fromMaybe luaFile <$>
3941
findFileWithDataFallback "custom" luaFile
4042
either throw pure <=< runLuaWith luaState $ do
43+
userInit initialState
4144
let globals = [ PANDOC_SCRIPT_FILE luaFile' ]
4245
setGlobals globals
4346
dofileTrace (Just luaFile') >>= \case

pandoc-lua-engine/src/Text/Pandoc/Lua/Engine.hs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,15 +17,16 @@ import Control.Exception (throw)
1717
import Control.Monad ((>=>))
1818
import Control.Monad.IO.Class (MonadIO (liftIO))
1919
import HsLua.Core (getglobal, openlibs, run, top, tostring)
20-
import Text.Pandoc.Class (PandocMonad)
20+
import Text.Pandoc.Class (PandocMonad (getCommonState))
2121
import Text.Pandoc.Definition (Pandoc)
2222
import Text.Pandoc.Filter (Environment (..))
2323
import Text.Pandoc.Error (PandocError (PandocFilterError, PandocLuaError))
2424
import Text.Pandoc.Lua.Custom (loadCustom)
2525
import Text.Pandoc.Lua.Filter (runFilterFile)
2626
import Text.Pandoc.Lua.Global (Global (..), setGlobals)
27-
import Text.Pandoc.Lua.Run (runLua)
27+
import Text.Pandoc.Lua.Init (userInit)
2828
import Text.Pandoc.Lua.Orphans ()
29+
import Text.Pandoc.Lua.Run (runLua)
2930
import Text.Pandoc.Scripting (ScriptingEngine (..))
3031
import qualified Text.Pandoc.UTF8 as UTF8
3132
import qualified Data.Text as T
@@ -60,7 +61,9 @@ applyFilter fenv args fp doc = do
6061
, PANDOC_WRITER_OPTIONS (envWriterOptions fenv)
6162
, PANDOC_SCRIPT_FILE fp
6263
]
64+
st <- getCommonState
6365
runLua >=> forceResult fp $ do
66+
userInit st
6467
setGlobals globals
6568
runFilterFile fp doc
6669

pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ module Text.Pandoc.Lua.Init
1717
import Control.Monad (when)
1818
import Control.Monad.Catch (throwM)
1919
import HsLua as Lua hiding (status)
20-
import Text.Pandoc.Class (report)
20+
import Text.Pandoc.Class (PandocMonad (putCommonState), CommonState, report)
2121
import Text.Pandoc.Data (readDataFile)
2222
import Text.Pandoc.Error (PandocError (PandocLuaError))
2323
import Text.Pandoc.Logging (LogMessage (ScriptingWarning))
@@ -34,11 +34,12 @@ initLua = do
3434
liftPandocLua Lua.openlibs
3535
setWarnFunction
3636
initModules
37-
liftPandocLua userInit
3837

3938
-- | User-controlled initialization, e.g., running the user's init script.
40-
userInit :: LuaE PandocError ()
41-
userInit = runInitScript
39+
userInit :: CommonState -> LuaE PandocError ()
40+
userInit st = do
41+
unPandocLua $ putCommonState st
42+
runInitScript
4243

4344
-- | Run the @init.lua@ data file as a Lua script.
4445
runInitScript :: LuaE PandocError ()

pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Chunks.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
{-# LANGUAGE OverloadedStrings #-}
33
{- |
44
Module : Text.Pandoc.Lua.Marshal.Chunks
5-
Copyright : © 2022 Albert Krewinkel
5+
Copyright : © 2022-2024 Albert Krewinkel
66
License : GPL-2.0-or-later
77
Maintainer : Albert Krewinkel <[email protected]>
88

pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/CommonState.hs

Lines changed: 31 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE LambdaCase #-}
12
{-# LANGUAGE OverloadedStrings #-}
23
{- |
34
Module : Text.Pandoc.Lua.Marshal.CommonState
@@ -13,8 +14,10 @@ module Text.Pandoc.Lua.Marshal.CommonState
1314
( typeCommonState
1415
, peekCommonState
1516
, pushCommonState
17+
, peekCommonStateFromTable
1618
) where
1719

20+
import Data.Default (def)
1821
import HsLua
1922
import Text.Pandoc.Class (CommonState (..))
2023
import Text.Pandoc.Lua.Marshal.List (pushPandocList)
@@ -57,3 +60,31 @@ peekCommonState = peekUD typeCommonState
5760

5861
pushCommonState :: LuaError e => Pusher e CommonState
5962
pushCommonState = pushUD typeCommonState
63+
64+
peekCommonStateFromTable :: LuaError e => Peeker e CommonState
65+
peekCommonStateFromTable idx = do
66+
absidx <- liftLua $ absindex idx
67+
let setnext st = do
68+
liftLua (next absidx) >>= \case
69+
False -> pure st
70+
True -> do
71+
prop <- peekName (nth 2)
72+
case lookup prop setters of
73+
Just setter -> setnext =<< setter top st `lastly` pop 1
74+
Nothing -> failPeek ("Unknown field " <> fromName prop)
75+
`lastly` pop 1
76+
liftLua pushnil
77+
setnext def
78+
79+
setters :: LuaError e
80+
=> [ (Name, StackIndex -> CommonState -> Peek e CommonState)]
81+
setters =
82+
[ ("input_files", mkS (peekList peekString) (\st x -> st{stInputFiles = x}))
83+
, ("output_file", mkS (peekNilOr peekString) (\st x -> st{stOutputFile = x}))
84+
, ("request_headers", mkS (peekList (peekPair peekText peekText))
85+
(\st x -> st{ stRequestHeaders = x }))
86+
, ("user_data_dir", mkS (peekNilOr peekString) (\st x -> st{stUserDataDir = x}))
87+
, ("trace", mkS peekBool (\st x -> st{stTrace = x}))
88+
]
89+
where
90+
mkS peekX setValue idx' st = setValue st <$> peekX idx'

pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs

Lines changed: 24 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -28,11 +28,13 @@ import Data.Proxy (Proxy (Proxy))
2828
import Data.Text.Encoding.Error (UnicodeException)
2929
import HsLua
3030
import System.Exit (ExitCode (..))
31+
import Text.Pandoc.Class (PandocMonad(putCommonState))
3132
import Text.Pandoc.Definition
3233
import Text.Pandoc.Error (PandocError (..))
3334
import Text.Pandoc.Format (parseFlavoredFormat)
3435
import Text.Pandoc.Lua.Orphans ()
3536
import Text.Pandoc.Lua.Marshal.AST
37+
import Text.Pandoc.Lua.Marshal.CommonState (peekCommonStateFromTable)
3638
import Text.Pandoc.Lua.Marshal.Format (peekFlavoredFormat)
3739
import Text.Pandoc.Lua.Marshal.Filter (peekFilter)
3840
import Text.Pandoc.Lua.Marshal.ReaderOptions ( peekReaderOptions
@@ -194,7 +196,28 @@ stringConstants =
194196

195197
functions :: [DocumentedFunction PandocError]
196198
functions =
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")

pandoc-lua-engine/src/Text/Pandoc/Lua/PandocLua.hs

Lines changed: 10 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
{-# LANGUAGE FlexibleContexts #-}
33
{-# LANGUAGE FlexibleInstances #-}
44
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
5+
{-# LANGUAGE LambdaCase #-}
56
{-# LANGUAGE MultiParamTypeClasses #-}
67
{-# LANGUAGE OverloadedStrings #-}
78
{-# OPTIONS_GHC -fno-warn-orphans #-}
@@ -11,7 +12,7 @@
1112
License : GPL-2.0-or-later
1213
Maintainer : Albert Krewinkel <[email protected]>
1314
14-
PandocMonad instance which allows execution of Lua operations and which
15+
PandocMonad instance that allows execution of Lua operations; it
1516
uses Lua to handle state.
1617
-}
1718
module Text.Pandoc.Lua.PandocLua
@@ -22,6 +23,7 @@ module Text.Pandoc.Lua.PandocLua
2223
import Control.Monad.Catch (MonadCatch, MonadMask, MonadThrow)
2324
import Control.Monad.Except (MonadError (catchError, throwError))
2425
import Control.Monad.IO.Class (MonadIO)
26+
import Data.Default (def)
2527
import HsLua as Lua
2628
import Text.Pandoc.Class (PandocMonad (..))
2729
import Text.Pandoc.Error (PandocError (..))
@@ -77,8 +79,13 @@ instance PandocMonad PandocLua where
7779
getModificationTime = IO.getModificationTime
7880

7981
getCommonState = PandocLua $ do
80-
Lua.getfield registryindex "PANDOC_STATE"
81-
forcePeek $ peekCommonState Lua.top `lastly` pop 1
82+
-- initialize with the default value if is hadn't been initialized yet.
83+
Lua.getfield registryindex "PANDOC_STATE" >>= \case
84+
TypeNil -> do
85+
pop 1 -- pop nil
86+
unPandocLua $ putCommonState def
87+
return def
88+
_ -> forcePeek $ peekCommonState Lua.top `lastly` pop 1
8289
putCommonState cst = PandocLua $ do
8390
pushCommonState cst
8491
Lua.pushvalue Lua.top

pandoc-lua-engine/test/Tests/Lua.hs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,12 +25,13 @@ import Text.Pandoc.Builder (bulletList, definitionList, displayMath, divWith,
2525
singleQuoted, space, str, strong,
2626
HasMeta (setMeta))
2727
import Text.Pandoc.Class ( CommonState (stVerbosity)
28+
, PandocMonad (getCommonState)
2829
, modifyCommonState, runIOorExplode, setUserDataDir)
2930
import Text.Pandoc.Definition (Attr, Block (BlockQuote, Div, Para), Pandoc,
3031
Inline (Emph, Str), pandocTypesVersion)
3132
import Text.Pandoc.Error (PandocError (PandocLuaError))
3233
import Text.Pandoc.Logging (Verbosity (ERROR))
33-
import Text.Pandoc.Lua (Global (..), applyFilter, runLua, setGlobals)
34+
import Text.Pandoc.Lua (Global (..), applyFilter, runLua, setGlobals, userInit)
3435
import Text.Pandoc.Options (def)
3536
import Text.Pandoc.Version (pandocVersionText)
3637

@@ -243,7 +244,9 @@ runLuaTest op = runIOorExplode $ do
243244
-- Disable printing of warnings on stderr: some tests will generate
244245
-- warnings, we don't want to see those messages.
245246
modifyCommonState $ \st -> st { stVerbosity = ERROR }
247+
st <- getCommonState
246248
res <- runLua $ do
249+
userInit st
247250
setGlobals [ PANDOC_WRITER_OPTIONS def ]
248251
op
249252
case res of

0 commit comments

Comments
 (0)