diff options
| author | Albert Krewinkel <[email protected]> | 2022-09-22 23:39:25 +0200 |
|---|---|---|
| committer | GitHub <[email protected]> | 2022-09-22 14:39:25 -0700 |
| commit | 22fa51ded17367a49114a1dc993402294579f7ea (patch) | |
| tree | 5b59dcd1375a3db296777758dd1308ab161340c5 | |
| parent | bd1d923b86edba6e090ba14b1cd17e1e32c727f2 (diff) | |
Make pandoc behave like a Lua interpreter when called as `pandoc-lua`. (#8311)
| -rw-r--r-- | MANUAL.txt | 10 | ||||
| -rw-r--r-- | Makefile | 6 | ||||
| -rw-r--r-- | doc/pandoc-lua.md | 50 | ||||
| -rw-r--r-- | pandoc-cli/src/pandoc.hs | 2 | ||||
| -rw-r--r-- | pandoc.cabal | 1 | ||||
| -rw-r--r-- | src/Text/Pandoc/Lua.hs | 135 |
6 files changed, 201 insertions, 3 deletions
diff --git a/MANUAL.txt b/MANUAL.txt index e80c920f2..de88b8e75 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -7096,6 +7096,16 @@ will be performed on the server during pandoc conversions. [pandoc-server]: https://github.com/jgm/pandoc/blob/master/doc/pandoc-server.md +# Running pandoc as a Lua interpreter + +Calling the pandoc executable under the name `pandoc-lua` will +make it function as a standalone Lua interpreter. The behavior is +mostly identical to that of the [standalone `lua` +executable][standalone lua], version 5.4. However, there is no +REPL yet, and the options `-W`, `-E`, and `-i` currently don't +have any effect. + +[lua standalone]: https://www.lua.org/manual/5.4/manual.html#7 # A note on security @@ -77,7 +77,7 @@ fix_spacing: ## Fix trailing newlines and spaces changes_github: ## copy this release's changes in gfm pandoc --lua-filter tools/extract-changes.lua changelog.md -t gfm --wrap=none --template tools/changes_template.html | sed -e 's/\\#/#/g' | pbcopy -man: man/pandoc.1 man/pandoc-server.1 +man: man/pandoc.1 man/pandoc-server.1 man/pandoc-lua.1 .PHONY: man @@ -102,10 +102,10 @@ man/pandoc.1: MANUAL.txt man/pandoc.1.before man/pandoc.1.after --variable footer="pandoc $(version)" \ -o $@ -man/pandoc-server.1: doc/pandoc-server.md +man/pandoc-%.1: doc/pandoc-%.md pandoc $< -f markdown -t man -s \ --lua-filter man/manfilter.lua \ - --variable footer="pandoc-server $(version)" \ + --variable footer="pandoc-$* $(version)" \ -o $@ README.md: README.template MANUAL.txt tools/update-readme.lua diff --git a/doc/pandoc-lua.md b/doc/pandoc-lua.md new file mode 100644 index 000000000..bacceeb1b --- /dev/null +++ b/doc/pandoc-lua.md @@ -0,0 +1,50 @@ +--- +title: pandoc-lua +section: 1 +date: September 22, 2022 +--- + +# SYNOPSIS + +`pandoc-lua` [*options*] [*script* [*args*]] + +# DESCRIPTION + +`pandoc-lua` is a standalone Lua interpreter with behavior similar +to that of the standard `lua` executable, but exposing all of +pandoc's Lua libraries. All `pandoc.*` packages, as well as the +packages `re` and `lpeg`, are available via global variables. +Furthermore, the globals `PANDOC_VERSION`, `PANDOC_STATE`, and +`PANDOC_API_VERSION` are set at startup. + +If no script argument is given, then the script is assumed to be +passed in via *stdin*. Interactive mode is not supported at this +time. + +# OPTIONS + +`-e stat` +: Execute statement `stat`. + +`-l mod` +: If mod has the pattern `g=m`, then require library `m` into + global `g`; otherwise require library `mod` into global + `mod`. + +`-v` +: Show version information. + +`-i`, `-E`, `-W` +: Not supported yet; print a warning to that effect. + +# AUTHORS + +Copyright 2022 John MacFarlane ([email protected]) and +contributors. Released under the [GPL], version 2 or later. This +software carries no warranty of any kind. (See COPYRIGHT for full +copyright and warranty notices.) + +Lua: Copyright 1994-2022 Lua.org, PUC-Rio. + +[GPL]: https://www.gnu.org/copyleft/gpl.html "GNU General Public License" + diff --git a/pandoc-cli/src/pandoc.hs b/pandoc-cli/src/pandoc.hs index 305fc405e..49aaa884e 100644 --- a/pandoc-cli/src/pandoc.hs +++ b/pandoc-cli/src/pandoc.hs @@ -14,6 +14,7 @@ module Main where import qualified Control.Exception as E import Text.Pandoc.App (convertWithOpts, defaultOpts, options, parseOptions) import Text.Pandoc.Error (handleError) +import Text.Pandoc.Lua (runScript) import Text.Pandoc.Server (ServerOpts(..), parseServerOpts, app) import Safe (readDef) import System.Environment (getProgName, lookupEnv) @@ -30,4 +31,5 @@ main = E.handle (handleError . Left) $ do "pandoc-server" -> do sopts <- parseServerOpts Warp.run (serverPort sopts) (timeout (serverTimeout sopts) app) + "pandoc-lua" -> runScript _ -> parseOptions options defaultOpts >>= convertWithOpts diff --git a/pandoc.cabal b/pandoc.cabal index b279f7ef3..338ffcf1a 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -502,6 +502,7 @@ library http-types >= 0.8 && < 0.13, ipynb >= 0.2 && < 0.3, jira-wiki-markup >= 1.4 && < 1.5, + lua >= 2.2 && < 2.3, lpeg >= 1.0.1 && < 1.1, mime-types >= 0.1.1 && < 0.2, mtl >= 2.2 && < 2.3, diff --git a/src/Text/Pandoc/Lua.hs b/src/Text/Pandoc/Lua.hs index b1d263fc7..612465aba 100644 --- a/src/Text/Pandoc/Lua.hs +++ b/src/Text/Pandoc/Lua.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE TypeApplications #-} {- | Module : Text.Pandoc.Lua Copyright : Copyright © 2017-2022 Albert Krewinkel @@ -13,15 +16,147 @@ module Text.Pandoc.Lua applyFilter , readCustom , writeCustom + -- * Run scripts as program + , runScript -- * Low-level functions , Global(..) , setGlobals , runLua ) where +import Control.Monad (forM_, when) +import Data.ByteString (ByteString) +import Data.Foldable (foldl') +import Data.Text (unpack) +import Foreign.Ptr (nullPtr) +import System.Console.GetOpt +import System.Environment (getArgs) +import System.Exit (exitSuccess) +import System.IO (hPutStrLn, stderr) +import Text.Pandoc.Class (runIOorExplode) +import Text.Pandoc.Error (handleError) import Text.Pandoc.Lua.Filter (applyFilter) import Text.Pandoc.Lua.Global (Global (..), setGlobals) import Text.Pandoc.Lua.Init (runLua) import Text.Pandoc.Lua.Reader (readCustom) import Text.Pandoc.Lua.Writer (writeCustom) import Text.Pandoc.Lua.Orphans () +import Text.Pandoc.Shared (pandocVersion) +import qualified Lua.Auxiliary as Lua +import qualified Lua.Constants as Lua +import qualified HsLua as Lua +import qualified HsLua.Core.Types as Lua +import qualified Text.Pandoc.UTF8 as UTF8 + +-- | Uses the first command line argument as the name of a script file +-- and tries to run that script in Lua. Falls back to stdin if no file +-- is given. Any remaining args are passed to Lua via the global table +-- @arg@. +runScript :: IO () +runScript = do + rawArgs <- getArgs + let (actions, args, errs) = getOpt RequireOrder luaOptions rawArgs + when (not $ null errs) . ioError . userError $ + concat errs ++ + usageInfo "Usage: pandoc-lua [options] [script [args]]" luaOptions + + let (script, arg) = splitAt 1 args + opts <- foldl' (>>=) (return defaultLuaOpts) actions + luaResult <- runIOorExplode . runLua $ do + Lua.pushList Lua.pushString arg + Lua.setglobal "arg" + + forM_ (reverse $ optExecute opts) $ \case + ExecuteCode stat -> do + status <- Lua.dostringTrace stat + when (status /= Lua.OK) + Lua.throwErrorAsException + RequireModule g mod' -> do + Lua.getglobal "require" + Lua.pushName mod' + status <- Lua.pcallTrace 1 1 + if status == Lua.OK + then Lua.setglobal g + else Lua.throwErrorAsException + + result <- case script of + [fp] -> Lua.dofileTrace fp + _ -> do + -- load script from stdin + l <- Lua.state + Lua.liftIO (Lua.luaL_loadfile l nullPtr) >>= \case + Lua.LUA_OK -> Lua.pcallTrace 0 Lua.multret + s -> pure $ Lua.toStatus s + + when (result /= Lua.OK) + Lua.throwErrorAsException + handleError luaResult + +-- | Code to execute on startup. +data LuaCode = ExecuteCode ByteString | RequireModule Lua.Name Lua.Name + +-- | Lua runner command line options. +data LuaOpt = LuaOpt + { optNoEnv :: Bool -- ^ Ignore environment variables + , optInteractive :: Bool -- ^ Interactive + , optWarnings :: Bool -- ^ Whether warnings are enabled + , optExecute :: [LuaCode] -- ^ code to execute + } + +defaultLuaOpts :: LuaOpt +defaultLuaOpts = LuaOpt + { optNoEnv = False + , optInteractive = False + , optWarnings = False + , optExecute = mempty + } + +-- | Lua command line options. +luaOptions :: [OptDescr (LuaOpt -> IO LuaOpt)] +luaOptions = + [ Option "e" [] + (flip ReqArg "stat" $ \stat opt -> return $ + let code = ExecuteCode $ UTF8.fromString stat + in opt{ optExecute = code:(optExecute opt) }) + "execute string 'stat'" + + , Option "i" [] + (NoArg $ \opt -> do + hPutStrLn stderr "[WARNING] Flag `-i` is not supported yet." + return opt { optInteractive = True }) + "interactive mode -- currently not supported" + + , Option "l" [] + (flip ReqArg "mod" $ \mod' opt -> return $ + let toName = Lua.Name . UTF8.fromString + code = case break (== '=') mod' of + (glb, ('=':m)) -> RequireModule (toName glb) (toName m) + (glb, _ ) -> RequireModule (toName glb) (toName glb) + in opt{ optExecute = code:(optExecute opt) }) + (unlines + [ "require library 'mod' into global 'mod';" + , "if 'mod' has the pattern 'g=module', then" + , "require library 'module' into global 'g'" + ]) + + , Option "v" [] + (NoArg $ \_opt -> do + Lua.run @Lua.Exception $ do + Lua.openlibs + Lua.dostring "print(_VERSION)" + putStrLn $ "Embedded in pandoc " ++ unpack pandocVersion + exitSuccess) + "show version information" + + , Option "E" [] + (NoArg $ \opt -> do + hPutStrLn stderr "[WARNING] Flag `-E` is not supported yet." + return opt { optNoEnv = True }) + "ignore environment variables -- currently not supported" + + , Option "W" [] + (NoArg $ \opt -> do + hPutStrLn stderr "[WARNING] Flag `-W` is not supported yet." + return opt { optWarnings = True }) + "turn warnings on -- currently not supported" + ] |
