From 9c76c52e9bb1481234b8ee5ef9c524a5a61d43bd Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Tue, 12 May 2020 17:10:30 +0200 Subject: Lua: fix regression in package searcher This caused `require 'module'` to fail for third party packages. Fixes: #6361 --- src/Text/Pandoc/Lua/Packages.hs | 10 ++++++++-- test/Tests/Lua.hs | 6 ++++++ test/lua/require-file.lua | 2 ++ 3 files changed, 16 insertions(+), 2 deletions(-) create mode 100644 test/lua/require-file.lua diff --git a/src/Text/Pandoc/Lua/Packages.hs b/src/Text/Pandoc/Lua/Packages.hs index 79d42a6d7..4c3b9d79d 100644 --- a/src/Text/Pandoc/Lua/Packages.hs +++ b/src/Text/Pandoc/Lua/Packages.hs @@ -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 diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs index 14800f7bb..bf9ddc2d5 100644 --- a/test/Tests/Lua.hs +++ b/test/Tests/Lua.hs @@ -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") diff --git a/test/lua/require-file.lua b/test/lua/require-file.lua new file mode 100644 index 000000000..d610e5266 --- /dev/null +++ b/test/lua/require-file.lua @@ -0,0 +1,2 @@ +package.path = package.path .. ';lua/?.lua' +require 'script-name' -- cgit v1.2.3