aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2022-03-29 17:38:00 +0200
committerGitHub <[email protected]>2022-03-29 08:38:00 -0700
commit40dd8fd129449fb9db356f418afffa5ae71ebfd4 (patch)
treed7e3ec1adc4ea2e3eedd0594598126635e0a5571
parente4f4be6c8010e9d2913af12dc6177f4f7ca84b17 (diff)
Include Lua version in `--version` output. (#7997)
-rw-r--r--src/Text/Pandoc/App/CommandLineOptions.hs8
1 files changed, 7 insertions, 1 deletions
diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs
index 27374a81f..ffb7c5eb8 100644
--- a/src/Text/Pandoc/App/CommandLineOptions.hs
+++ b/src/Text/Pandoc/App/CommandLineOptions.hs
@@ -4,6 +4,7 @@
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE TypeApplications #-}
{- |
Module : Text.Pandoc.App.CommandLineOptions
Copyright : Copyright (C) 2006-2022 John MacFarlane
@@ -37,6 +38,7 @@ import Data.List (isPrefixOf)
#endif
import Data.Maybe (fromMaybe, isJust)
import Data.Text (Text)
+import HsLua (Exception, getglobal, openlibs, peek, run, top)
import Safe (tailDef)
import Skylighting (Style, Syntax (..), defaultSyntaxMap, parseTheme)
import System.Console.GetOpt
@@ -946,10 +948,14 @@ options =
(\_ -> do
prg <- getProgName
defaultDatadir <- defaultUserDataDir
+ luaVersion <- HsLua.run @HsLua.Exception $ do
+ openlibs
+ getglobal "_VERSION"
+ peek top
UTF8.hPutStrLn stdout
$ T.pack
$ prg ++ " " ++ T.unpack pandocVersion ++
- compileInfo ++
+ compileInfo ++ "\nScripting engine: " ++ luaVersion ++
"\nUser data directory: " ++ defaultDatadir ++
('\n':copyrightMessage)
exitSuccess ))