Lua: fix regression in package searcher
This caused `require 'module'` to fail for third party packages. Fixes: #6361
This commit is contained in:
parent
82eb4df284
commit
9c76c52e9b
3 changed files with 16 additions and 2 deletions
|
@ -1,4 +1,5 @@
|
|||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{- |
|
||||
Module : Text.Pandoc.Lua.Packages
|
||||
|
@ -14,9 +15,11 @@ module Text.Pandoc.Lua.Packages
|
|||
( installPandocPackageSearcher
|
||||
) where
|
||||
|
||||
import Control.Monad.Catch (try)
|
||||
import Control.Monad (forM_)
|
||||
import Data.ByteString (ByteString)
|
||||
import Foreign.Lua (Lua, NumResults)
|
||||
import Text.Pandoc.Error (PandocError)
|
||||
import Text.Pandoc.Class.PandocMonad (readDataFile)
|
||||
import Text.Pandoc.Lua.PandocLua (PandocLua, liftPandocLua)
|
||||
|
||||
|
@ -58,8 +61,11 @@ pandocPackageSearcher pkgName =
|
|||
return 1
|
||||
searchPureLuaLoader = do
|
||||
let filename = pkgName ++ ".lua"
|
||||
script <- readDataFile filename
|
||||
pushWrappedHsFun (loadStringAsPackage pkgName script)
|
||||
try (readDataFile filename) >>= \case
|
||||
Right script -> pushWrappedHsFun (loadStringAsPackage pkgName script)
|
||||
Left (_ :: PandocError) -> liftPandocLua $ do
|
||||
Lua.push ("\n\tno file '" ++ filename ++ "' in pandoc's datadir")
|
||||
return (1 :: NumResults)
|
||||
|
||||
loadStringAsPackage :: String -> ByteString -> Lua NumResults
|
||||
loadStringAsPackage pkgName script = do
|
||||
|
|
|
@ -172,6 +172,12 @@ tests = map (localOption (QuickCheckTests 20))
|
|||
Lua.liftIO . assertEqual "pandoc-types version is wrong" pandocTypesVersion
|
||||
=<< Lua.peek Lua.stackTop
|
||||
|
||||
, testCase "require file" $
|
||||
assertFilterConversion "requiring file failed"
|
||||
"require-file.lua"
|
||||
(doc $ para "ignored")
|
||||
(doc $ para (str . T.pack $ "lua" </> "require-file.lua"))
|
||||
|
||||
, testCase "Allow singleton inline in constructors" . runLuaTest $ do
|
||||
Lua.liftIO . assertEqual "Not the exptected Emph" (Emph [Str "test"])
|
||||
=<< Lua.callFunc "pandoc.Emph" (Str "test")
|
||||
|
|
2
test/lua/require-file.lua
Normal file
2
test/lua/require-file.lua
Normal file
|
@ -0,0 +1,2 @@
|
|||
package.path = package.path .. ';lua/?.lua'
|
||||
require 'script-name'
|
Loading…
Add table
Reference in a new issue