Skip to content

Commit

Permalink
Lua: provide global PANDOC_WRITER_OPTIONS [API change]
Browse files Browse the repository at this point in the history
API changes:

- The function T.P.Filter.applyFilters now takes a filter
  environment of type `Environment`, instead of a ReaderOptions value.
  The `Environment` type is exported from `T.P.Filter` and allows to
  combine ReaderOptions and WriterOptions in a single value.

- Global, exported from T.P.Lua, has a new type constructor
  `PANDOC_WRITER_OPTIONS`.

Closes: jgm#5221
  • Loading branch information
tarleb committed Jan 1, 2022
1 parent 13740c4 commit 7b5f88a
Show file tree
Hide file tree
Showing 9 changed files with 318 additions and 20 deletions.
5 changes: 5 additions & 0 deletions doc/lua-filters.md
Original file line number Diff line number Diff line change
Expand Up @@ -262,6 +262,11 @@ variables.
`PANDOC_READER_OPTIONS`
: Table of the options which were provided to the parser.

`PANDOC_WRITER_OPTIONS`
: Table of the options that will be passed to the writer.
While the object can be modified, the changes will **not**
be picked up by pandoc.

`PANDOC_VERSION`
: Contains the pandoc version as a [Version] object which
behaves like a numerically indexed table, most significant
Expand Down
2 changes: 2 additions & 0 deletions pandoc.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -631,6 +631,7 @@ library
Text.Pandoc.Class.PandocIO,
Text.Pandoc.Class.PandocPure,
Text.Pandoc.Class.Sandbox,
Text.Pandoc.Filter.Environment,
Text.Pandoc.Filter.JSON,
Text.Pandoc.Filter.Lua,
Text.Pandoc.Filter.Path,
Expand Down Expand Up @@ -705,6 +706,7 @@ library
Text.Pandoc.Lua.Marshal.ReaderOptions,
Text.Pandoc.Lua.Marshal.Reference,
Text.Pandoc.Lua.Marshal.Sources,
Text.Pandoc.Lua.Marshal.WriterOptions,
Text.Pandoc.Lua.Module.MediaBag,
Text.Pandoc.Lua.Module.Pandoc,
Text.Pandoc.Lua.Module.System,
Expand Down
6 changes: 4 additions & 2 deletions src/Text/Pandoc/App.hs
Original file line number Diff line number Diff line change
Expand Up @@ -60,7 +60,8 @@ import Text.Pandoc.App.CommandLineOptions (parseOptions, parseOptionsFromArgs,
options)
import Text.Pandoc.App.OutputSettings (OutputSettings (..), optToOutputSettings)
import Text.Collate.Lang (Lang (..), parseLang)
import Text.Pandoc.Filter (Filter (JSONFilter, LuaFilter), applyFilters)
import Text.Pandoc.Filter (Filter (JSONFilter, LuaFilter), Environment (..),
applyFilters)
import Text.Pandoc.PDF (makePDF)
import Text.Pandoc.SelfContained (makeSelfContained)
import Text.Pandoc.Shared (eastAsianLineBreakFilter, stripEmptyParagraphs,
Expand Down Expand Up @@ -280,6 +281,7 @@ convertWithOpts opts = do
maybe id (setMeta "citation-abbreviations")
(optCitationAbbreviations opts) $ mempty

let filterEnv = Environment readerOpts writerOptions
doc <- (case reader of
TextReader r
| readerNameBase == "json" ->
Expand All @@ -305,7 +307,7 @@ convertWithOpts opts = do
>=> return . adjustMetadata (<> optMetadata opts)
>=> return . adjustMetadata (<> cslMetadata)
>=> applyTransforms transforms
>=> applyFilters readerOpts filters [T.unpack format]
>=> applyFilters filterEnv filters [T.unpack format]
>=> maybe return extractMedia (optExtractMedia opts)
)

Expand Down
12 changes: 6 additions & 6 deletions src/Text/Pandoc/Filter.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Filter
Expand All @@ -15,6 +14,7 @@ Programmatically modifications of pandoc documents.
-}
module Text.Pandoc.Filter
( Filter (..)
, Environment (..)
, applyFilters
) where

Expand All @@ -23,7 +23,7 @@ import Data.Aeson
import GHC.Generics (Generic)
import Text.Pandoc.Class (report, getVerbosity, PandocMonad)
import Text.Pandoc.Definition (Pandoc)
import Text.Pandoc.Options (ReaderOptions)
import Text.Pandoc.Filter.Environment (Environment (..))
import Text.Pandoc.Logging
import Text.Pandoc.Citeproc (processCitations)
import qualified Text.Pandoc.Filter.JSON as JSONFilter
Expand Down Expand Up @@ -72,19 +72,19 @@ instance ToJSON Filter where

-- | Modify the given document using a filter.
applyFilters :: (PandocMonad m, MonadIO m)
=> ReaderOptions
=> Environment
-> [Filter]
-> [String]
-> Pandoc
-> m Pandoc
applyFilters ropts filters args d = do
applyFilters fenv filters args d = do
expandedFilters <- mapM expandFilterPath filters
foldM applyFilter d expandedFilters
where
applyFilter doc (JSONFilter f) =
withMessages f $ JSONFilter.apply ropts args f doc
withMessages f $ JSONFilter.apply fenv args f doc
applyFilter doc (LuaFilter f) =
withMessages f $ LuaFilter.apply ropts args f doc
withMessages f $ LuaFilter.apply fenv args f doc
applyFilter doc CiteprocFilter =
processCitations doc
withMessages f action = do
Expand Down
27 changes: 27 additions & 0 deletions src/Text/Pandoc/Filter/Environment.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,27 @@
{- |
Module : Text.Pandoc.Filter.Environment
Copyright : ©2020-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <[email protected]>
Stability : alpha
Portability : portable
Environment for pandoc filters.
-}
module Text.Pandoc.Filter.Environment
( Environment (..)
) where

import Data.Default (Default (def))
import Text.Pandoc.Options (ReaderOptions, WriterOptions)

-- | Environment in which a filter is run. This includes reader and
-- writer options.
data Environment = Environment
{ envReaderOptions :: ReaderOptions
, envWriterOptions :: WriterOptions
}

instance Default Environment where
def = Environment def def
11 changes: 6 additions & 5 deletions src/Text/Pandoc/Filter/JSON.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,25 +23,25 @@ import System.Directory (executable, doesFileExist, findExecutable,
import System.Environment (getEnvironment)
import System.Exit (ExitCode (..))
import System.FilePath ((</>), takeExtension)
import Text.Pandoc.Error (PandocError (PandocFilterError))
import Text.Pandoc.Definition (Pandoc)
import Text.Pandoc.Options (ReaderOptions)
import Text.Pandoc.Error (PandocError (PandocFilterError))
import Text.Pandoc.Filter.Environment (Environment (..))
import Text.Pandoc.Process (pipeProcess)
import Text.Pandoc.Shared (pandocVersion, tshow)
import qualified Control.Exception as E
import qualified Text.Pandoc.UTF8 as UTF8

apply :: MonadIO m
=> ReaderOptions
=> Environment
-> [String]
-> FilePath
-> Pandoc
-> m Pandoc
apply ropts args f = liftIO . externalFilter ropts f args

externalFilter :: MonadIO m
=> ReaderOptions -> FilePath -> [String] -> Pandoc -> m Pandoc
externalFilter ropts f args' d = liftIO $ do
=> Environment -> FilePath -> [String] -> Pandoc -> m Pandoc
externalFilter fenv f args' d = liftIO $ do
exists <- doesFileExist f
isExecutable <- if exists
then executable <$> getPermissions f
Expand All @@ -62,6 +62,7 @@ externalFilter ropts f args' d = liftIO $ do
mbExe <- findExecutable f'
when (isNothing mbExe) $
E.throwIO $ PandocFilterError fText (T.pack $ "Could not find executable " <> f')
let ropts = envReaderOptions fenv
env <- getEnvironment
let env' = Just
( ("PANDOC_VERSION", T.unpack pandocVersion)
Expand Down
9 changes: 5 additions & 4 deletions src/Text/Pandoc/Filter/Lua.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,25 +18,26 @@ import Text.Pandoc.Class (PandocMonad)
import Control.Monad.Trans (MonadIO)
import Text.Pandoc.Definition (Pandoc)
import Text.Pandoc.Error (PandocError (PandocFilterError, PandocLuaError))
import Text.Pandoc.Filter.Environment (Environment (..))
import Text.Pandoc.Lua (Global (..), runLua, runFilterFile, setGlobals)
import Text.Pandoc.Options (ReaderOptions)

-- | Run the Lua filter in @filterPath@ for a transformation to the
-- target format (first element in args). Pandoc uses Lua init files to
-- setup the Lua interpreter.
apply :: (PandocMonad m, MonadIO m)
=> ReaderOptions
=> Environment
-> [String]
-> FilePath
-> Pandoc
-> m Pandoc
apply ropts args fp doc = do
apply fenv args fp doc = do
let format = case args of
(x:_) -> x
_ -> error "Format not supplied for Lua filter"
runLua >=> forceResult fp $ do
setGlobals [ FORMAT $ T.pack format
, PANDOC_READER_OPTIONS ropts
, PANDOC_READER_OPTIONS (envReaderOptions fenv)
, PANDOC_WRITER_OPTIONS (envWriterOptions fenv)
, PANDOC_SCRIPT_FILE fp
]
runFilterFile fp doc
Expand Down
11 changes: 8 additions & 3 deletions src/Text/Pandoc/Lua/Global.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,8 +23,9 @@ import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.Marshal.CommonState (pushCommonState)
import Text.Pandoc.Lua.Marshal.Pandoc (pushPandoc)
import Text.Pandoc.Lua.Marshal.ReaderOptions (pushReaderOptionsReadonly)
import Text.Pandoc.Lua.Marshal.WriterOptions (pushWriterOptions)
import Text.Pandoc.Lua.Orphans ()
import Text.Pandoc.Options (ReaderOptions)
import Text.Pandoc.Options (ReaderOptions, WriterOptions)

import qualified Data.Text as Text

Expand All @@ -34,6 +35,7 @@ data Global =
| PANDOC_API_VERSION
| PANDOC_DOCUMENT Pandoc
| PANDOC_READER_OPTIONS ReaderOptions
| PANDOC_WRITER_OPTIONS WriterOptions
| PANDOC_SCRIPT_FILE FilePath
| PANDOC_STATE CommonState
| PANDOC_VERSION
Expand All @@ -47,7 +49,7 @@ setGlobal :: Global -> LuaE PandocError ()
setGlobal global = case global of
-- This could be simplified if Global was an instance of Data.
FORMAT format -> do
Lua.push format
Lua.pushText format
Lua.setglobal "FORMAT"
PANDOC_API_VERSION -> do
pushVersion pandocTypesVersion
Expand All @@ -58,8 +60,11 @@ setGlobal global = case global of
PANDOC_READER_OPTIONS ropts -> do
pushReaderOptionsReadonly ropts
Lua.setglobal "PANDOC_READER_OPTIONS"
PANDOC_WRITER_OPTIONS wopts -> do
pushWriterOptions wopts
Lua.setglobal "PANDOC_WRITER_OPTIONS"
PANDOC_SCRIPT_FILE filePath -> do
Lua.push filePath
Lua.pushString filePath
Lua.setglobal "PANDOC_SCRIPT_FILE"
PANDOC_STATE commonState -> do
pushCommonState commonState
Expand Down
Loading

0 comments on commit 7b5f88a

Please sign in to comment.