From 83b5b79c0e4f073198b5af11b9e8a0a4471fcd41 Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Wed, 8 Dec 2021 19:06:48 +0100 Subject: Custom reader: pass list of sources instead of concatenated text The first argument passed to Lua `Reader` functions is no longer a plain string but a richer data structure. The structure can easily be converted to a string by applying `tostring`, but is also a list with elements that contain each the *text* and *name* of each input source as a property of the respective name. A small example is added to the custom reader documentation, showcasing its use in a reader that creates a syntax-highlighted code block for each source code file passed as input. Existing readers must be updated. --- src/Text/Pandoc/Lua/Marshal/Sources.hs | 46 ++++++++++++++++++++++++++++++++++ src/Text/Pandoc/Lua/Orphans.hs | 5 ++++ src/Text/Pandoc/Readers/Custom.hs | 10 +++----- 3 files changed, 55 insertions(+), 6 deletions(-) create mode 100644 src/Text/Pandoc/Lua/Marshal/Sources.hs (limited to 'src') diff --git a/src/Text/Pandoc/Lua/Marshal/Sources.hs b/src/Text/Pandoc/Lua/Marshal/Sources.hs new file mode 100644 index 000000000..7b5262ab5 --- /dev/null +++ b/src/Text/Pandoc/Lua/Marshal/Sources.hs @@ -0,0 +1,46 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} +{- | +Module : Text.Pandoc.Lua.Marshaling.Sources +Copyright : © 2021 Albert Krewinkel +License : GNU GPL, version 2 or above +Maintainer : Albert Krewinkel + +Marshal 'Sources'. +-} +module Text.Pandoc.Lua.Marshal.Sources + ( pushSources + ) where + +import Data.Text (Text) +import HsLua as Lua +import Text.Pandoc.Lua.Marshal.List (newListMetatable) +import Text.Pandoc.Sources (Sources (..)) +import Text.Parsec (SourcePos, sourceName) + +-- | Pushes the 'Sources' as a list of lazy Lua objects. +pushSources :: LuaError e => Pusher e Sources +pushSources (Sources srcs) = do + pushList (pushUD typeSource) srcs + newListMetatable "pandoc Sources" $ do + pushName "__tostring" + pushHaskellFunction $ do + sources <- forcePeek $ peekList (peekUD typeSource) (nthBottom 1) + pushText . mconcat $ map snd sources + return 1 + rawset (nth 3) + setmetatable (nth 2) + +-- | Source object type. +typeSource :: LuaError e => DocumentedType e (SourcePos, Text) +typeSource = deftype "pandoc input source" + [ operation Tostring $ lambda + ### liftPure snd + <#> udparam typeSource "srcs" "Source to print in native format" + =#> functionResult pushText "string" "Haskell representation" + ] + [ readonly "name" "source name" + (pushString, sourceName . fst) + , readonly "text" "source text" + (pushText, snd) + ] diff --git a/src/Text/Pandoc/Lua/Orphans.hs b/src/Text/Pandoc/Lua/Orphans.hs index eef05bd27..d5b8f2c5d 100644 --- a/src/Text/Pandoc/Lua/Orphans.hs +++ b/src/Text/Pandoc/Lua/Orphans.hs @@ -22,7 +22,9 @@ import Text.Pandoc.Lua.Marshal.CommonState () import Text.Pandoc.Lua.Marshal.Context () import Text.Pandoc.Lua.Marshal.PandocError() import Text.Pandoc.Lua.Marshal.ReaderOptions () +import Text.Pandoc.Lua.Marshal.Sources (pushSources) import Text.Pandoc.Lua.ErrorConversion () +import Text.Pandoc.Sources (Sources) instance Pushable Pandoc where push = pushPandoc @@ -109,3 +111,6 @@ instance Peekable Version where instance {-# OVERLAPPING #-} Peekable Attr where peek = forcePeek . peekAttr + +instance Pushable Sources where + push = pushSources diff --git a/src/Text/Pandoc/Readers/Custom.hs b/src/Text/Pandoc/Readers/Custom.hs index d7336012b..7b6c99ed8 100644 --- a/src/Text/Pandoc/Readers/Custom.hs +++ b/src/Text/Pandoc/Readers/Custom.hs @@ -17,7 +17,6 @@ Supports custom parsers written in Lua which produce a Pandoc AST. module Text.Pandoc.Readers.Custom ( readCustom ) where import Control.Exception import Control.Monad (when) -import Data.Text (Text) import HsLua as Lua hiding (Operation (Div), render) import HsLua.Class.Peekable (PeekError) import Control.Monad.IO.Class (MonadIO) @@ -26,13 +25,13 @@ import Text.Pandoc.Lua (Global (..), runLua, setGlobals) import Text.Pandoc.Lua.Util (dofileWithTraceback) import Text.Pandoc.Options import Text.Pandoc.Class (PandocMonad) -import Text.Pandoc.Sources (ToSources(..), sourcesToText) +import Text.Pandoc.Sources (Sources, ToSources(..)) -- | Convert custom markup to Pandoc. readCustom :: (PandocMonad m, MonadIO m, ToSources s) => FilePath -> ReaderOptions -> s -> m Pandoc -readCustom luaFile opts sources = do - let input = sourcesToText $ toSources sources +readCustom luaFile opts srcs = do + let input = toSources srcs let globals = [ PANDOC_SCRIPT_FILE luaFile ] res <- runLua $ do setGlobals globals @@ -47,8 +46,7 @@ readCustom luaFile opts sources = do Right doc -> return doc parseCustom :: forall e. PeekError e - => Text + => Sources -> ReaderOptions -> LuaE e Pandoc parseCustom = invoke @e "Reader" - -- cgit v1.2.3