diff options
| author | Albert Krewinkel <[email protected]> | 2022-10-02 21:00:18 +0200 |
|---|---|---|
| committer | John MacFarlane <[email protected]> | 2022-10-03 08:47:32 -0700 |
| commit | 309163f5bc88884b2f021ce480537d1f8c57e068 (patch) | |
| tree | 27e998c87c9f0de613850d3c6c12b3b6f60466da /pandoc-lua-engine | |
| parent | 3b0e70072023d519cfb97d25ab668cf0284a5e24 (diff) | |
[API Change] Base custom writers on Writer type.
The `T.P.Lua.writeCustom` function changed to allow either a TextWriter
or ByteStringWriter to be returned. The global variables
`PANDOC_DOCUMENT` and `PANDOC_WRITER_OPTIONS` are no longer set when the
writer script is loaded. Both variables are still set in classic writers
before the conversion is started, so they can be used when they are
wrapped in functions.
Diffstat (limited to 'pandoc-lua-engine')
| -rw-r--r-- | pandoc-lua-engine/src/Text/Pandoc/Lua/Writer.hs | 46 | ||||
| -rw-r--r-- | pandoc-lua-engine/test/Tests/Lua/Writer.hs | 10 |
2 files changed, 37 insertions, 19 deletions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer.hs index f216ea63b..8dbae9eae 100644 --- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer.hs +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer.hs @@ -1,5 +1,6 @@ {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE TypeApplications #-} {- | Module : Text.Pandoc.Lua.Writer Copyright : Copyright (C) 2012-2022 John MacFarlane @@ -17,26 +18,28 @@ module Text.Pandoc.Lua.Writer import Control.Exception import Control.Monad ((<=<)) +import Data.Default (def) import Data.Maybe (fromMaybe) -import Data.Text (Text) import HsLua +import HsLua.Core.Run (newGCManagedState, withGCManagedState) import Control.Monad.IO.Class (MonadIO) import Text.Pandoc.Class (PandocMonad, findFileWithDataFallback) -import Text.Pandoc.Definition (Pandoc (..)) +import Text.Pandoc.Error (PandocError) import Text.Pandoc.Lua.Global (Global (..), setGlobals) -import Text.Pandoc.Lua.Init (runLua) -import Text.Pandoc.Options (WriterOptions) +import Text.Pandoc.Lua.Init (runLuaWith) +import Text.Pandoc.Writers (Writer (..)) import qualified Text.Pandoc.Lua.Writer.Classic as Classic -- | Convert Pandoc to custom markup. writeCustom :: (PandocMonad m, MonadIO m) - => FilePath -> WriterOptions -> Pandoc -> m Text -writeCustom luaFile opts doc = do + => FilePath -> m (Writer m) +writeCustom luaFile = do + luaState <- liftIO newGCManagedState luaFile' <- fromMaybe luaFile <$> findFileWithDataFallback "writers" luaFile - either throw pure <=< runLua $ do - setGlobals [ PANDOC_DOCUMENT doc + either throw pure <=< runLuaWith luaState $ do + setGlobals [ PANDOC_DOCUMENT mempty , PANDOC_SCRIPT_FILE luaFile' - , PANDOC_WRITER_OPTIONS opts + , PANDOC_WRITER_OPTIONS def ] dofileTrace luaFile' >>= \case OK -> pure () @@ -50,14 +53,23 @@ writeCustom luaFile opts doc = do pushName x rawget (nth 2) <* remove (nth 2) -- remove global table + let writerField = "PANDOC Writer function" + rawgetglobal "Writer" >>= \case TypeNil -> do + -- Neither `Writer` nor `BinaryWriter` are defined. Try to + -- use the file as a classic writer. pop 1 -- remove nil - Classic.runCustom opts doc - _ -> do - -- Writer on top of the stack. Call it with document and writer - -- options as arguments. - push doc - push opts - callTrace 2 1 - forcePeek $ peekText top + return . TextWriter $ \opts doc -> + liftIO $ withGCManagedState luaState $ do + Classic.runCustom @PandocError opts doc + _ -> do + -- New-type text writer. Writer function is on top of the stack. + setfield registryindex writerField + return . TextWriter $ \opts doc -> + liftIO $ withGCManagedState luaState $ do + getfield registryindex writerField + push doc + push opts + callTrace 2 1 + forcePeek @PandocError $ peekText top diff --git a/pandoc-lua-engine/test/Tests/Lua/Writer.hs b/pandoc-lua-engine/test/Tests/Lua/Writer.hs index 4086b9768..80d743dd5 100644 --- a/pandoc-lua-engine/test/Tests/Lua/Writer.hs +++ b/pandoc-lua-engine/test/Tests/Lua/Writer.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE LambdaCase #-} {- | Module : Tests.Lua.Writer Copyright : © 2019-2022 Albert Krewinkel @@ -15,6 +16,7 @@ import Data.Default (Default (def)) import Text.Pandoc.Class (runIOorExplode, readFileStrict) import Text.Pandoc.Lua (writeCustom) import Text.Pandoc.Readers (readNative) +import Text.Pandoc.Writers (Writer (TextWriter)) import Test.Tasty (TestTree) import Test.Tasty.Golden (goldenVsString) @@ -28,7 +30,9 @@ tests = (runIOorExplode $ do source <- UTF8.toText <$> readFileStrict "testsuite.native" doc <- readNative def source - txt <- writeCustom "sample.lua" def doc + txt <- writeCustom "sample.lua" >>= \case + TextWriter f -> f def doc + _ -> error "Expected a text writer" pure $ BL.fromStrict (UTF8.fromText txt)) , goldenVsString "tables testsuite" @@ -36,6 +40,8 @@ tests = (runIOorExplode $ do source <- UTF8.toText <$> readFileStrict "tables.native" doc <- readNative def source - txt <- writeCustom "sample.lua" def doc + txt <- writeCustom "sample.lua" >>= \case + TextWriter f -> f def doc + _ -> error "Expected a text writer" pure $ BL.fromStrict (UTF8.fromText txt)) ] |
