aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2022-12-12 17:15:34 +0100
committerJohn MacFarlane <[email protected]>2022-12-12 09:35:21 -0800
commit928dde57b968066366b567201961dba6441d89e2 (patch)
tree0d297c3c3c4f95f8d7800838442ed502d5f6f57c
parent09af316f360ff316b954af700be7d35e1dd0c29f (diff)
Lua: add pandoc.cli module
Allow processing of CLI options in Lua.
-rw-r--r--doc/lua-filters.md30
-rw-r--r--pandoc-lua-engine/pandoc-lua-engine.cabal1
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs4
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/CLI.hs64
4 files changed, 98 insertions, 1 deletions
diff --git a/doc/lua-filters.md b/doc/lua-filters.md
index c3c528b76..5cefa28de 100644
--- a/doc/lua-filters.md
+++ b/doc/lua-filters.md
@@ -3583,6 +3583,36 @@ Usage:
[WriterOptions]: #type-writeroptions
+# Module pandoc.cli
+
+Command line options and argument parsing.
+
+## Fields {#pandoc.cli-fields}
+
+### default\_options {#pandoc.cli.default_options}
+
+Default CLI options, using a JSON-like representation (table).
+
+## Functions
+
+### parse_options {#pandoc.cli.parse_options}
+
+`parse_options (args)`
+
+Parses command line arguments into pandoc options. Typically this
+function will be used in stand-alone pandoc Lua scripts, taking
+the list of arguments from the global `arg`.
+
+Parameters:
+
+`args`
+: list of command line arguments ({string,...})
+
+Returns:
+
+- parsed options, using their JSON-like representation. (table)
+
+
# Module pandoc.utils
This module exposes internal pandoc functions and utility
diff --git a/pandoc-lua-engine/pandoc-lua-engine.cabal b/pandoc-lua-engine/pandoc-lua-engine.cabal
index 62dd95971..e17f0ad08 100644
--- a/pandoc-lua-engine/pandoc-lua-engine.cabal
+++ b/pandoc-lua-engine/pandoc-lua-engine.cabal
@@ -76,6 +76,7 @@ library
, Text.Pandoc.Lua.Marshal.Sources
, Text.Pandoc.Lua.Marshal.Template
, Text.Pandoc.Lua.Marshal.WriterOptions
+ , Text.Pandoc.Lua.Module.CLI
, Text.Pandoc.Lua.Module.Format
, Text.Pandoc.Lua.Module.MediaBag
, Text.Pandoc.Lua.Module.Pandoc
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs
index a05d68355..f5f73c5b4 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs
@@ -37,6 +37,7 @@ import qualified HsLua.Module.DocLayout as Module.Layout
import qualified HsLua.Module.Path as Module.Path
import qualified HsLua.Module.Text as Module.Text
import qualified HsLua.Module.Zip as Module.Zip
+import qualified Text.Pandoc.Lua.Module.CLI as Pandoc.CLI
import qualified Text.Pandoc.Lua.Module.Format as Pandoc.Format
import qualified Text.Pandoc.Lua.Module.MediaBag as Pandoc.MediaBag
import qualified Text.Pandoc.Lua.Module.Pandoc as Module.Pandoc
@@ -82,7 +83,8 @@ runLuaNoEnv action = do
-- it must be handled separately.
loadedModules :: [Module PandocError]
loadedModules =
- [ Pandoc.Format.documentedModule
+ [ Pandoc.CLI.documentedModule
+ , Pandoc.Format.documentedModule
, Pandoc.MediaBag.documentedModule
, Pandoc.Scaffolding.documentedModule
, Pandoc.System.documentedModule
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/CLI.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/CLI.hs
new file mode 100644
index 000000000..01c94cdbb
--- /dev/null
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/CLI.hs
@@ -0,0 +1,64 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE OverloadedStrings #-}
+{- |
+ Module : Text.Pandoc.Lua.Module.CLI
+ Copyright : © 2022 Albert Krewinkel
+ License : GPL-2.0-or-later
+ Maintainer : Albert Krewinkel <[email protected]>
+
+Command line helpers
+-}
+module Text.Pandoc.Lua.Module.CLI
+ ( documentedModule
+ ) where
+
+import Control.Applicative ((<|>))
+import HsLua ( Field (..), Module (..), (###), (<#>), (=#>), (#?)
+ , defun, failLua, functionResult, liftIO, parameter, pop
+ , pushViaJSON, rawgeti, top)
+import HsLua.Marshalling (lastly, liftLua, peekList, peekString)
+import Text.Pandoc.App (defaultOpts, options, parseOptionsFromArgs)
+import Text.Pandoc.Error (PandocError)
+import Text.Pandoc.Lua.PandocLua ()
+import qualified Data.Text as T
+
+-- | Push the pandoc.types module on the Lua stack.
+documentedModule :: Module PandocError
+documentedModule = Module
+ { moduleName = "pandoc.cli"
+ , moduleDescription =
+ "Command line options and argument parsing."
+ , moduleFields =
+ [ Field
+ { fieldName = "default_options"
+ , fieldDescription = "Default CLI options, using a JSON-like " <>
+ "representation."
+ , fieldPushValue = pushViaJSON defaultOpts
+ }
+ ]
+ , moduleFunctions =
+ [ defun "parse_options"
+ ### parseOptions
+ <#> parameter peekArgs "{string,...}" "args"
+ "list of command line arguments"
+ =#> functionResult pushViaJSON "table"
+ "parsed options, using their JSON-like representation."
+ #? T.unlines
+ [ "Parses command line arguments into pandoc options."
+ , "Typically this function will be used in stand-alone pandoc Lua"
+ , "scripts, taking the list of arguments from the global `arg`."
+ ]
+ ]
+ , moduleOperations = []
+ }
+ where
+ peekArgs idx =
+ (,)
+ <$> (liftLua (rawgeti idx 0) *> (peekString top <|> pure "") `lastly` pop 1)
+ <*> peekList peekString idx
+
+ parseOptions (prg, args) =
+ liftIO (parseOptionsFromArgs options defaultOpts prg args) >>=
+ \case
+ Left e -> failLua $ "Cannot process info option: " ++ show e
+ Right opts -> pure opts