Lua: make pandoc version available as PANDOC_VERSION

The current pandoc version is made available to Lua programs in the
global PANDOC_VERSION.  It contains the version as a list of numbers.
This commit is contained in:
Albert Krewinkel 2018-01-07 13:43:03 +01:00
parent 458e633bc4
commit 043740d32b
No known key found for this signature in database
GPG key ID: 388DC0B21F631124
2 changed files with 29 additions and 13 deletions

View file

@ -35,8 +35,10 @@ module Text.Pandoc.Lua.Init
import Control.Monad.Trans (MonadIO (..))
import Data.IORef (newIORef, readIORef)
import Data.Version (Version (versionBranch))
import Foreign.Lua (Lua, LuaException (..))
import GHC.IO.Encoding (getForeignEncoding, setForeignEncoding, utf8)
import Paths_pandoc (version)
import Text.Pandoc.Class (PandocIO, getCommonState, getUserDataDir, getMediaBag,
setMediaBag)
import Text.Pandoc.Lua.Packages (LuaPackageParams (..),
@ -75,5 +77,7 @@ initLuaState :: LuaPackageParams -> Lua ()
initLuaState luaPkgParams = do
Lua.openlibs
Lua.preloadTextModule "text"
Lua.push (versionBranch version)
Lua.setglobal "PANDOC_VERSION"
installPandocPackageSearcher luaPkgParams
loadScriptFromDataDir (luaPkgDataDir luaPkgParams) "init.lua"

View file

@ -13,6 +13,7 @@ import Text.Pandoc.Builder (bulletList, divWith, doc, doubleQuoted, emph,
import Text.Pandoc.Class (runIOorExplode, setUserDataDir)
import Text.Pandoc.Definition (Block, Inline, Meta, Pandoc)
import Text.Pandoc.Lua (runLuaFilter, runPandocLua)
import Text.Pandoc.Shared (pandocVersion)
import qualified Foreign.Lua as Lua
@ -106,6 +107,14 @@ tests = map (localOption (QuickCheckTests 20))
, plain (str "stringify: OK")
, plain (str "to_roman_numeral: OK")
])
, testCase "Pandoc version is set" . runPandocLua' $ do
Lua.getglobal' "table.concat"
Lua.getglobal "PANDOC_VERSION"
Lua.push ("." :: String) -- seperator
Lua.call 2 1
Lua.liftIO . assertEqual "pandoc version is wrong" pandocVersion
=<< Lua.peek Lua.stackTop
]
assertFilterConversion :: String -> FilePath -> Pandoc -> Pandoc -> Assertion
@ -121,18 +130,21 @@ roundtripEqual :: (Eq a, Lua.FromLuaStack a, Lua.ToLuaStack a) => a -> IO Bool
roundtripEqual x = (x ==) <$> roundtripped
where
roundtripped :: (Lua.FromLuaStack a, Lua.ToLuaStack a) => IO a
roundtripped = runIOorExplode $ do
setUserDataDir (Just "../data")
res <- runPandocLua $ do
oldSize <- Lua.gettop
Lua.push x
size <- Lua.gettop
when (size - oldSize /= 1) $
error ("not exactly one additional element on the stack: " ++ show size)
res <- Lua.peekEither (-1)
case res of
Left _ -> error "could not read from stack"
Right y -> return y
roundtripped = runPandocLua' $ do
oldSize <- Lua.gettop
Lua.push x
size <- Lua.gettop
when (size - oldSize /= 1) $
error ("not exactly one additional element on the stack: " ++ show size)
res <- Lua.peekEither (-1)
case res of
Left e -> error (show e)
Left _ -> error "could not read from stack"
Right y -> return y
runPandocLua' :: Lua.Lua a -> IO a
runPandocLua' op = runIOorExplode $ do
setUserDataDir (Just "../data")
res <- runPandocLua op
case res of
Left e -> error (show e)
Right x -> return x