Skip to content

Commit d9748ef

Browse files
committed
Lua: move Lua module setup to separate Haskell module
1 parent 9af5b1c commit d9748ef

File tree

3 files changed

+182
-151
lines changed

3 files changed

+182
-151
lines changed

pandoc-lua-engine/pandoc-lua-engine.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -71,6 +71,7 @@ library
7171
, Text.Pandoc.Lua.Filter
7272
, Text.Pandoc.Lua.Global
7373
, Text.Pandoc.Lua.Init
74+
, Text.Pandoc.Lua.Module
7475
, Text.Pandoc.Lua.Marshal.Chunks
7576
, Text.Pandoc.Lua.Marshal.CommonState
7677
, Text.Pandoc.Lua.Marshal.Context

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

Lines changed: 21 additions & 151 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
{-# LANGUAGE OverloadedStrings #-}
33
{-# LANGUAGE RankNTypes #-}
44
{- |
5-
Module : Text.Pandoc.Lua
5+
Module : Text.Pandoc.Lua.Init
66
Copyright : Copyright © 2017-2024 Albert Krewinkel
77
License : GNU GPL, version 2 or above
88
@@ -17,41 +17,19 @@ module Text.Pandoc.Lua.Init
1717
, runLuaWith
1818
) where
1919

20-
import Control.Monad (forM, forM_, when)
20+
import Control.Monad (when)
2121
import Control.Monad.Catch (throwM, try)
2222
import Control.Monad.Trans (MonadIO (..))
23-
import Data.Maybe (catMaybes)
24-
import Data.Version (makeVersion)
2523
import HsLua as Lua hiding (status, try)
2624
import Text.Pandoc.Class (PandocMonad (..), report)
2725
import Text.Pandoc.Data (readDataFile)
2826
import Text.Pandoc.Error (PandocError (PandocLuaError))
2927
import Text.Pandoc.Logging (LogMessage (ScriptingWarning))
3028
import Text.Pandoc.Lua.Global (Global (..), setGlobals)
31-
import Text.Pandoc.Lua.Marshal.List (pushPandocList, pushListModule)
29+
import Text.Pandoc.Lua.Module (initModules)
3230
import Text.Pandoc.Lua.PandocLua (PandocLua (..), liftPandocLua)
3331
import Text.Pandoc.Lua.SourcePos (luaSourcePos)
34-
import qualified Data.ByteString.Char8 as Char8
3532
import qualified Data.Text as T
36-
import qualified Lua.LPeg as LPeg
37-
import qualified HsLua.Aeson
38-
import qualified HsLua.Module.DocLayout as Module.Layout
39-
import qualified HsLua.Module.Path as Module.Path
40-
import qualified HsLua.Module.Zip as Module.Zip
41-
import qualified Text.Pandoc.Lua.Module.CLI as Pandoc.CLI
42-
import qualified Text.Pandoc.Lua.Module.Format as Pandoc.Format
43-
import qualified Text.Pandoc.Lua.Module.Image as Pandoc.Image
44-
import qualified Text.Pandoc.Lua.Module.JSON as Pandoc.JSON
45-
import qualified Text.Pandoc.Lua.Module.Log as Pandoc.Log
46-
import qualified Text.Pandoc.Lua.Module.MediaBag as Pandoc.MediaBag
47-
import qualified Text.Pandoc.Lua.Module.Pandoc as Module.Pandoc
48-
import qualified Text.Pandoc.Lua.Module.Scaffolding as Pandoc.Scaffolding
49-
import qualified Text.Pandoc.Lua.Module.Structure as Pandoc.Structure
50-
import qualified Text.Pandoc.Lua.Module.System as Pandoc.System
51-
import qualified Text.Pandoc.Lua.Module.Template as Pandoc.Template
52-
import qualified Text.Pandoc.Lua.Module.Text as Pandoc.Text
53-
import qualified Text.Pandoc.Lua.Module.Types as Pandoc.Types
54-
import qualified Text.Pandoc.Lua.Module.Utils as Pandoc.Utils
5533
import qualified Text.Pandoc.UTF8 as UTF8
5634

5735
-- | Run the Lua interpreter, using pandoc's default way of environment
@@ -83,137 +61,29 @@ runLuaNoEnv action = do
8361
initLuaState
8462
liftPandocLua action
8563

86-
-- | Modules that are loaded at startup and assigned to fields in the
87-
-- pandoc module.
88-
--
89-
-- Note that @pandoc.List@ is not included here for technical reasons;
90-
-- it must be handled separately.
91-
loadedModules :: [Module PandocError]
92-
loadedModules =
93-
[ Pandoc.CLI.documentedModule
94-
, Pandoc.Format.documentedModule
95-
, Pandoc.Image.documentedModule
96-
, Pandoc.JSON.documentedModule
97-
, Pandoc.Log.documentedModule
98-
, Pandoc.MediaBag.documentedModule
99-
, Pandoc.Scaffolding.documentedModule
100-
, Pandoc.Structure.documentedModule
101-
, Pandoc.System.documentedModule
102-
, Pandoc.Template.documentedModule
103-
, Pandoc.Text.documentedModule
104-
, Pandoc.Types.documentedModule
105-
, Pandoc.Utils.documentedModule
106-
, Module.Layout.documentedModule { moduleName = "pandoc.layout" }
107-
`allSince` [2,18]
108-
, Module.Path.documentedModule { moduleName = "pandoc.path" }
109-
`allSince` [2,12]
110-
, Module.Zip.documentedModule { moduleName = "pandoc.zip" }
111-
`allSince` [3,0]
112-
]
113-
where
114-
allSince mdl version = mdl
115-
{ moduleFunctions = map (`since` makeVersion version) $ moduleFunctions mdl
116-
}
117-
11864
-- | Initialize the lua state with all required values
11965
initLuaState :: PandocLua ()
12066
initLuaState = do
12167
liftPandocLua Lua.openlibs
12268
setWarnFunction
123-
initPandocModule
124-
initJsonMetatable
125-
installLpegSearcher
126-
setGlobalModules
127-
loadInitScript "init.lua"
128-
where
129-
initPandocModule :: PandocLua ()
130-
initPandocModule = liftPandocLua $ do
131-
-- Push module table
132-
registerModule Module.Pandoc.documentedModule
133-
-- load modules and add them to the `pandoc` module table.
134-
forM_ loadedModules $ \mdl -> do
135-
registerModule mdl
136-
-- pandoc.text must be require-able as 'text' for backwards compat.
137-
when (moduleName mdl == "pandoc.text") $ do
138-
getfield registryindex loaded
139-
pushvalue (nth 2)
140-
setfield (nth 2) "text"
141-
pop 1 -- _LOADED
142-
-- Shorten name, drop everything before the first dot (if any).
143-
let fieldname (Name mdlname) = Name .
144-
maybe mdlname snd . Char8.uncons . snd $
145-
Char8.break (== '.') mdlname
146-
Lua.setfield (nth 2) (fieldname $ moduleName mdl)
147-
-- pandoc.List is low-level and must be opened differently.
148-
requirehs "pandoc.List" (const pushListModule)
149-
setfield (nth 2) "List"
150-
-- assign module to global variable
151-
Lua.setglobal "pandoc"
152-
153-
loadInitScript :: FilePath -> PandocLua ()
154-
loadInitScript scriptFile = do
155-
script <- readDataFile scriptFile
156-
status <- liftPandocLua $ Lua.dostring script
157-
when (status /= Lua.OK) . liftPandocLua $ do
158-
err <- popException
159-
let prefix = "Couldn't load '" <> T.pack scriptFile <> "':\n"
160-
throwM . PandocLuaError . (prefix <>) $ case err of
161-
PandocLuaError msg -> msg
162-
_ -> T.pack $ show err
163-
164-
setGlobalModules :: PandocLua ()
165-
setGlobalModules = liftPandocLua $ do
166-
let globalModules =
167-
[ ("lpeg", LPeg.luaopen_lpeg_ptr) -- must be loaded first
168-
, ("re", LPeg.luaopen_re_ptr) -- re depends on lpeg
169-
]
170-
loadedBuiltInModules <- fmap catMaybes . forM globalModules $
171-
\(pkgname, luaopen) -> do
172-
Lua.pushcfunction luaopen
173-
usedBuiltIn <- Lua.pcall 0 1 Nothing >>= \case
174-
OK -> do -- all good, loading succeeded
175-
-- register as loaded module so later modules can rely on this
176-
Lua.getfield Lua.registryindex Lua.loaded
177-
Lua.pushvalue (Lua.nth 2)
178-
Lua.setfield (Lua.nth 2) pkgname
179-
Lua.pop 1 -- pop _LOADED
180-
return True
181-
_ -> do -- built-in library failed, load system lib
182-
Lua.pop 1 -- ignore error message
183-
-- Try loading via the normal package loading mechanism.
184-
Lua.getglobal "require"
185-
Lua.pushName pkgname
186-
Lua.call 1 1 -- Throws an exception if loading failed again!
187-
return False
188-
189-
-- Module on top of stack. Register as global
190-
Lua.setglobal pkgname
191-
return $ if usedBuiltIn then Just pkgname else Nothing
192-
193-
-- Remove module entry from _LOADED table in registry if we used a
194-
-- built-in library. This ensures that later calls to @require@ will
195-
-- prefer the shared library, if any.
196-
forM_ loadedBuiltInModules $ \pkgname -> do
197-
Lua.getfield Lua.registryindex Lua.loaded
198-
Lua.pushnil
199-
Lua.setfield (Lua.nth 2) pkgname
200-
Lua.pop 1 -- registry
201-
202-
installLpegSearcher :: PandocLua ()
203-
installLpegSearcher = liftPandocLua $ do
204-
Lua.getglobal' "package.searchers"
205-
Lua.pushHaskellFunction $ Lua.state >>= liftIO . LPeg.lpeg_searcher
206-
Lua.rawseti (Lua.nth 2) . (+1) . fromIntegral =<< Lua.rawlen (Lua.nth 2)
207-
Lua.pop 1 -- remove 'package.searchers' from stack
208-
209-
-- | Setup the metatable that's assigned to Lua tables that were created
210-
-- from/via JSON arrays.
211-
initJsonMetatable :: PandocLua ()
212-
initJsonMetatable = liftPandocLua $ do
213-
pushPandocList (const pushnil) []
214-
getmetatable top
215-
setfield registryindex HsLua.Aeson.jsonarray
216-
Lua.pop 1
69+
initModules
70+
liftPandocLua runInitScript
71+
72+
-- | Run the @init.lua@ data file as a Lua script.
73+
runInitScript :: LuaE PandocError ()
74+
runInitScript = runDataFileScript "init.lua"
75+
76+
-- | Get a data file and run it as a Lua script.
77+
runDataFileScript :: FilePath -> LuaE PandocError ()
78+
runDataFileScript scriptFile = do
79+
script <- unPandocLua $ readDataFile scriptFile
80+
status <- Lua.dostring script
81+
when (status /= Lua.OK) $ do
82+
err <- popException
83+
let prefix = "Couldn't load '" <> T.pack scriptFile <> "':\n"
84+
throwM . PandocLuaError . (prefix <>) $ case err of
85+
PandocLuaError msg -> msg
86+
_ -> T.pack $ show err
21787

21888
-- | Evaluate a @'PandocLua'@ computation, running all contained Lua
21989
-- operations.
Lines changed: 160 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,160 @@
1+
{-# LANGUAGE LambdaCase #-}
2+
{-# LANGUAGE OverloadedStrings #-}
3+
{- |
4+
Module : Text.Pandoc.Lua.Module
5+
Copyright : Copyright © 2017-2024 Albert Krewinkel
6+
License : GPL-2.0-or-later
7+
Maintainer : Albert Krewinkel <[email protected]>
8+
9+
Setting up and initializing Lua modules.
10+
-}
11+
12+
module Text.Pandoc.Lua.Module
13+
( initModules
14+
) where
15+
16+
import Control.Monad (forM, forM_, when)
17+
import Data.Maybe (catMaybes)
18+
import Data.Version (makeVersion)
19+
import HsLua as Lua
20+
import Text.Pandoc.Error (PandocError)
21+
import Text.Pandoc.Lua.Marshal.List (pushPandocList, pushListModule)
22+
import Text.Pandoc.Lua.PandocLua (PandocLua (..), liftPandocLua)
23+
import qualified Data.ByteString.Char8 as Char8
24+
import qualified Lua.LPeg as LPeg
25+
import qualified HsLua.Aeson
26+
import qualified HsLua.Module.DocLayout as Module.Layout
27+
import qualified HsLua.Module.Path as Module.Path
28+
import qualified HsLua.Module.Zip as Module.Zip
29+
import qualified Text.Pandoc.Lua.Module.CLI as Pandoc.CLI
30+
import qualified Text.Pandoc.Lua.Module.Format as Pandoc.Format
31+
import qualified Text.Pandoc.Lua.Module.Image as Pandoc.Image
32+
import qualified Text.Pandoc.Lua.Module.JSON as Pandoc.JSON
33+
import qualified Text.Pandoc.Lua.Module.Log as Pandoc.Log
34+
import qualified Text.Pandoc.Lua.Module.MediaBag as Pandoc.MediaBag
35+
import qualified Text.Pandoc.Lua.Module.Pandoc as Module.Pandoc
36+
import qualified Text.Pandoc.Lua.Module.Scaffolding as Pandoc.Scaffolding
37+
import qualified Text.Pandoc.Lua.Module.Structure as Pandoc.Structure
38+
import qualified Text.Pandoc.Lua.Module.System as Pandoc.System
39+
import qualified Text.Pandoc.Lua.Module.Template as Pandoc.Template
40+
import qualified Text.Pandoc.Lua.Module.Text as Pandoc.Text
41+
import qualified Text.Pandoc.Lua.Module.Types as Pandoc.Types
42+
import qualified Text.Pandoc.Lua.Module.Utils as Pandoc.Utils
43+
44+
initModules :: PandocLua ()
45+
initModules = do
46+
initPandocModule
47+
initJsonMetatable
48+
installLpegSearcher
49+
setGlobalModules
50+
51+
initPandocModule :: PandocLua ()
52+
initPandocModule = liftPandocLua $ do
53+
-- Push module table
54+
registerModule Module.Pandoc.documentedModule
55+
-- load modules and add them to the `pandoc` module table.
56+
forM_ submodules $ \mdl -> do
57+
registerModule mdl
58+
-- pandoc.text must be require-able as 'text' for backwards compat.
59+
when (moduleName mdl == "pandoc.text") $ do
60+
getfield registryindex loaded
61+
pushvalue (nth 2)
62+
setfield (nth 2) "text"
63+
pop 1 -- _LOADED
64+
-- Shorten name, drop everything before the first dot (if any).
65+
let fieldname (Name mdlname) = Name .
66+
maybe mdlname snd . Char8.uncons . snd $
67+
Char8.break (== '.') mdlname
68+
Lua.setfield (nth 2) (fieldname $ moduleName mdl)
69+
-- pandoc.List is low-level and must be opened differently.
70+
requirehs "pandoc.List" (const pushListModule)
71+
setfield (nth 2) "List"
72+
-- assign module to global variable
73+
Lua.setglobal "pandoc"
74+
75+
-- | Modules that are loaded at startup and assigned to fields in the
76+
-- pandoc module.
77+
--
78+
-- Note that @pandoc.List@ is not included here for technical reasons;
79+
-- it must be handled separately.
80+
submodules :: [Module PandocError]
81+
submodules =
82+
[ Pandoc.CLI.documentedModule
83+
, Pandoc.Format.documentedModule
84+
, Pandoc.Image.documentedModule
85+
, Pandoc.JSON.documentedModule
86+
, Pandoc.Log.documentedModule
87+
, Pandoc.MediaBag.documentedModule
88+
, Pandoc.Scaffolding.documentedModule
89+
, Pandoc.Structure.documentedModule
90+
, Pandoc.System.documentedModule
91+
, Pandoc.Template.documentedModule
92+
, Pandoc.Text.documentedModule
93+
, Pandoc.Types.documentedModule
94+
, Pandoc.Utils.documentedModule
95+
, Module.Layout.documentedModule { moduleName = "pandoc.layout" }
96+
`allSince` [2,18]
97+
, Module.Path.documentedModule { moduleName = "pandoc.path" }
98+
`allSince` [2,12]
99+
, Module.Zip.documentedModule { moduleName = "pandoc.zip" }
100+
`allSince` [3,0]
101+
]
102+
where
103+
allSince mdl version = mdl
104+
{ moduleFunctions = map (`since` makeVersion version) $ moduleFunctions mdl
105+
}
106+
107+
-- | Load all global modules and set them to their global variables.
108+
setGlobalModules :: PandocLua ()
109+
setGlobalModules = liftPandocLua $ do
110+
let globalModules =
111+
[ ("lpeg", LPeg.luaopen_lpeg_ptr) -- must be loaded first
112+
, ("re", LPeg.luaopen_re_ptr) -- re depends on lpeg
113+
]
114+
loadedBuiltInModules <- fmap catMaybes . forM globalModules $
115+
\(pkgname, luaopen) -> do
116+
Lua.pushcfunction luaopen
117+
usedBuiltIn <- Lua.pcall 0 1 Nothing >>= \case
118+
OK -> do -- all good, loading succeeded
119+
-- register as loaded module so later modules can rely on this
120+
Lua.getfield Lua.registryindex Lua.loaded
121+
Lua.pushvalue (Lua.nth 2)
122+
Lua.setfield (Lua.nth 2) pkgname
123+
Lua.pop 1 -- pop _LOADED
124+
return True
125+
_ -> do -- built-in library failed, load system lib
126+
Lua.pop 1 -- ignore error message
127+
-- Try loading via the normal package loading mechanism.
128+
Lua.getglobal "require"
129+
Lua.pushName pkgname
130+
Lua.call 1 1 -- Throws an exception if loading failed again!
131+
return False
132+
133+
-- Module on top of stack. Register as global
134+
Lua.setglobal pkgname
135+
return $ if usedBuiltIn then Just pkgname else Nothing
136+
137+
-- Remove module entry from _LOADED table in registry if we used a
138+
-- built-in library. This ensures that later calls to @require@ will
139+
-- prefer the shared library, if any.
140+
forM_ loadedBuiltInModules $ \pkgname -> do
141+
Lua.getfield Lua.registryindex Lua.loaded
142+
Lua.pushnil
143+
Lua.setfield (Lua.nth 2) pkgname
144+
Lua.pop 1 -- registry
145+
146+
installLpegSearcher :: PandocLua ()
147+
installLpegSearcher = liftPandocLua $ do
148+
Lua.getglobal' "package.searchers"
149+
Lua.pushHaskellFunction $ Lua.state >>= liftIO . LPeg.lpeg_searcher
150+
Lua.rawseti (Lua.nth 2) . (+1) . fromIntegral =<< Lua.rawlen (Lua.nth 2)
151+
Lua.pop 1 -- remove 'package.searchers' from stack
152+
153+
-- | Setup the metatable that's assigned to Lua tables that were created
154+
-- from/via JSON arrays.
155+
initJsonMetatable :: PandocLua ()
156+
initJsonMetatable = liftPandocLua $ do
157+
pushPandocList (const pushnil) []
158+
getmetatable top
159+
setfield registryindex HsLua.Aeson.jsonarray
160+
Lua.pop 1

0 commit comments

Comments
 (0)