Lua filters: make PANDOC_READER_OPTIONS available
The options which were used to read the document are made available to Lua filters via the `PANDOC_READER_OPTIONS` global.
This commit is contained in:
parent
624abeec5c
commit
5b852f8d2a
4 changed files with 63 additions and 11 deletions
|
@ -855,12 +855,12 @@ applyFilter :: ReaderOptions
|
|||
-> Filter
|
||||
-> Pandoc
|
||||
-> PandocIO Pandoc
|
||||
applyFilter _ropts args (LuaFilter f) d = do
|
||||
applyFilter ropts args (LuaFilter f) d = do
|
||||
f' <- expandFilterPath f
|
||||
let format = case args of
|
||||
(x:_) -> x
|
||||
_ -> error "Format not supplied for lua filter"
|
||||
res <- runLuaFilter f' format d
|
||||
res <- runLuaFilter ropts f' format d
|
||||
case res of
|
||||
Right x -> return x
|
||||
Left (LuaException s) -> E.throw (PandocFilterError f s)
|
||||
|
|
|
@ -39,21 +39,22 @@ import Text.Pandoc.Definition (Pandoc)
|
|||
import Text.Pandoc.Lua.Filter (LuaFilter, walkMWithLuaFilter)
|
||||
import Text.Pandoc.Lua.Init (runPandocLua)
|
||||
import Text.Pandoc.Lua.Util (popValue)
|
||||
import Text.Pandoc.Options (ReaderOptions)
|
||||
import qualified Foreign.Lua as Lua
|
||||
|
||||
-- | Run the Lua filter in @filterPath@ for a transformation to target
|
||||
-- format @format@. Pandoc uses Lua init files to setup the Lua
|
||||
-- interpreter.
|
||||
runLuaFilter :: FilePath -> String
|
||||
runLuaFilter :: ReaderOptions -> FilePath -> String
|
||||
-> Pandoc -> PandocIO (Either LuaException Pandoc)
|
||||
runLuaFilter filterPath format doc =
|
||||
runPandocLua (runLuaFilter' filterPath format doc)
|
||||
runLuaFilter ropts filterPath format doc =
|
||||
runPandocLua (runLuaFilter' ropts filterPath format doc)
|
||||
|
||||
runLuaFilter' :: FilePath -> String
|
||||
runLuaFilter' :: ReaderOptions -> FilePath -> String
|
||||
-> Pandoc -> Lua Pandoc
|
||||
runLuaFilter' filterPath format pd = do
|
||||
-- store module in global "pandoc"
|
||||
runLuaFilter' ropts filterPath format pd = do
|
||||
registerFormat
|
||||
registerReaderOptions
|
||||
top <- Lua.gettop
|
||||
stat <- Lua.dofile filterPath
|
||||
if stat /= OK
|
||||
|
@ -73,5 +74,9 @@ runLuaFilter' filterPath format pd = do
|
|||
push format
|
||||
Lua.setglobal "FORMAT"
|
||||
|
||||
registerReaderOptions = do
|
||||
push ropts
|
||||
Lua.setglobal "PANDOC_READER_OPTIONS"
|
||||
|
||||
runAll :: [LuaFilter] -> Pandoc -> Lua Pandoc
|
||||
runAll = foldr ((>=>) . walkMWithLuaFilter) return
|
||||
|
|
|
@ -16,8 +16,9 @@ You should have received a copy of the GNU General Public License
|
|||
along with this program; if not, write to the Free Software
|
||||
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
||||
-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||
{- |
|
||||
Module : Text.Pandoc.Lua.StackInstances
|
||||
|
@ -34,13 +35,18 @@ module Text.Pandoc.Lua.StackInstances () where
|
|||
|
||||
import Control.Applicative ((<|>))
|
||||
import Control.Monad (when)
|
||||
import Data.Data (showConstr, toConstr)
|
||||
import Data.Foldable (forM_)
|
||||
import Foreign.Lua (FromLuaStack (peek), Lua, LuaInteger, LuaNumber, StackIndex,
|
||||
ToLuaStack (push), Type (..), throwLuaError, tryLua)
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Extensions (Extensions)
|
||||
import Text.Pandoc.Lua.Util (adjustIndexBy, getTable, pushViaConstructor)
|
||||
import Text.Pandoc.Options (ReaderOptions (..), TrackChanges)
|
||||
import Text.Pandoc.Shared (Element (Blk, Sec), safeRead)
|
||||
|
||||
import qualified Foreign.Lua as Lua
|
||||
import qualified Data.Set as Set
|
||||
import qualified Text.Pandoc.Lua.Util as LuaUtil
|
||||
|
||||
instance ToLuaStack Pandoc where
|
||||
|
@ -332,3 +338,43 @@ instance ToLuaStack Element where
|
|||
Lua.push "__index"
|
||||
Lua.pushvalue (-2)
|
||||
Lua.rawset (-3)
|
||||
|
||||
|
||||
--
|
||||
-- Reader Options
|
||||
--
|
||||
instance ToLuaStack Extensions where
|
||||
push exts = push (show exts)
|
||||
|
||||
instance ToLuaStack TrackChanges where
|
||||
push = push . showConstr . toConstr
|
||||
|
||||
instance ToLuaStack a => ToLuaStack (Set.Set a) where
|
||||
push set = do
|
||||
Lua.newtable
|
||||
forM_ set (`LuaUtil.addValue` True)
|
||||
|
||||
instance ToLuaStack ReaderOptions where
|
||||
push ro = do
|
||||
let ReaderOptions
|
||||
(extensions :: Extensions)
|
||||
(standalone :: Bool)
|
||||
(columns :: Int)
|
||||
(tabStop :: Int)
|
||||
(indentedCodeClasses :: [String])
|
||||
(abbreviations :: Set.Set String)
|
||||
(defaultImageExtension :: String)
|
||||
(trackChanges :: TrackChanges)
|
||||
(stripComments :: Bool)
|
||||
= ro
|
||||
Lua.newtable
|
||||
LuaUtil.addValue "extensions" extensions
|
||||
LuaUtil.addValue "standalone" standalone
|
||||
LuaUtil.addValue "columns" columns
|
||||
LuaUtil.addValue "tabStop" tabStop
|
||||
LuaUtil.addValue "indentedCodeClasses" indentedCodeClasses
|
||||
LuaUtil.addValue "abbreviations" abbreviations
|
||||
LuaUtil.addValue "defaultImageExtension" defaultImageExtension
|
||||
LuaUtil.addValue "trackChanges" trackChanges
|
||||
LuaUtil.addValue "stripComments" stripComments
|
||||
|
||||
|
|
|
@ -14,6 +14,7 @@ import Text.Pandoc.Builder (bulletList, divWith, doc, doubleQuoted, emph,
|
|||
import Text.Pandoc.Class (runIOorExplode, setUserDataDir)
|
||||
import Text.Pandoc.Definition (Block, Inline, Meta, Pandoc, pandocTypesVersion)
|
||||
import Text.Pandoc.Lua (runLuaFilter, runPandocLua)
|
||||
import Text.Pandoc.Options (def)
|
||||
import Text.Pandoc.Shared (pandocVersion)
|
||||
|
||||
import qualified Foreign.Lua as Lua
|
||||
|
@ -128,7 +129,7 @@ assertFilterConversion :: String -> FilePath -> Pandoc -> Pandoc -> Assertion
|
|||
assertFilterConversion msg filterPath docIn docExpected = do
|
||||
docEither <- runIOorExplode $ do
|
||||
setUserDataDir (Just "../data")
|
||||
runLuaFilter ("lua" </> filterPath) [] docIn
|
||||
runLuaFilter def ("lua" </> filterPath) [] docIn
|
||||
case docEither of
|
||||
Left _ -> fail "lua filter failed"
|
||||
Right docRes -> assertEqual msg docExpected docRes
|
||||
|
|
Loading…
Add table
Reference in a new issue