diff options
| author | Albert Krewinkel <albert@zeitkraut.de> | 2021-11-16 12:03:49 +0100 | 
|---|---|---|
| committer | Albert Krewinkel <albert@zeitkraut.de> | 2021-11-16 12:06:22 +0100 | 
| commit | 305a4f406d64fcf8b3a0d3ac09a276a5f0803e0d (patch) | |
| tree | ba42b370ca24c6952a2716403578957e87f65f63 /src/Text | |
| parent | c19f0634203f224a26851635f4b86e1013a6618a (diff) | |
| download | pandoc-305a4f406d64fcf8b3a0d3ac09a276a5f0803e0d.tar.gz | |
Lua: make loading of global LPeg modules more robust
Ignore errors if the normal package mechanism failed; this not only
covers the case of modules being unavailable on the system, but also
works if the modules are present, but fail to load for some reason.
This makes the built-in package version a true fallback.
Diffstat (limited to 'src/Text')
| -rw-r--r-- | src/Text/Pandoc/Lua/Init.hs | 34 | 
1 files changed, 20 insertions, 14 deletions
| diff --git a/src/Text/Pandoc/Lua/Init.hs b/src/Text/Pandoc/Lua/Init.hs index 23c51969c..bf87f0a41 100644 --- a/src/Text/Pandoc/Lua/Init.hs +++ b/src/Text/Pandoc/Lua/Init.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE LambdaCase        #-}  {-# LANGUAGE OverloadedStrings #-}  {- |     Module      : Text.Pandoc.Lua @@ -46,7 +47,6 @@ initLuaState = do    liftPandocLua Lua.openlibs    installPandocPackageSearcher    initPandocModule -  installLpegSearcher    requireGlobalModules    loadInitScript "init.lua"   where @@ -78,25 +78,31 @@ initLuaState = do    requireGlobalModules :: PandocLua ()    requireGlobalModules = liftPandocLua $ -    forM_ ["lpeg", "re"] $ \pkgname -> do -        -- Try loading via the normal package loading mechanism, which -        -- includes the custom LPeg searcher as a last resort. This -        -- means the system installation of the package, should it be -        -- available, is preferred. +    forM_ [ ("lpeg", LPeg.luaopen_lpeg_ptr) +          , ("re", LPeg.luaopen_re_ptr) +          ] $ +      \(pkgname, luaopen) -> do +        -- Try loading via the normal package loading mechanism, and +        -- fall back to manual module loading if the normal mechanism +        -- fails. This means the system installation of the package, +        -- should it be available, is preferred.          Lua.getglobal "require"          Lua.pushName pkgname -        Lua.call 1 1   -- throws an exception if the module is not found +        Lua.pcall 1 1 Nothing >>= \case +          OK -> pure ()          -- all good, loading succeeded +          _  -> do               -- default mechanism failed, load included lib +            Lua.pop 1  -- ignore error message +            Lua.pushcfunction luaopen +            Lua.call 0 1  -- Throws an exception if loading failed again! +            -- Success. Add module to table @_LOADED@ in the registry +            _ <- Lua.getfield Lua.registryindex Lua.loaded +            Lua.pushvalue (Lua.nth 2)  -- push module to top +            Lua.setfield (Lua.nth 2) pkgname +            Lua.pop 1  -- pop _LOADED          -- Module on top of stack. Register as global          Lua.setglobal pkgname -  installLpegSearcher :: PandocLua () -  installLpegSearcher = liftPandocLua $ do -    Lua.getglobal' "package.searchers" -    Lua.pushHaskellFunction $ Lua.state >>= liftIO . LPeg.lpeg_searcher -    Lua.rawseti (Lua.nth 2) . (+1) . fromIntegral =<< Lua.rawlen (Lua.nth 2) -    Lua.pop 1  -- remove 'package.searchers' from stack -  -- | AST elements are marshaled via normal constructor functions in the  -- @pandoc@ module. However, accessing Lua globals from Haskell is  -- expensive (due to error handling). Accessing the Lua registry is much | 
