Lua: Simplify module loading code.
Modules are now loaded directly; the special pandoc Lua package searcher is no longer necessary and has been removed.
This commit is contained in:
parent
665d5b0fbd
commit
b3cee8bdb0
3 changed files with 34 additions and 103 deletions
|
@ -753,7 +753,6 @@ library
|
||||||
Text.Pandoc.Lua.Module.Types,
|
Text.Pandoc.Lua.Module.Types,
|
||||||
Text.Pandoc.Lua.Module.Utils,
|
Text.Pandoc.Lua.Module.Utils,
|
||||||
Text.Pandoc.Lua.Orphans,
|
Text.Pandoc.Lua.Orphans,
|
||||||
Text.Pandoc.Lua.Packages,
|
|
||||||
Text.Pandoc.Lua.PandocLua,
|
Text.Pandoc.Lua.PandocLua,
|
||||||
Text.Pandoc.Lua.Writer.Classic,
|
Text.Pandoc.Lua.Writer.Classic,
|
||||||
Text.Pandoc.XML.Light,
|
Text.Pandoc.XML.Light,
|
||||||
|
|
|
@ -22,11 +22,20 @@ import HsLua as Lua hiding (status, try)
|
||||||
import GHC.IO.Encoding (getForeignEncoding, setForeignEncoding, utf8)
|
import GHC.IO.Encoding (getForeignEncoding, setForeignEncoding, utf8)
|
||||||
import Text.Pandoc.Class.PandocMonad (PandocMonad, readDataFile)
|
import Text.Pandoc.Class.PandocMonad (PandocMonad, readDataFile)
|
||||||
import Text.Pandoc.Error (PandocError (PandocLuaError))
|
import Text.Pandoc.Error (PandocError (PandocLuaError))
|
||||||
import Text.Pandoc.Lua.Packages (installPandocPackageSearcher)
|
import Text.Pandoc.Lua.Marshal.List (pushListModule)
|
||||||
import Text.Pandoc.Lua.PandocLua (PandocLua, liftPandocLua, runPandocLua)
|
import Text.Pandoc.Lua.PandocLua (PandocLua, liftPandocLua, runPandocLua)
|
||||||
|
import qualified Data.ByteString as B
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import qualified Lua.LPeg as LPeg
|
import qualified Lua.LPeg as LPeg
|
||||||
import qualified Text.Pandoc.Lua.Module.Pandoc as ModulePandoc
|
import qualified HsLua.Module.DocLayout as Module.Layout
|
||||||
|
import qualified HsLua.Module.Path as Module.Path
|
||||||
|
import qualified HsLua.Module.Text as Module.Text
|
||||||
|
import qualified Text.Pandoc.Lua.Module.Pandoc as Module.Pandoc
|
||||||
|
import qualified Text.Pandoc.Lua.Module.MediaBag as Pandoc.MediaBag
|
||||||
|
import qualified Text.Pandoc.Lua.Module.System as Pandoc.System
|
||||||
|
import qualified Text.Pandoc.Lua.Module.Template as Pandoc.Template
|
||||||
|
import qualified Text.Pandoc.Lua.Module.Types as Pandoc.Types
|
||||||
|
import qualified Text.Pandoc.Lua.Module.Utils as Pandoc.Utils
|
||||||
|
|
||||||
-- | Run the lua interpreter, using pandoc's default way of environment
|
-- | Run the lua interpreter, using pandoc's default way of environment
|
||||||
-- initialization.
|
-- initialization.
|
||||||
|
@ -42,47 +51,45 @@ runLua luaOp = do
|
||||||
|
|
||||||
-- | Modules that are loaded at startup and assigned to fields in the
|
-- | Modules that are loaded at startup and assigned to fields in the
|
||||||
-- pandoc module.
|
-- pandoc module.
|
||||||
loadedModules :: [(Name, Name)]
|
--
|
||||||
|
-- Note that @pandoc.List@ is not included here for technical reasons;
|
||||||
|
-- it must be handled separately.
|
||||||
|
loadedModules :: [Module PandocError]
|
||||||
loadedModules =
|
loadedModules =
|
||||||
[ ("pandoc.List", "List")
|
[ Pandoc.MediaBag.documentedModule
|
||||||
, ("pandoc.layout", "layout")
|
, Pandoc.System.documentedModule
|
||||||
, ("pandoc.mediabag", "mediabag")
|
, Pandoc.Template.documentedModule
|
||||||
, ("pandoc.path", "path")
|
, Pandoc.Types.documentedModule
|
||||||
, ("pandoc.system", "system")
|
, Pandoc.Utils.documentedModule
|
||||||
, ("pandoc.template", "template")
|
, Module.Layout.documentedModule { moduleName = "pandoc.layout" }
|
||||||
, ("pandoc.types", "types")
|
, Module.Path.documentedModule { moduleName = "pandoc.path" }
|
||||||
, ("pandoc.utils", "utils")
|
, Module.Text.documentedModule
|
||||||
, ("text", "text")
|
|
||||||
]
|
]
|
||||||
|
|
||||||
-- | Initialize the lua state with all required values
|
-- | Initialize the lua state with all required values
|
||||||
initLuaState :: PandocLua ()
|
initLuaState :: PandocLua ()
|
||||||
initLuaState = do
|
initLuaState = do
|
||||||
liftPandocLua Lua.openlibs
|
liftPandocLua Lua.openlibs
|
||||||
installPandocPackageSearcher
|
|
||||||
initPandocModule
|
initPandocModule
|
||||||
installLpegSearcher
|
installLpegSearcher
|
||||||
setGlobalModules
|
setGlobalModules
|
||||||
loadInitScript "init.lua"
|
loadInitScript "init.lua"
|
||||||
where
|
where
|
||||||
initPandocModule :: PandocLua ()
|
initPandocModule :: PandocLua ()
|
||||||
initPandocModule = do
|
initPandocModule = liftPandocLua $ do
|
||||||
-- Push module table
|
-- Push module table
|
||||||
ModulePandoc.pushModule
|
registerModule Module.Pandoc.documentedModule
|
||||||
-- register as loaded module
|
|
||||||
liftPandocLua $ do
|
|
||||||
Lua.getfield Lua.registryindex Lua.loaded
|
|
||||||
Lua.pushvalue (Lua.nth 2)
|
|
||||||
Lua.setfield (Lua.nth 2) "pandoc"
|
|
||||||
Lua.pop 1 -- remove LOADED table
|
|
||||||
-- load modules and add them to the `pandoc` module table.
|
-- load modules and add them to the `pandoc` module table.
|
||||||
liftPandocLua $ forM_ loadedModules $ \(pkgname, fieldname) -> do
|
forM_ loadedModules $ \mdl -> do
|
||||||
Lua.getglobal "require"
|
registerModule mdl
|
||||||
Lua.pushName pkgname
|
let isNotAsciiDot = (/= 46)
|
||||||
Lua.call 1 1
|
let fieldname = B.takeWhileEnd isNotAsciiDot (fromName $ moduleName mdl)
|
||||||
Lua.setfield (nth 2) fieldname
|
Lua.setfield (nth 2) (Name fieldname)
|
||||||
|
-- pandoc.List is low-level and must be opened differently.
|
||||||
|
requirehs "pandoc.List" (const pushListModule)
|
||||||
|
setfield (nth 2) "List"
|
||||||
-- assign module to global variable
|
-- assign module to global variable
|
||||||
liftPandocLua $ Lua.setglobal "pandoc"
|
Lua.setglobal "pandoc"
|
||||||
|
|
||||||
loadInitScript :: FilePath -> PandocLua ()
|
loadInitScript :: FilePath -> PandocLua ()
|
||||||
loadInitScript scriptFile = do
|
loadInitScript scriptFile = do
|
||||||
|
|
|
@ -1,75 +0,0 @@
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
|
||||||
{-# LANGUAGE TypeApplications #-}
|
|
||||||
{- |
|
|
||||||
Module : Text.Pandoc.Lua.Packages
|
|
||||||
Copyright : Copyright © 2017-2022 Albert Krewinkel
|
|
||||||
License : GNU GPL, version 2 or above
|
|
||||||
|
|
||||||
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
|
||||||
Stability : alpha
|
|
||||||
|
|
||||||
Pandoc module for Lua.
|
|
||||||
-}
|
|
||||||
module Text.Pandoc.Lua.Packages
|
|
||||||
( installPandocPackageSearcher
|
|
||||||
) where
|
|
||||||
|
|
||||||
import Control.Monad (forM_)
|
|
||||||
import Data.String (fromString)
|
|
||||||
import Text.Pandoc.Error (PandocError)
|
|
||||||
import Text.Pandoc.Lua.Marshal.List (pushListModule)
|
|
||||||
import Text.Pandoc.Lua.PandocLua (PandocLua, liftPandocLua)
|
|
||||||
|
|
||||||
import qualified HsLua as Lua
|
|
||||||
import qualified HsLua.Module.DocLayout as DocLayout
|
|
||||||
import qualified HsLua.Module.Path as Path
|
|
||||||
import qualified HsLua.Module.Text as Text
|
|
||||||
import qualified Text.Pandoc.Lua.Module.Pandoc as Pandoc
|
|
||||||
import qualified Text.Pandoc.Lua.Module.MediaBag as MediaBag
|
|
||||||
import qualified Text.Pandoc.Lua.Module.System as System
|
|
||||||
import qualified Text.Pandoc.Lua.Module.Template as Template
|
|
||||||
import qualified Text.Pandoc.Lua.Module.Types as Types
|
|
||||||
import qualified Text.Pandoc.Lua.Module.Utils as Utils
|
|
||||||
|
|
||||||
-- | Insert pandoc's package loader as the first loader, making it the default.
|
|
||||||
installPandocPackageSearcher :: PandocLua ()
|
|
||||||
installPandocPackageSearcher = liftPandocLua $ do
|
|
||||||
Lua.getglobal' "package.searchers"
|
|
||||||
shiftArray
|
|
||||||
Lua.pushHaskellFunction $ Lua.toHaskellFunction pandocPackageSearcher
|
|
||||||
Lua.rawseti (Lua.nth 2) 1
|
|
||||||
Lua.pop 1 -- remove 'package.searchers' from stack
|
|
||||||
where
|
|
||||||
shiftArray = forM_ [4, 3, 2, 1] $ \i -> do
|
|
||||||
Lua.rawgeti (-1) i
|
|
||||||
Lua.rawseti (-2) (i + 1)
|
|
||||||
|
|
||||||
-- | Load a pandoc module.
|
|
||||||
pandocPackageSearcher :: String -> PandocLua Lua.NumResults
|
|
||||||
pandocPackageSearcher pkgName =
|
|
||||||
case pkgName of
|
|
||||||
"pandoc" -> pushModuleLoader Pandoc.documentedModule
|
|
||||||
"pandoc.layout" -> pushModuleLoader DocLayout.documentedModule
|
|
||||||
"pandoc.mediabag" -> pushModuleLoader MediaBag.documentedModule
|
|
||||||
"pandoc.path" -> pushModuleLoader Path.documentedModule
|
|
||||||
"pandoc.system" -> pushModuleLoader System.documentedModule
|
|
||||||
"pandoc.template" -> pushModuleLoader Template.documentedModule
|
|
||||||
"pandoc.types" -> pushModuleLoader Types.documentedModule
|
|
||||||
"pandoc.utils" -> pushModuleLoader Utils.documentedModule
|
|
||||||
"text" -> pushModuleLoader Text.documentedModule
|
|
||||||
"pandoc.List" -> pushWrappedHsFun . Lua.toHaskellFunction @PandocError $
|
|
||||||
(Lua.NumResults 1 <$ pushListModule @PandocError)
|
|
||||||
_ -> reportPandocSearcherFailure
|
|
||||||
where
|
|
||||||
pushModuleLoader mdl = liftPandocLua $ do
|
|
||||||
let mdl' = mdl { Lua.moduleName = fromString pkgName }
|
|
||||||
Lua.pushHaskellFunction $
|
|
||||||
Lua.NumResults 1 <$ Lua.pushModule mdl'
|
|
||||||
return (Lua.NumResults 1)
|
|
||||||
pushWrappedHsFun f = liftPandocLua $ do
|
|
||||||
Lua.pushHaskellFunction f
|
|
||||||
return 1
|
|
||||||
reportPandocSearcherFailure = liftPandocLua $ do
|
|
||||||
Lua.push ("\n\t" <> pkgName <> " is not one of pandoc's default packages")
|
|
||||||
return (Lua.NumResults 1)
|
|
Loading…
Reference in a new issue