Added parameter for user data directory to runLuaFilter.

in Text.Pandoc.Lua.  Also to pushPandocModule.

This change allows users to override pandoc.lua with a file
in their local data directory, adding custom functions, etc.

@tarleb, if you think this is a bad idea, you can revert this.
But in general our data files are all overridable.
This commit is contained in:
John MacFarlane 2017-06-29 17:13:19 +02:00
parent 0f658eb46c
commit 5e00cf8086
4 changed files with 11 additions and 11 deletions

View file

@ -795,7 +795,7 @@ applyLuaFilters :: MonadIO m
applyLuaFilters mbDatadir filters args d = do
expandedFilters <- mapM (expandFilterPath mbDatadir) filters
let go f d' = liftIO $ do
res <- E.try (runLuaFilter f args d')
res <- E.try (runLuaFilter mbDatadir f args d')
case res of
Right x -> return x
Left (LuaException s) -> E.throw (PandocFilterError f s)

View file

@ -56,12 +56,12 @@ newtype LuaException = LuaException String
instance Exception LuaException
runLuaFilter :: (MonadIO m)
=> FilePath -> [String] -> Pandoc -> m Pandoc
runLuaFilter filterPath args pd = liftIO $ do
=> Maybe FilePath -> FilePath -> [String] -> Pandoc -> m Pandoc
runLuaFilter datadir filterPath args pd = liftIO $ do
lua <- Lua.newstate
Lua.openlibs lua
-- store module in global "pandoc"
pushPandocModule lua
pushPandocModule datadir lua
Lua.setglobal lua "pandoc"
top <- Lua.gettop lua
status <- Lua.loadfile lua filterPath

View file

@ -41,9 +41,9 @@ import Text.Pandoc.Readers (Reader (..), getReader)
import Text.Pandoc.Shared (readDataFile)
-- | Push the "pandoc" on the lua stack.
pushPandocModule :: LuaState -> IO ()
pushPandocModule lua = do
script <- pandocModuleScript
pushPandocModule :: Maybe FilePath -> LuaState -> IO ()
pushPandocModule datadir lua = do
script <- pandocModuleScript datadir
status <- loadstring lua script "pandoc.lua"
unless (status /= 0) $ call lua 0 1
push lua "__read"
@ -51,8 +51,8 @@ pushPandocModule lua = do
rawset lua (-3)
-- | Get the string representation of the pandoc module
pandocModuleScript :: IO String
pandocModuleScript = unpack <$> readDataFile Nothing "pandoc.lua"
pandocModuleScript :: Maybe FilePath -> IO String
pandocModuleScript datadir = unpack <$> readDataFile datadir "pandoc.lua"
read_doc :: String -> String -> IO (Either String Pandoc)
read_doc formatSpec content = do

View file

@ -68,7 +68,7 @@ tests = map (localOption (QuickCheckTests 20))
assertFilterConversion :: String -> FilePath -> Pandoc -> Pandoc -> Assertion
assertFilterConversion msg filterPath docIn docExpected = do
docRes <- runLuaFilter ("lua" </> filterPath) [] docIn
docRes <- runLuaFilter Nothing ("lua" </> filterPath) [] docIn
assertEqual msg docExpected docRes
roundtripEqual :: (Eq a, Lua.StackValue a) => a -> IO Bool
@ -78,7 +78,7 @@ roundtripEqual x = (x ==) <$> roundtripped
roundtripped = do
lua <- Lua.newstate
Lua.openlibs lua
pushPandocModule lua
pushPandocModule Nothing lua
Lua.setglobal lua "pandoc"
oldSize <- Lua.gettop lua
Lua.push lua x