diff options
| author | Albert Krewinkel <[email protected]> | 2022-09-29 17:59:31 +0200 |
|---|---|---|
| committer | John MacFarlane <[email protected]> | 2022-09-30 08:33:40 -0700 |
| commit | b6a571d5774176202c1719f626c497f1bcdbaf2c (patch) | |
| tree | 2eb50335ee48bdf22286cc898403ccc1d9be979b /pandoc-cli | |
| parent | 5be9052f5fb7283372b3d5497bef499718a34992 (diff) | |
pandoc-cli: Allow building a binary without Lua support
Disabling the `lua` cabal flag will result in a binary without Lua.
Diffstat (limited to 'pandoc-cli')
| -rw-r--r-- | pandoc-cli/lua/PandocCLI/Lua.hs | 35 | ||||
| -rw-r--r-- | pandoc-cli/no-lua/PandocCLI/Lua.hs | 26 | ||||
| -rw-r--r-- | pandoc-cli/pandoc-cli.cabal | 17 | ||||
| -rw-r--r-- | pandoc-cli/src/pandoc.hs | 22 |
4 files changed, 76 insertions, 24 deletions
diff --git a/pandoc-cli/lua/PandocCLI/Lua.hs b/pandoc-cli/lua/PandocCLI/Lua.hs new file mode 100644 index 000000000..6507587c8 --- /dev/null +++ b/pandoc-cli/lua/PandocCLI/Lua.hs @@ -0,0 +1,35 @@ +{-# LANGUAGE OverloadedStrings #-} +{- | + Module : PandocCLI.Lua + Copyright : © 2022 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 Text.Pandoc.Class (runIOorExplode) +import Text.Pandoc.Error (handleError) +import Text.Pandoc.Lua (runLua, runLuaNoEnv, getEngine) +import Text.Pandoc.Shared (pandocVersionText) + +-- | Runs pandoc as a Lua interpreter that is (mostly) compatible with +-- the default @lua@ program shipping with Lua. +runLuaInterpreter :: String -- ^ Program name + -> [String] -- ^ Command line arguments + -> IO () +runLuaInterpreter progName args = do + let settings = Settings + { settingsVersionInfo = "\nEmbedded in pandoc " <> pandocVersionText + , settingsRunner = runner + } + runStandalone settings progName args + where + runner envBehavior = + let runLua' = case envBehavior of + IgnoreEnvVars -> runLuaNoEnv + ConsultEnvVars -> runLua + in handleError <=< runIOorExplode . runLua' diff --git a/pandoc-cli/no-lua/PandocCLI/Lua.hs b/pandoc-cli/no-lua/PandocCLI/Lua.hs new file mode 100644 index 000000000..350a4cdbc --- /dev/null +++ b/pandoc-cli/no-lua/PandocCLI/Lua.hs @@ -0,0 +1,26 @@ +{-# LANGUAGE OverloadedStrings #-} +{- | + Module : PandocCLI.Lua + Copyright : © 2022 Albert Krewinkel + License : GPL-2.0-or-later + Maintainer : Albert Krewinkel <[email protected]> + +Placeholder values to be used when pandoc is compiled without support +for the Lua scripting engine. +-} +module PandocCLI.Lua (runLuaInterpreter, getEngine) where + +import Control.Monad.IO.Class (MonadIO) +import Text.Pandoc.Error (PandocError (PandocNoScriptingEngine), handleError) +import Text.Pandoc.Scripting (ScriptingEngine, noEngine) + +-- | Raises an error, reporting that the scripting engine is unavailable. +runLuaInterpreter :: String -- ^ Program name + -> [String] -- ^ Command line arguments + -> IO () +runLuaInterpreter _progName _args = do + handleError (Left PandocNoScriptingEngine) + +-- | Placeholder scripting engine. +getEngine :: MonadIO m => m ScriptingEngine +getEngine = pure noEngine diff --git a/pandoc-cli/pandoc-cli.cabal b/pandoc-cli/pandoc-cli.cabal index 9a3e5ff2d..82437d441 100644 --- a/pandoc-cli/pandoc-cli.cabal +++ b/pandoc-cli/pandoc-cli.cabal @@ -21,6 +21,11 @@ source-repository head type: git location: git://github.com/jgm/pandoc.git +flag lua + description: Support custom modifications and conversions with the + pandoc Lua scripting engine. + default: True + flag server Description: Include support for running pandoc as an HTTP server. Default: True @@ -58,9 +63,8 @@ executable pandoc main-is: pandoc.hs buildable: True build-depends: pandoc >= 3.0, - pandoc-lua-engine >= 0.1 && < 0.2, - hslua-cli >= 1.2 && < 1.3 - other-modules: PandocCLI.Server + other-modules: PandocCLI.Lua + , PandocCLI.Server if flag(server) build-depends: pandoc-server >= 0.1 && < 0.2, wai-extra >= 3.0.24, @@ -69,3 +73,10 @@ executable pandoc hs-source-dirs: server else hs-source-dirs: no-server + + if flag(lua) + build-depends: hslua-cli >= 1.2 && < 1.3, + pandoc-lua-engine >= 0.1 && < 0.2 + hs-source-dirs: lua + else + hs-source-dirs: no-lua diff --git a/pandoc-cli/src/pandoc.hs b/pandoc-cli/src/pandoc.hs index 306b2dc8a..1b95d898e 100644 --- a/pandoc-cli/src/pandoc.hs +++ b/pandoc-cli/src/pandoc.hs @@ -12,17 +12,13 @@ Parses command-line options and calls the appropriate readers and writers. -} module Main where -import Control.Monad ((<=<)) import qualified Control.Exception as E -import HsLua.CLI (EnvBehavior (..), Settings (..), runStandalone) import System.Environment (getArgs, getProgName) import Text.Pandoc.App ( convertWithOpts, defaultOpts, options , parseOptionsFromArgs) -import Text.Pandoc.Class (runIOorExplode) import Text.Pandoc.Error (handleError) -import Text.Pandoc.Lua (getEngine, runLua, runLuaNoEnv) -import Text.Pandoc.Shared (pandocVersionText) import qualified Text.Pandoc.UTF8 as UTF8 +import PandocCLI.Lua import PandocCLI.Server main :: IO () @@ -42,19 +38,3 @@ main = E.handle (handleError . Left) $ do let cliOpts = options engine opts <- parseOptionsFromArgs cliOpts defaultOpts prg rawArgs convertWithOpts engine opts - --- | Runs pandoc as a Lua interpreter that is (mostly) compatible with --- the default @lua@ program shipping with Lua. -runLuaInterpreter :: String -> [String] -> IO () -runLuaInterpreter progName args = do - let settings = Settings - { settingsVersionInfo = "\nEmbedded in pandoc " <> pandocVersionText - , settingsRunner = runner - } - runStandalone settings progName args - where - runner envBehavior = - let runLua' = case envBehavior of - IgnoreEnvVars -> runLuaNoEnv - ConsultEnvVars -> runLua - in handleError <=< runIOorExplode . runLua' |
