blob: 07259af04f3e36f5e0bd50d7cd2d2623093d3dc0 (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
|
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : PandocCLI.Lua
Copyright : © 2022-2023 Albert Krewinkel
License : GPL-2.0-or-later
Maintainer : Albert Krewinkel <[email protected]>
Functions to run the pandoc Lua scripting engine.
-}
module PandocCLI.Lua (runLuaInterpreter, getEngine) where
import Control.Monad ((<=<))
import HsLua.CLI (EnvBehavior (..), Settings (..), runStandalone)
import System.Environment (lookupEnv)
import System.IO.Temp (withSystemTempFile)
import System.IO (hClose)
import Text.Pandoc.Class (runIOorExplode)
import Text.Pandoc.Error (handleError)
import Text.Pandoc.Lua (runLua, runLuaNoEnv, getEngine)
import Text.Pandoc.Version (pandocVersionText)
-- | Runs pandoc as a Lua interpreter that is (mostly) compatible with
-- the default @lua@ program shipping with Lua.
--
-- The filename for the history of the REPL is taken from the
-- @PANDOC_REPL_HISTORY@ environment variable if possible. Otherwise a
-- new temporary file is used; it is removed after the REPL finishes.
runLuaInterpreter :: String -- ^ Program name
-> [String] -- ^ Command line arguments
-> IO ()
runLuaInterpreter progName args = do
-- We need some kind of temp
mbhistfile <- lookupEnv "PANDOC_REPL_HISTORY"
case mbhistfile of
Just histfile -> runStandaloneWithHistory histfile
Nothing -> withSystemTempFile "pandoc-hist" $ \fp handle -> do
-- We cannot pass a handle to the repl; the file will be re-opened
-- there.
hClose handle
runStandaloneWithHistory fp
where
runStandaloneWithHistory histfile = do
let settings = Settings
{ settingsVersionInfo = "\nEmbedded in pandoc " <>
pandocVersionText
, settingsRunner = runner
, settingsHistory = Just histfile
}
runStandalone settings progName args
runner envBehavior =
let runLua' = case envBehavior of
IgnoreEnvVars -> runLuaNoEnv
ConsultEnvVars -> runLua
in handleError <=< runIOorExplode . runLua'
|