From 096cbe698746d621bfee9607b1ab826240082a10 Mon Sep 17 00:00:00 2001
From: Albert Krewinkel <albert+github@zeitkraut.de>
Date: Fri, 26 Oct 2018 07:12:14 +0200
Subject: [PATCH] Lua: allow access to pandoc state (#5015)

* Lua: allow access to pandoc state

Lua filters and custom writers now have read-only access to most fields
of pandoc's internal state via the global variable `PANDOC_STATE`.

* Lua: allow iterating through fields of PANDOC_STATE

* Lua filters doc: describe CommonState

* Lua filters doc: mention global variable PANDOC_STATE

* Lua: add access to logs

Log messages can currently only be printed, but not decomposed.
---
 doc/lua-filters.md                    | 47 +++++++++++++++
 pandoc.cabal                          |  1 +
 src/Text/Pandoc/Lua/Init.hs           | 15 +++--
 src/Text/Pandoc/Lua/StackInstances.hs | 86 ++++++++++++++++++++++++++-
 test/command/lua-pandoc-state.lua     | 11 ++++
 test/command/lua-pandoc-state.md      | 14 +++++
 6 files changed, 168 insertions(+), 6 deletions(-)
 create mode 100644 test/command/lua-pandoc-state.lua
 create mode 100644 test/command/lua-pandoc-state.md

diff --git a/doc/lua-filters.md b/doc/lua-filters.md
index 810b9d606..57eb4e79c 100644
--- a/doc/lua-filters.md
+++ b/doc/lua-filters.md
@@ -171,6 +171,12 @@ variables.
 :   The name used to involve the filter. This value can be used
     to find files relative to the script file. This variable is
     also set in custom writers.
+    
+`PANDOC_STATE`
+:   The state shared by all readers and writers. It is used by
+    pandoc to collect and pass information. The value of this
+    variable is of type [CommonState](#type-ref-CommonState) and
+    is read-only.
 
 # Pandoc Module
 
@@ -1280,6 +1286,46 @@ Pandoc reader options
 :   track changes setting for docx; one of `AcceptChanges`,
     `RejectChanges`, and `AllChanges` (string)
 
+## CommonState {#type-ref-CommonState}
+
+The state used by pandoc to collect information and make it
+available to readers and writers.
+
+`input_files`
+:   List of input files from command line ([List] of strings)
+
+`output_file`
+:   Output file from command line (string or nil)
+
+`log`
+:   A list of log messages in reverse order ([List] of [LogMessage]s)
+
+`request_headers`
+:   Headers to add for HTTP requests; table with header names as
+    keys and header contents as value (table)
+
+`resource_path`
+:   Path to search for resources like included images ([List] of
+    strings)
+
+`source_url`
+:   Absolute URL or directory of first source file (string or
+    nil)
+
+`user_data_dir`
+:   Directory to search for data files (string or nil)
+
+`trace`
+:   Whether tracing messages are issued (boolean)
+
+`verbosity`
+:   Verbosity level; one of `INFO`, `WARNING`, `ERROR` (string)
+
+## LogMessage {#type-ref-LogMessage}
+
+A pandoc log message. Object have no fields, but can be converted
+to a string via `tostring`.
+
 [Block]: #type-ref-Block
 [List]: #module-pandoc.list
 [MetaValue]: #type-ref-MetaValue
@@ -1287,6 +1333,7 @@ Pandoc reader options
 [Attr]: #type-ref-Attr
 [Attributes]: #type-ref-Attributes
 [citations]: #type-ref-Citation
+[LogMessage]: #type-ref-LogMessage
 
 # Module text
 
diff --git a/pandoc.cabal b/pandoc.cabal
index 9480753ff..f09c0e9ba 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -191,6 +191,7 @@ extra-source-files:
                  test/command/SVG_logo.svg
                  test/command/corrupt.svg
                  test/command/inkscape-cube.svg
+                 test/command/lua-pandoc-state.lua
                  test/command/sub-file-chapter-1.tex
                  test/command/sub-file-chapter-2.tex
                  test/command/bar.tex
diff --git a/src/Text/Pandoc/Lua/Init.hs b/src/Text/Pandoc/Lua/Init.hs
index 8449d736d..78fb6204e 100644
--- a/src/Text/Pandoc/Lua/Init.hs
+++ b/src/Text/Pandoc/Lua/Init.hs
@@ -43,8 +43,8 @@ import Data.Version (Version (versionBranch))
 import Foreign.Lua (Lua)
 import GHC.IO.Encoding (getForeignEncoding, setForeignEncoding, utf8)
 import Paths_pandoc (version)
-import Text.Pandoc.Class (PandocIO, getCommonState, getUserDataDir, getMediaBag,
-                          setMediaBag)
+import Text.Pandoc.Class (CommonState, PandocIO, getCommonState,
+                          getUserDataDir, getMediaBag, setMediaBag)
 import Text.Pandoc.Definition (pandocTypesVersion)
 import Text.Pandoc.Lua.Packages (LuaPackageParams (..),
                                  installPandocPackageSearcher)
@@ -61,9 +61,12 @@ newtype LuaException = LuaException String deriving (Show)
 -- initialization.
 runPandocLua :: Lua a -> PandocIO (Either LuaException a)
 runPandocLua luaOp = do
+  commonState <- getCommonState
   luaPkgParams <- luaPackageParams
   enc <- liftIO $ getForeignEncoding <* setForeignEncoding utf8
-  res <- liftIO $ Lua.runEither (initLuaState luaPkgParams *> luaOp)
+  res <- liftIO . Lua.runEither $ do
+    initLuaState commonState luaPkgParams
+    luaOp
   liftIO $ setForeignEncoding enc
   newMediaBag <- liftIO (readIORef (luaPkgMediaBag luaPkgParams))
   setMediaBag newMediaBag
@@ -84,14 +87,16 @@ luaPackageParams = do
     }
 
 -- Initialize the lua state with all required values
-initLuaState :: LuaPackageParams -> Lua ()
-initLuaState luaPkgParams = do
+initLuaState :: CommonState -> LuaPackageParams -> Lua ()
+initLuaState commonState luaPkgParams = do
   Lua.openlibs
   Lua.preloadTextModule "text"
   Lua.push (versionBranch version)
   Lua.setglobal "PANDOC_VERSION"
   Lua.push (versionBranch pandocTypesVersion)
   Lua.setglobal "PANDOC_API_VERSION"
+  Lua.push commonState
+  Lua.setglobal "PANDOC_STATE"
   installPandocPackageSearcher luaPkgParams
   loadScriptFromDataDir (luaPkgDataDir luaPkgParams) "init.lua"
   putConstructorsInRegistry
diff --git a/src/Text/Pandoc/Lua/StackInstances.hs b/src/Text/Pandoc/Lua/StackInstances.hs
index 2d7b9c583..c0f5fdd59 100644
--- a/src/Text/Pandoc/Lua/StackInstances.hs
+++ b/src/Text/Pandoc/Lua/StackInstances.hs
@@ -38,14 +38,18 @@ import Prelude
 import Control.Applicative ((<|>))
 import Data.Data (showConstr, toConstr)
 import Foreign.Lua (Lua, Peekable, Pushable, StackIndex)
+import Foreign.Lua.Types.Peekable (reportValueOnFailure)
 import Foreign.Lua.Userdata ( ensureUserdataMetatable, pushAnyWithMetatable
-                            , metatableName)
+                            , toAnyWithName, metatableName)
+import Text.Pandoc.Class (CommonState (..))
 import Text.Pandoc.Definition
 import Text.Pandoc.Extensions (Extensions)
+import Text.Pandoc.Logging (LogMessage, showLogMessage)
 import Text.Pandoc.Lua.Util (defineHowTo, pushViaConstructor)
 import Text.Pandoc.Options (ReaderOptions (..), TrackChanges)
 import Text.Pandoc.Shared (Element (Blk, Sec))
 
+import qualified Data.Map as Map
 import qualified Data.Set as Set
 import qualified Foreign.Lua as Lua
 import qualified Text.Pandoc.Lua.Util as LuaUtil
@@ -386,5 +390,85 @@ instance Pushable ReaderOptions where
 -- | Dummy type to allow values of arbitrary Lua type.
 newtype AnyValue = AnyValue StackIndex
 
+--
+-- TODO: Much of the following should be abstracted, factored out
+-- and go into HsLua.
+--
+
 instance Peekable AnyValue where
   peek = return . AnyValue
+
+-- | Name used by Lua for the @CommonState@ type.
+commonStateTypeName :: String
+commonStateTypeName = "Pandoc CommonState"
+
+instance Peekable CommonState where
+  peek idx = reportValueOnFailure commonStateTypeName
+             (`toAnyWithName` commonStateTypeName) idx
+
+instance Pushable CommonState where
+  push st = pushAnyWithMetatable pushCommonStateMetatable st
+   where
+    pushCommonStateMetatable = ensureUserdataMetatable commonStateTypeName $ do
+      LuaUtil.addFunction "__index" indexCommonState
+      LuaUtil.addFunction "__pairs" pairsCommonState
+
+indexCommonState :: CommonState -> AnyValue -> Lua Lua.NumResults
+indexCommonState st (AnyValue idx) = Lua.ltype idx >>= \case
+  Lua.TypeString -> 1 <$ (Lua.peek idx >>= pushField)
+  _ -> 1 <$ Lua.pushnil
+ where
+  pushField :: String -> Lua ()
+  pushField name = case lookup name commonStateFields of
+    Just pushValue -> pushValue st
+    Nothing -> Lua.pushnil
+
+pairsCommonState :: CommonState -> Lua Lua.NumResults
+pairsCommonState st = do
+  Lua.pushHaskellFunction nextFn
+  Lua.pushnil
+  Lua.pushnil
+  return 3
+ where
+  nextFn :: AnyValue -> AnyValue -> Lua Lua.NumResults
+  nextFn _ (AnyValue idx) =
+    Lua.ltype idx >>= \case
+      Lua.TypeNil -> case commonStateFields of
+        []  -> 2 <$ (Lua.pushnil *> Lua.pushnil)
+        (key, pushValue):_ -> 2 <$ (Lua.push key *> pushValue st)
+      Lua.TypeString -> do
+        key <- Lua.peek idx
+        case tail $ dropWhile ((/= key) . fst) commonStateFields of
+          []                     -> 2 <$ (Lua.pushnil *> Lua.pushnil)
+          (nextKey, pushValue):_ -> 2 <$ (Lua.push nextKey *> pushValue st)
+      _ -> 2 <$ (Lua.pushnil *> Lua.pushnil)
+
+commonStateFields :: [(String, CommonState -> Lua ())]
+commonStateFields =
+  [ ("input_files", Lua.push . stInputFiles)
+  , ("output_file", Lua.push . Lua.Optional . stOutputFile)
+  , ("log", Lua.push . stLog)
+  , ("request_headers", Lua.push . Map.fromList . stRequestHeaders)
+  , ("resource_path", Lua.push . stResourcePath)
+  , ("source_url", Lua.push . Lua.Optional . stSourceURL)
+  , ("user_data_dir", Lua.push . Lua.Optional . stUserDataDir)
+  , ("trace", Lua.push . stTrace)
+  , ("verbosity", Lua.push . show . stVerbosity)
+  ]
+
+-- | Name used by Lua for the @CommonState@ type.
+logMessageTypeName :: String
+logMessageTypeName = "Pandoc LogMessage"
+
+instance Peekable LogMessage where
+  peek idx = reportValueOnFailure logMessageTypeName
+             (`toAnyWithName` logMessageTypeName) idx
+
+instance Pushable LogMessage where
+  push msg = pushAnyWithMetatable pushLogMessageMetatable msg
+   where
+    pushLogMessageMetatable = ensureUserdataMetatable logMessageTypeName $
+      LuaUtil.addFunction "__tostring" tostringLogMessage
+
+tostringLogMessage :: LogMessage -> Lua String
+tostringLogMessage = return . showLogMessage
diff --git a/test/command/lua-pandoc-state.lua b/test/command/lua-pandoc-state.lua
new file mode 100644
index 000000000..5282a4c29
--- /dev/null
+++ b/test/command/lua-pandoc-state.lua
@@ -0,0 +1,11 @@
+function report (what, value)
+  print(string.format('%16s: %s', what, value))
+end
+report('# input files', #PANDOC_STATE.input_files)
+report('output file', PANDOC_STATE.output_file)
+report('# request header', #PANDOC_STATE.request_headers)
+report('resource path', table.concat(PANDOC_STATE.resource_path, ', '))
+report('source URL', PANDOC_STATE.source_url)
+report('user data dir', PANDOC_STATE.user_data_dir and 'defined' or 'unset')
+report('trace', PANDOC_STATE.trace)
+report('verbosity', PANDOC_STATE.verbosity)
diff --git a/test/command/lua-pandoc-state.md b/test/command/lua-pandoc-state.md
new file mode 100644
index 000000000..33045f64a
--- /dev/null
+++ b/test/command/lua-pandoc-state.md
@@ -0,0 +1,14 @@
+```
+% pandoc --lua-filter=command/lua-pandoc-state.lua
+Hello
+^D
+   # input files: 0
+     output file: nil
+# request header: 0
+   resource path: .
+      source URL: nil
+   user data dir: defined
+           trace: false
+       verbosity: WARNING
+<p>Hello</p>
+```