{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Text.Pandoc.Lua.Module.Pandoc
( documentedModule
) where
import Prelude hiding (read)
import Control.Applicative ((<|>))
import Control.Monad (foldM, forM_, when)
import Control.Monad.Catch (catch, handle, throwM)
import Control.Monad.Except (MonadError (throwError))
import Data.Data (Data, dataTypeConstrs, dataTypeOf, showConstr)
import Data.Default (Default (..))
import Data.Maybe (fromMaybe)
import Data.Proxy (Proxy (Proxy))
import Data.Text.Encoding.Error (UnicodeException)
import Data.Version (makeVersion)
import HsLua
import System.Exit (ExitCode (..))
import Text.Pandoc.Class ( PandocMonad, FileInfo (..), FileTree
, addToFileTree, getCurrentTime
, insertInFileTree, sandboxWithFileTree
)
import Text.Pandoc.Definition
import Text.Pandoc.Error (PandocError (..))
import Text.Pandoc.Format (FlavoredFormat, parseFlavoredFormat)
import Text.Pandoc.Lua.Orphans ()
import Text.Pandoc.Lua.Marshal.AST
import Text.Pandoc.Lua.Marshal.Format (peekFlavoredFormat)
import Text.Pandoc.Lua.Marshal.Filter (peekFilter)
import Text.Pandoc.Lua.Marshal.ReaderOptions ( peekReaderOptions
, pushReaderOptions)
import Text.Pandoc.Lua.Marshal.Sources (peekSources)
import Text.Pandoc.Lua.Marshal.WriterOptions ( peekWriterOptions
, pushWriterOptions)
import Text.Pandoc.Lua.Module.Utils (sha1)
import Text.Pandoc.Lua.PandocLua (PandocLua (unPandocLua))
import Text.Pandoc.Lua.Writer.Classic (runCustom)
import Text.Pandoc.Options ( ReaderOptions (readerExtensions)
, WriterOptions (writerExtensions) )
import Text.Pandoc.Process (pipeProcess)
import Text.Pandoc.Readers (Reader (..), getReader, readers)
import Text.Pandoc.Sources (toSources)
import Text.Pandoc.Writers (Writer (..), getWriter, writers)
import qualified HsLua as Lua
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BSL
import qualified Data.Set as Set
import qualified Data.Text as T
import qualified Text.Pandoc.UTF8 as UTF8
documentedModule :: Module PandocError
documentedModule :: Module PandocError
documentedModule = Module
{ moduleName :: Name
moduleName = Name
"pandoc"
, moduleDescription :: Text
moduleDescription = [Text] -> Text
T.unlines
[ Text
"Fields and functions for pandoc scripts; includes constructors for"
, Text
"document tree elements, functions to parse text in a given"
, Text
"format, and functions to filter and modify a subtree."
]
, moduleFields :: [Field PandocError]
moduleFields = Field PandocError
readersField Field PandocError -> [Field PandocError] -> [Field PandocError]
forall a. a -> [a] -> [a]
: Field PandocError
writersField Field PandocError -> [Field PandocError] -> [Field PandocError]
forall a. a -> [a] -> [a]
:
[Field PandocError]
forall e. [Field e]
stringConstants [Field PandocError] -> [Field PandocError] -> [Field PandocError]
forall a. [a] -> [a] -> [a]
++ [Field PandocError
inlineField, Field PandocError
blockField]
, moduleOperations :: [(Operation, DocumentedFunction PandocError)]
moduleOperations = []
, moduleFunctions :: [DocumentedFunction PandocError]
moduleFunctions = [[DocumentedFunction PandocError]]
-> [DocumentedFunction PandocError]
forall a. Monoid a => [a] -> a
mconcat
[ [DocumentedFunction PandocError
forall e. LuaError e => DocumentedFunction e
mkPandoc, DocumentedFunction PandocError
forall e. LuaError e => DocumentedFunction e
mkMeta]
, [DocumentedFunction PandocError]
forall e. LuaError e => [DocumentedFunction e]
metaValueConstructors
, [DocumentedFunction PandocError]
forall e. LuaError e => [DocumentedFunction e]
blockConstructors
, [DocumentedFunction PandocError
forall e. LuaError e => DocumentedFunction e
mkBlocks]
, [DocumentedFunction PandocError]
forall e. LuaError e => [DocumentedFunction e]
inlineConstructors
, [DocumentedFunction PandocError
forall e. LuaError e => DocumentedFunction e
mkInlines]
, [DocumentedFunction PandocError]
otherConstructors
, [DocumentedFunction PandocError]
functions
]
, moduleTypeInitializers :: [LuaE PandocError Name]
moduleTypeInitializers =
[ DocumentedTypeWithList PandocError Pandoc Void
-> LuaE PandocError Name
forall e a itemtype.
LuaError e =>
DocumentedTypeWithList e a itemtype -> LuaE e Name
initType DocumentedTypeWithList PandocError Pandoc Void
forall e. LuaError e => DocumentedType e Pandoc
typePandoc
, DocumentedTypeWithList PandocError Block Void
-> LuaE PandocError Name
forall e a itemtype.
LuaError e =>
DocumentedTypeWithList e a itemtype -> LuaE e Name
initType DocumentedTypeWithList PandocError Block Void
forall e. LuaError e => DocumentedType e Block
typeBlock
, DocumentedTypeWithList PandocError Inline Void
-> LuaE PandocError Name
forall e a itemtype.
LuaError e =>
DocumentedTypeWithList e a itemtype -> LuaE e Name
initType DocumentedTypeWithList PandocError Inline Void
forall e. LuaError e => DocumentedType e Inline
typeInline
]
}
readersField :: Field PandocError
readersField :: Field PandocError
readersField = Field
{ fieldName :: Text
fieldName = Text
"readers"
, fieldType :: TypeSpec
fieldType = TypeSpec
"table"
, fieldDescription :: Text
fieldDescription = [Text] -> Text
T.unlines
[ Text
"Set of formats that pandoc can parse. All keys in this table can"
, Text
"be used as the `format` value in `pandoc.read`."
]
, fieldPushValue :: LuaE PandocError ()
fieldPushValue = Pusher PandocError Text -> Pusher PandocError (Set Text)
forall e a. LuaError e => Pusher e a -> Pusher e (Set a)
pushSet Pusher PandocError Text
forall e. Pusher e Text
pushText Pusher PandocError (Set Text) -> Pusher PandocError (Set Text)
forall a b. (a -> b) -> a -> b
$
[Text] -> Set Text
forall a. Ord a => [a] -> Set a
Set.fromList (((Text, Reader PandocLua) -> Text)
-> [(Text, Reader PandocLua)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text, Reader PandocLua) -> Text
forall a b. (a, b) -> a
fst (forall (m :: * -> *). PandocMonad m => [(Text, Reader m)]
readers @PandocLua))
}
writersField :: Field PandocError
writersField :: Field PandocError
writersField = Field
{ fieldName :: Text
fieldName = Text
"writers"
, fieldType :: TypeSpec
fieldType = TypeSpec
"table"
, fieldDescription :: Text
fieldDescription = [Text] -> Text
T.unlines
[ Text
"Set of formats that pandoc can generate. All keys in this table"
, Text
"can be used as the `format` value in `pandoc.write`."
]
, fieldPushValue :: LuaE PandocError ()
fieldPushValue = Pusher PandocError Text -> Pusher PandocError (Set Text)
forall e a. LuaError e => Pusher e a -> Pusher e (Set a)
pushSet Pusher PandocError Text
forall e. Pusher e Text
pushText Pusher PandocError (Set Text) -> Pusher PandocError (Set Text)
forall a b. (a -> b) -> a -> b
$
[Text] -> Set Text
forall a. Ord a => [a] -> Set a
Set.fromList (((Text, Writer PandocLua) -> Text)
-> [(Text, Writer PandocLua)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text, Writer PandocLua) -> Text
forall a b. (a, b) -> a
fst (forall (m :: * -> *). PandocMonad m => [(Text, Writer m)]
writers @PandocLua))
}
inlineField :: Field PandocError
inlineField :: Field PandocError
inlineField = Field
{ fieldName :: Text
fieldName = Text
"Inline"
, fieldType :: TypeSpec
fieldType = TypeSpec
"table"
, fieldDescription :: Text
fieldDescription = Text
"Inline constructors, nested under 'constructors'."
, fieldPushValue :: LuaE PandocError ()
fieldPushValue = [DocumentedFunction PandocError] -> LuaE PandocError ()
pushWithConstructorsSubtable [DocumentedFunction PandocError]
forall e. LuaError e => [DocumentedFunction e]
inlineConstructors
}
blockField :: Field PandocError
blockField :: Field PandocError
blockField = Field
{ fieldName :: Text
fieldName = Text
"Block"
, fieldType :: TypeSpec
fieldType = TypeSpec
"table"
, fieldDescription :: Text
fieldDescription = Text
"Inline constructors, nested under 'constructors'."
, fieldPushValue :: LuaE PandocError ()
fieldPushValue = [DocumentedFunction PandocError] -> LuaE PandocError ()
pushWithConstructorsSubtable [DocumentedFunction PandocError]
forall e. LuaError e => [DocumentedFunction e]
blockConstructors
}
pushWithConstructorsSubtable :: [DocumentedFunction PandocError]
-> LuaE PandocError ()
[DocumentedFunction PandocError]
constructors = do
LuaE PandocError ()
forall e. LuaE e ()
newtable
LuaE PandocError ()
forall e. LuaE e ()
newtable
Name -> LuaE PandocError ()
forall e. Name -> LuaE e ()
pushName Name
"constructor" LuaE PandocError () -> LuaE PandocError () -> LuaE PandocError ()
forall a b.
LuaE PandocError a -> LuaE PandocError b -> LuaE PandocError b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StackIndex -> LuaE PandocError ()
forall e. StackIndex -> LuaE e ()
pushvalue (CInt -> StackIndex
nth CInt
2) LuaE PandocError () -> LuaE PandocError () -> LuaE PandocError ()
forall a b.
LuaE PandocError a -> LuaE PandocError b -> LuaE PandocError b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StackIndex -> LuaE PandocError ()
forall e. LuaError e => StackIndex -> LuaE e ()
rawset (CInt -> StackIndex
nth CInt
4)
[DocumentedFunction PandocError]
-> (DocumentedFunction PandocError -> LuaE PandocError ())
-> LuaE PandocError ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [DocumentedFunction PandocError]
constructors ((DocumentedFunction PandocError -> LuaE PandocError ())
-> LuaE PandocError ())
-> (DocumentedFunction PandocError -> LuaE PandocError ())
-> LuaE PandocError ()
forall a b. (a -> b) -> a -> b
$ \DocumentedFunction PandocError
fn -> do
Name -> LuaE PandocError ()
forall e. Name -> LuaE e ()
pushName (DocumentedFunction PandocError -> Name
forall e. DocumentedFunction e -> Name
functionName DocumentedFunction PandocError
fn)
DocumentedFunction PandocError -> LuaE PandocError ()
forall e. LuaError e => DocumentedFunction e -> LuaE e ()
pushDocumentedFunction DocumentedFunction PandocError
fn
StackIndex -> LuaE PandocError ()
forall e. LuaError e => StackIndex -> LuaE e ()
rawset (CInt -> StackIndex
nth CInt
3)
Int -> LuaE PandocError ()
forall e. Int -> LuaE e ()
pop Int
1
otherConstructors :: [DocumentedFunction PandocError]
otherConstructors :: [DocumentedFunction PandocError]
otherConstructors =
[ DocumentedFunction PandocError
forall e. LuaError e => DocumentedFunction e
mkAttr
, DocumentedFunction PandocError
forall e. LuaError e => DocumentedFunction e
mkCaption DocumentedFunction PandocError
-> Version -> DocumentedFunction PandocError
forall e. DocumentedFunction e -> Version -> DocumentedFunction e
`since` [Int] -> Version
makeVersion [Int
3,Int
6,Int
1]
, DocumentedFunction PandocError
forall e. LuaError e => DocumentedFunction e
mkCell
, DocumentedFunction PandocError
forall e. LuaError e => DocumentedFunction e
mkAttributeList
, DocumentedFunction PandocError
forall e. LuaError e => DocumentedFunction e
mkCitation
, DocumentedFunction PandocError
forall e. LuaError e => DocumentedFunction e
mkListAttributes
, DocumentedFunction PandocError
forall e. LuaError e => DocumentedFunction e
mkRow
, DocumentedFunction PandocError
forall e. LuaError e => DocumentedFunction e
mkTableFoot
, DocumentedFunction PandocError
forall e. LuaError e => DocumentedFunction e
mkTableHead
, DocumentedFunction PandocError
forall e. LuaError e => DocumentedFunction e
mkSimpleTable
, Name
-> (ReaderOptions -> LuaE PandocError ReaderOptions)
-> HsFnPrecursor
PandocError (ReaderOptions -> LuaE PandocError ReaderOptions)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"ReaderOptions"
### liftPure id
HsFnPrecursor
PandocError (ReaderOptions -> LuaE PandocError ReaderOptions)
-> Parameter PandocError ReaderOptions
-> HsFnPrecursor PandocError (LuaE PandocError ReaderOptions)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError ReaderOptions
-> TypeSpec -> Text -> Text -> Parameter PandocError ReaderOptions
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker PandocError ReaderOptions
forall e. LuaError e => Peeker e ReaderOptions
peekReaderOptions TypeSpec
"ReaderOptions|table" Text
"opts"
([Text] -> Text
T.unlines
[ Text
"Either a table with a subset of the properties of a"
, Text
"[[ReaderOptions]] object, or another ReaderOptions object."
, Text
"Uses the defaults specified in the manual for all"
, Text
"properties that are not explicitly specified. Throws an"
, Text
"error if a table contains properties which are not present"
, Text
"in a ReaderOptions object."
]
)
HsFnPrecursor PandocError (LuaE PandocError ReaderOptions)
-> FunctionResults PandocError ReaderOptions
-> DocumentedFunction PandocError
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher PandocError ReaderOptions
-> TypeSpec -> Text -> FunctionResults PandocError ReaderOptions
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher PandocError ReaderOptions
forall e. LuaError e => Pusher e ReaderOptions
pushReaderOptions TypeSpec
"ReaderOptions" Text
"new object"
#? T.unlines
[ "Creates a new ReaderOptions value."
, ""
, "Usage:"
, ""
, " -- copy of the reader options that were defined on the command line."
, " local cli_opts = pandoc.ReaderOptions(PANDOC_READER_OPTIONS)"
, " -- default reader options, but columns set to 66."
, " local short_colums_opts = pandoc.ReaderOptions {columns = 66}"
]
, Name
-> (WriterOptions -> LuaE PandocError WriterOptions)
-> HsFnPrecursor
PandocError (WriterOptions -> LuaE PandocError WriterOptions)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"WriterOptions"
### liftPure id
HsFnPrecursor
PandocError (WriterOptions -> LuaE PandocError WriterOptions)
-> Parameter PandocError WriterOptions
-> HsFnPrecursor PandocError (LuaE PandocError WriterOptions)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError WriterOptions
-> TypeSpec -> Text -> Text -> Parameter PandocError WriterOptions
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker PandocError WriterOptions
peekWriterOptions TypeSpec
"WriterOptions|table" Text
"opts"
([Text] -> Text
T.unlines
[ Text
"Either a table with a subset of the properties of a"
, Text
"[[WriterOptions]] object, or another WriterOptions object."
, Text
"Uses the defaults specified in the manual for all"
, Text
"properties that are not explicitly specified. Throws an"
, Text
"error if a table contains properties which are not present"
, Text
"in a WriterOptions object."
])
HsFnPrecursor PandocError (LuaE PandocError WriterOptions)
-> FunctionResults PandocError WriterOptions
-> DocumentedFunction PandocError
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher PandocError WriterOptions
-> TypeSpec -> Text -> FunctionResults PandocError WriterOptions
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher PandocError WriterOptions
pushWriterOptions TypeSpec
"WriterOptions" Text
"new object"
#? "Creates a new WriterOptions value."
]
stringConstants :: [Field e]
stringConstants :: forall e. [Field e]
stringConstants =
let constrs :: forall a. Data a => Proxy a -> [String]
constrs :: forall a. Data a => Proxy a -> [String]
constrs Proxy a
_ = (Constr -> String) -> [Constr] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Constr -> String
showConstr ([Constr] -> [String]) -> (a -> [Constr]) -> a -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DataType -> [Constr]
dataTypeConstrs (DataType -> [Constr]) -> (a -> DataType) -> a -> [Constr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Data a => a -> DataType
dataTypeOf @a (a -> [String]) -> a -> [String]
forall a b. (a -> b) -> a -> b
$ a
forall a. HasCallStack => a
undefined
nullaryConstructors :: [String]
nullaryConstructors = [[String]] -> [String]
forall a. Monoid a => [a] -> a
mconcat
[ Proxy ListNumberStyle -> [String]
forall a. Data a => Proxy a -> [String]
constrs (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @ListNumberStyle)
, Proxy ListNumberDelim -> [String]
forall a. Data a => Proxy a -> [String]
constrs (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @ListNumberDelim)
, Proxy QuoteType -> [String]
forall a. Data a => Proxy a -> [String]
constrs (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @QuoteType)
, Proxy MathType -> [String]
forall a. Data a => Proxy a -> [String]
constrs (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @MathType)
, Proxy Alignment -> [String]
forall a. Data a => Proxy a -> [String]
constrs (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @Alignment)
, Proxy CitationMode -> [String]
forall a. Data a => Proxy a -> [String]
constrs (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @CitationMode)
]
toField :: String -> Field e
toField String
s = Field
{ fieldName :: Text
fieldName = String -> Text
T.pack String
s
, fieldType :: TypeSpec
fieldType = TypeSpec
"string"
, fieldDescription :: Text
fieldDescription = String -> Text
T.pack String
s
, fieldPushValue :: LuaE e ()
fieldPushValue = String -> LuaE e ()
forall e. String -> LuaE e ()
pushString String
s
}
in (String -> Field e) -> [String] -> [Field e]
forall a b. (a -> b) -> [a] -> [b]
map String -> Field e
forall {e}. String -> Field e
toField [String]
nullaryConstructors
functions :: [DocumentedFunction PandocError]
functions :: [DocumentedFunction PandocError]
functions =
[ Name
-> (String
-> [String] -> ByteString -> LuaE PandocError NumResults)
-> HsFnPrecursor
PandocError
(String -> [String] -> ByteString -> LuaE PandocError NumResults)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"pipe"
### (\command args input -> do
(ec, output) <- Lua.liftIO $ pipeProcess Nothing command args input
`catch` (throwM . PandocIOError "pipe")
case ec of
ExitSuccess -> 1 <$ Lua.pushLazyByteString output
ExitFailure n -> do
pushPipeError (PipeError (T.pack command) n output)
Lua.error)
HsFnPrecursor
PandocError
(String -> [String] -> ByteString -> LuaE PandocError NumResults)
-> Parameter PandocError String
-> HsFnPrecursor
PandocError ([String] -> ByteString -> LuaE PandocError NumResults)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError String
-> TypeSpec -> Text -> Text -> Parameter PandocError String
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker PandocError String
forall e. Peeker e String
peekString TypeSpec
"string" Text
"command" Text
"path to executable"
HsFnPrecursor
PandocError ([String] -> ByteString -> LuaE PandocError NumResults)
-> Parameter PandocError [String]
-> HsFnPrecursor
PandocError (ByteString -> LuaE PandocError NumResults)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError [String]
-> TypeSpec -> Text -> Text -> Parameter PandocError [String]
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter (Peeker PandocError String -> Peeker PandocError [String]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker PandocError String
forall e. Peeker e String
peekString) TypeSpec
"{string,...}" Text
"args"
Text
"list of arguments"
HsFnPrecursor
PandocError (ByteString -> LuaE PandocError NumResults)
-> Parameter PandocError ByteString
-> HsFnPrecursor PandocError (LuaE PandocError NumResults)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError ByteString
-> TypeSpec -> Text -> Text -> Parameter PandocError ByteString
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker PandocError ByteString
forall e. Peeker e ByteString
peekLazyByteString TypeSpec
"string" Text
"input"
Text
"input passed to process via stdin"
HsFnPrecursor PandocError (LuaE PandocError NumResults)
-> Text -> DocumentedFunction PandocError
forall e.
HsFnPrecursor e (LuaE e NumResults) -> Text -> DocumentedFunction e
=?> Text
"output string, or error triple"
, Name
-> (Either ByteString Sources
-> Maybe FlavoredFormat
-> Maybe ReaderOptions
-> Maybe FileTree
-> LuaE PandocError Pandoc)
-> HsFnPrecursor
PandocError
(Either ByteString Sources
-> Maybe FlavoredFormat
-> Maybe ReaderOptions
-> Maybe FileTree
-> LuaE PandocError Pandoc)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"read"
### (\content mformatspec mreaderOptions mreadEnv -> do
let readerOpts = fromMaybe def mreaderOptions
readAction :: PandocMonad m => FlavoredFormat -> m Pandoc
readAction flvrd = getReader flvrd >>= \case
(TextReader r, es) ->
r readerOpts{readerExtensions = es} $
case content of
Left bs -> toSources $ UTF8.toText bs
Right sources -> sources
(ByteStringReader r, es) ->
case content of
Left bs -> r readerOpts{readerExtensions = es}
(BSL.fromStrict bs)
Right _ -> throwError $ PandocLuaError
"Cannot use bytestring reader with Sources"
handle (failLua . show @UnicodeException) . unPandocLua $ do
flvrd <- maybe (parseFlavoredFormat "markdown") pure mformatspec
case mreadEnv of
Nothing -> readAction flvrd
Just tree -> sandboxWithFileTree tree (readAction flvrd))
HsFnPrecursor
PandocError
(Either ByteString Sources
-> Maybe FlavoredFormat
-> Maybe ReaderOptions
-> Maybe FileTree
-> LuaE PandocError Pandoc)
-> Parameter PandocError (Either ByteString Sources)
-> HsFnPrecursor
PandocError
(Maybe FlavoredFormat
-> Maybe ReaderOptions
-> Maybe FileTree
-> LuaE PandocError Pandoc)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError (Either ByteString Sources)
-> TypeSpec
-> Text
-> Text
-> Parameter PandocError (Either ByteString Sources)
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter (\StackIndex
idx -> (ByteString -> Either ByteString Sources
forall a b. a -> Either a b
Left (ByteString -> Either ByteString Sources)
-> Peek PandocError ByteString
-> Peek PandocError (Either ByteString Sources)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peeker PandocError ByteString
forall e. Peeker e ByteString
peekByteString StackIndex
idx)
Peek PandocError (Either ByteString Sources)
-> Peek PandocError (Either ByteString Sources)
-> Peek PandocError (Either ByteString Sources)
forall a.
Peek PandocError a -> Peek PandocError a -> Peek PandocError a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Sources -> Either ByteString Sources
forall a b. b -> Either a b
Right (Sources -> Either ByteString Sources)
-> Peek PandocError Sources
-> Peek PandocError (Either ByteString Sources)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peeker PandocError Sources
forall e. LuaError e => Peeker e Sources
peekSources StackIndex
idx))
TypeSpec
"string|Sources" Text
"content" Text
"text to parse"
HsFnPrecursor
PandocError
(Maybe FlavoredFormat
-> Maybe ReaderOptions
-> Maybe FileTree
-> LuaE PandocError Pandoc)
-> Parameter PandocError (Maybe FlavoredFormat)
-> HsFnPrecursor
PandocError
(Maybe ReaderOptions -> Maybe FileTree -> LuaE PandocError Pandoc)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter PandocError FlavoredFormat
-> Parameter PandocError (Maybe FlavoredFormat)
forall e a. Parameter e a -> Parameter e (Maybe a)
opt (Peeker PandocError FlavoredFormat
-> TypeSpec -> Text -> Text -> Parameter PandocError FlavoredFormat
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker PandocError FlavoredFormat
peekFlavoredFormat TypeSpec
"string|table"
Text
"formatspec" Text
"format and extensions")
HsFnPrecursor
PandocError
(Maybe ReaderOptions -> Maybe FileTree -> LuaE PandocError Pandoc)
-> Parameter PandocError (Maybe ReaderOptions)
-> HsFnPrecursor
PandocError (Maybe FileTree -> LuaE PandocError Pandoc)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter PandocError ReaderOptions
-> Parameter PandocError (Maybe ReaderOptions)
forall e a. Parameter e a -> Parameter e (Maybe a)
opt (Peeker PandocError ReaderOptions
-> TypeSpec -> Text -> Text -> Parameter PandocError ReaderOptions
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker PandocError ReaderOptions
forall e. LuaError e => Peeker e ReaderOptions
peekReaderOptions TypeSpec
"ReaderOptions" Text
"reader_options"
Text
"reader options")
HsFnPrecursor
PandocError (Maybe FileTree -> LuaE PandocError Pandoc)
-> Parameter PandocError (Maybe FileTree)
-> HsFnPrecursor PandocError (LuaE PandocError Pandoc)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter PandocError FileTree
-> Parameter PandocError (Maybe FileTree)
forall e a. Parameter e a -> Parameter e (Maybe a)
opt (Peeker PandocError FileTree
-> TypeSpec -> Text -> Text -> Parameter PandocError FileTree
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker PandocError FileTree
peekReadEnv TypeSpec
"table" Text
"read_env" (Text -> Parameter PandocError FileTree)
-> Text -> Parameter PandocError FileTree
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.unlines
[ Text
"If the value is not given or `nil`, then the global environment"
, Text
"is used. Passing a list of filenames causes the reader to"
, Text
"be run in a sandbox. The given files are read from the file"
, Text
"system and provided to the sandbox via an ersatz file system."
, Text
"The table can also contain mappings from filenames to"
, Text
"contents, which will be used to populate the ersatz file"
, Text
"system."
])
HsFnPrecursor PandocError (LuaE PandocError Pandoc)
-> FunctionResults PandocError Pandoc
-> DocumentedFunction PandocError
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher PandocError Pandoc
-> TypeSpec -> Text -> FunctionResults PandocError Pandoc
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher PandocError Pandoc
forall e. LuaError e => Pusher e Pandoc
pushPandoc TypeSpec
"Pandoc" Text
"result document"
, DocumentedFunction PandocError
forall e. DocumentedFunction e
sha1
, Name
-> (Block -> Filter -> LuaE PandocError Block)
-> HsFnPrecursor
PandocError (Block -> Filter -> LuaE PandocError Block)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"walk_block"
### walkElement
HsFnPrecursor
PandocError (Block -> Filter -> LuaE PandocError Block)
-> Parameter PandocError Block
-> HsFnPrecursor PandocError (Filter -> LuaE PandocError Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError Block
-> TypeSpec -> Text -> Text -> Parameter PandocError Block
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker PandocError Block
forall e. LuaError e => Peeker e Block
peekBlockFuzzy TypeSpec
"Block" Text
"block" Text
"element to traverse"
HsFnPrecursor PandocError (Filter -> LuaE PandocError Block)
-> Parameter PandocError Filter
-> HsFnPrecursor PandocError (LuaE PandocError Block)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError Filter
-> TypeSpec -> Text -> Text -> Parameter PandocError Filter
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker PandocError Filter
forall e. LuaError e => Peeker e Filter
peekFilter TypeSpec
"Filter" Text
"lua_filter" Text
"filter functions"
HsFnPrecursor PandocError (LuaE PandocError Block)
-> FunctionResults PandocError Block
-> DocumentedFunction PandocError
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher PandocError Block
-> TypeSpec -> Text -> FunctionResults PandocError Block
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher PandocError Block
forall e. LuaError e => Pusher e Block
pushBlock TypeSpec
"Block" Text
"modified Block"
, Name
-> (Inline -> Filter -> LuaE PandocError Inline)
-> HsFnPrecursor
PandocError (Inline -> Filter -> LuaE PandocError Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"walk_inline"
### walkElement
HsFnPrecursor
PandocError (Inline -> Filter -> LuaE PandocError Inline)
-> Parameter PandocError Inline
-> HsFnPrecursor PandocError (Filter -> LuaE PandocError Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError Inline
-> TypeSpec -> Text -> Text -> Parameter PandocError Inline
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker PandocError Inline
forall e. LuaError e => Peeker e Inline
peekInlineFuzzy TypeSpec
"Inline" Text
"inline" Text
"element to traverse"
HsFnPrecursor PandocError (Filter -> LuaE PandocError Inline)
-> Parameter PandocError Filter
-> HsFnPrecursor PandocError (LuaE PandocError Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError Filter
-> TypeSpec -> Text -> Text -> Parameter PandocError Filter
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker PandocError Filter
forall e. LuaError e => Peeker e Filter
peekFilter TypeSpec
"Filter" Text
"lua_filter" Text
"filter functions"
HsFnPrecursor PandocError (LuaE PandocError Inline)
-> FunctionResults PandocError Inline
-> DocumentedFunction PandocError
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher PandocError Inline
-> TypeSpec -> Text -> FunctionResults PandocError Inline
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher PandocError Inline
forall e. LuaError e => Pusher e Inline
pushInline TypeSpec
"Inline" Text
"modified Inline"
, Name
-> (Pandoc
-> Maybe FlavoredFormat
-> Maybe WriterOptions
-> LuaE PandocError (Either ByteString Text))
-> HsFnPrecursor
PandocError
(Pandoc
-> Maybe FlavoredFormat
-> Maybe WriterOptions
-> LuaE PandocError (Either ByteString Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"write"
### (\doc mformatspec mwriterOpts -> unPandocLua $ do
flvrd <- maybe (parseFlavoredFormat "markdown") pure mformatspec
let writerOpts = fromMaybe def mwriterOpts
getWriter flvrd >>= \case
(TextWriter w, es) -> Right <$>
w writerOpts{ writerExtensions = es } doc
(ByteStringWriter w, es) -> Left <$>
w writerOpts{ writerExtensions = es } doc)
HsFnPrecursor
PandocError
(Pandoc
-> Maybe FlavoredFormat
-> Maybe WriterOptions
-> LuaE PandocError (Either ByteString Text))
-> Parameter PandocError Pandoc
-> HsFnPrecursor
PandocError
(Maybe FlavoredFormat
-> Maybe WriterOptions
-> LuaE PandocError (Either ByteString Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError Pandoc
-> TypeSpec -> Text -> Text -> Parameter PandocError Pandoc
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker PandocError Pandoc
forall e. LuaError e => Peeker e Pandoc
peekPandoc TypeSpec
"Pandoc" Text
"doc" Text
"document to convert"
HsFnPrecursor
PandocError
(Maybe FlavoredFormat
-> Maybe WriterOptions
-> LuaE PandocError (Either ByteString Text))
-> Parameter PandocError (Maybe FlavoredFormat)
-> HsFnPrecursor
PandocError
(Maybe WriterOptions -> LuaE PandocError (Either ByteString Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter PandocError FlavoredFormat
-> Parameter PandocError (Maybe FlavoredFormat)
forall e a. Parameter e a -> Parameter e (Maybe a)
opt (Peeker PandocError FlavoredFormat
-> TypeSpec -> Text -> Text -> Parameter PandocError FlavoredFormat
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker PandocError FlavoredFormat
peekFlavoredFormat TypeSpec
"string|table" Text
"formatspec"
([Text] -> Text
T.unlines
[ Text
"format specification; defaults to `\"html\"`. See the"
, Text
"documentation of [`pandoc.read`](#pandoc.read) for a complete"
, Text
"description of this parameter."
]))
HsFnPrecursor
PandocError
(Maybe WriterOptions -> LuaE PandocError (Either ByteString Text))
-> Parameter PandocError (Maybe WriterOptions)
-> HsFnPrecursor
PandocError (LuaE PandocError (Either ByteString Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter PandocError WriterOptions
-> Parameter PandocError (Maybe WriterOptions)
forall e a. Parameter e a -> Parameter e (Maybe a)
opt (Peeker PandocError WriterOptions
-> TypeSpec -> Text -> Text -> Parameter PandocError WriterOptions
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker PandocError WriterOptions
peekWriterOptions TypeSpec
"WriterOptions|table" Text
"writer_options"
([Text] -> Text
T.unlines
[ Text
"options passed to the writer; may be a WriterOptions object"
, Text
"or a table with a subset of the keys and values of a"
, Text
"WriterOptions object; defaults to the default values"
, Text
"documented in the manual."
])
)
HsFnPrecursor
PandocError (LuaE PandocError (Either ByteString Text))
-> FunctionResults PandocError (Either ByteString Text)
-> DocumentedFunction PandocError
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher PandocError (Either ByteString Text)
-> TypeSpec
-> Text
-> FunctionResults PandocError (Either ByteString Text)
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult (Pusher PandocError ByteString
-> Pusher PandocError Text
-> Pusher PandocError (Either ByteString Text)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either Pusher PandocError ByteString
forall e. Pusher e ByteString
pushLazyByteString Pusher PandocError Text
forall e. Pusher e Text
pushText) TypeSpec
"string"
Text
"result document"
#? T.unlines
[ "Converts a document to the given target format."
, ""
, "Usage:"
, ""
, " local doc = pandoc.Pandoc("
, " {pandoc.Para {pandoc.Strong 'Tea'}}"
, " )"
, " local html = pandoc.write(doc, 'html')"
, " assert(html == '<p><strong>Tea</strong></p>')"
]
, Name
-> (Pandoc -> Maybe WriterOptions -> LuaE PandocError Text)
-> HsFnPrecursor
PandocError
(Pandoc -> Maybe WriterOptions -> LuaE PandocError Text)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"write_classic"
### (\doc mwopts -> runCustom (fromMaybe def mwopts) doc)
HsFnPrecursor
PandocError
(Pandoc -> Maybe WriterOptions -> LuaE PandocError Text)
-> Parameter PandocError Pandoc
-> HsFnPrecursor
PandocError (Maybe WriterOptions -> LuaE PandocError Text)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker PandocError Pandoc
-> TypeSpec -> Text -> Text -> Parameter PandocError Pandoc
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker PandocError Pandoc
forall e. LuaError e => Peeker e Pandoc
peekPandoc TypeSpec
"Pandoc" Text
"doc" Text
"document to convert"
HsFnPrecursor
PandocError (Maybe WriterOptions -> LuaE PandocError Text)
-> Parameter PandocError (Maybe WriterOptions)
-> HsFnPrecursor PandocError (LuaE PandocError Text)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter PandocError WriterOptions
-> Parameter PandocError (Maybe WriterOptions)
forall e a. Parameter e a -> Parameter e (Maybe a)
opt (Peeker PandocError WriterOptions
-> TypeSpec -> Text -> Text -> Parameter PandocError WriterOptions
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker PandocError WriterOptions
peekWriterOptions TypeSpec
"WriterOptions" Text
"writer_options"
([Text] -> Text
T.unlines
[ Text
"options passed to the writer; may be a WriterOptions object"
, Text
"or a table with a subset of the keys and values of a"
, Text
"WriterOptions object; defaults to the default values"
, Text
"documented in the manual."
]))
HsFnPrecursor PandocError (LuaE PandocError Text)
-> FunctionResults PandocError Text
-> DocumentedFunction PandocError
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher PandocError Text
-> TypeSpec -> Text -> FunctionResults PandocError Text
forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher PandocError Text
forall e. Pusher e Text
pushText TypeSpec
"string" Text
"rendered document"
#? (T.unlines
[ "Runs a classic custom Lua writer, using the functions defined"
, "in the current environment."
, ""
, "Usage:"
, ""
, " -- Adding this function converts a classic writer into a"
, " -- new-style custom writer."
, " function Writer (doc, opts)"
, " PANDOC_DOCUMENT = doc"
, " PANDOC_WRITER_OPTIONS = opts"
, " loadfile(PANDOC_SCRIPT_FILE)()"
, " return pandoc.write_classic(doc, opts)"
, " end"
])
]
where
walkElement :: b -> Filter -> LuaE e b
walkElement b
x Filter
f =
Filter -> b -> LuaE e b
forall e a.
(LuaError e, Walkable (SpliceList Inline) a) =>
Filter -> a -> LuaE e a
walkInlineSplicing Filter
f b
x
LuaE e b -> (b -> LuaE e b) -> LuaE e b
forall a b. LuaE e a -> (a -> LuaE e b) -> LuaE e b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Filter -> b -> LuaE e b
forall e a.
(LuaError e, Walkable [Inline] a) =>
Filter -> a -> LuaE e a
walkInlinesStraight Filter
f
LuaE e b -> (b -> LuaE e b) -> LuaE e b
forall a b. LuaE e a -> (a -> LuaE e b) -> LuaE e b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Filter -> b -> LuaE e b
forall e a.
(LuaError e, Walkable (SpliceList Block) a) =>
Filter -> a -> LuaE e a
walkBlockSplicing Filter
f
LuaE e b -> (b -> LuaE e b) -> LuaE e b
forall a b. LuaE e a -> (a -> LuaE e b) -> LuaE e b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Filter -> b -> LuaE e b
forall e a.
(LuaError e, Walkable [Block] a) =>
Filter -> a -> LuaE e a
walkBlocksStraight Filter
f
data PipeError = PipeError
{ PipeError -> Text
pipeErrorCommand :: T.Text
, PipeError -> Int
pipeErrorCode :: Int
, PipeError -> ByteString
pipeErrorOutput :: BL.ByteString
}
peekPipeError :: LuaError e => StackIndex -> LuaE e PipeError
peekPipeError :: forall e. LuaError e => StackIndex -> LuaE e PipeError
peekPipeError StackIndex
idx =
Text -> Int -> ByteString -> PipeError
PipeError
(Text -> Int -> ByteString -> PipeError)
-> LuaE e Text -> LuaE e (Int -> ByteString -> PipeError)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (StackIndex -> Name -> LuaE e Type
forall e. LuaError e => StackIndex -> Name -> LuaE e Type
Lua.getfield StackIndex
idx Name
"command" LuaE e Type -> LuaE e Text -> LuaE e Text
forall a b. LuaE e a -> LuaE e b -> LuaE e b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StackIndex -> LuaE e Text
forall a e. (LuaError e, Peekable a) => StackIndex -> LuaE e a
Lua.peek (-StackIndex
1) LuaE e Text -> LuaE e () -> LuaE e Text
forall a b. LuaE e a -> LuaE e b -> LuaE e a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Int -> LuaE e ()
forall e. Int -> LuaE e ()
Lua.pop Int
1)
LuaE e (Int -> ByteString -> PipeError)
-> LuaE e Int -> LuaE e (ByteString -> PipeError)
forall a b. LuaE e (a -> b) -> LuaE e a -> LuaE e b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (StackIndex -> Name -> LuaE e Type
forall e. LuaError e => StackIndex -> Name -> LuaE e Type
Lua.getfield StackIndex
idx Name
"error_code" LuaE e Type -> LuaE e Int -> LuaE e Int
forall a b. LuaE e a -> LuaE e b -> LuaE e b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StackIndex -> LuaE e Int
forall a e. (LuaError e, Peekable a) => StackIndex -> LuaE e a
Lua.peek (-StackIndex
1) LuaE e Int -> LuaE e () -> LuaE e Int
forall a b. LuaE e a -> LuaE e b -> LuaE e a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Int -> LuaE e ()
forall e. Int -> LuaE e ()
Lua.pop Int
1)
LuaE e (ByteString -> PipeError)
-> LuaE e ByteString -> LuaE e PipeError
forall a b. LuaE e (a -> b) -> LuaE e a -> LuaE e b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (StackIndex -> Name -> LuaE e Type
forall e. LuaError e => StackIndex -> Name -> LuaE e Type
Lua.getfield StackIndex
idx Name
"output" LuaE e Type -> LuaE e ByteString -> LuaE e ByteString
forall a b. LuaE e a -> LuaE e b -> LuaE e b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StackIndex -> LuaE e ByteString
forall a e. (LuaError e, Peekable a) => StackIndex -> LuaE e a
Lua.peek (-StackIndex
1) LuaE e ByteString -> LuaE e () -> LuaE e ByteString
forall a b. LuaE e a -> LuaE e b -> LuaE e a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Int -> LuaE e ()
forall e. Int -> LuaE e ()
Lua.pop Int
1)
pushPipeError :: LuaError e => Pusher e PipeError
pushPipeError :: forall e. LuaError e => Pusher e PipeError
pushPipeError PipeError
pipeErr = do
[(Name, PipeError -> LuaE e ())] -> PipeError -> LuaE e ()
forall e a.
LuaError e =>
[(Name, a -> LuaE e ())] -> a -> LuaE e ()
pushAsTable [ (Name
"command" , Pusher e Text
forall e. Pusher e Text
pushText Pusher e Text -> (PipeError -> Text) -> PipeError -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PipeError -> Text
pipeErrorCommand)
, (Name
"error_code" , Int -> LuaE e ()
forall a e. (Integral a, Show a) => a -> LuaE e ()
pushIntegral (Int -> LuaE e ()) -> (PipeError -> Int) -> PipeError -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PipeError -> Int
pipeErrorCode)
, (Name
"output" , Pusher e ByteString
forall e. Pusher e ByteString
pushLazyByteString Pusher e ByteString
-> (PipeError -> ByteString) -> PipeError -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PipeError -> ByteString
pipeErrorOutput)
] PipeError
pipeErr
LuaE e ()
forall e. LuaError e => LuaE e ()
pushPipeErrorMetaTable
StackIndex -> LuaE e ()
forall e. StackIndex -> LuaE e ()
Lua.setmetatable (CInt -> StackIndex
nth CInt
2)
where
pushPipeErrorMetaTable :: LuaError e => LuaE e ()
pushPipeErrorMetaTable :: forall e. LuaError e => LuaE e ()
pushPipeErrorMetaTable = do
v <- Name -> LuaE e Bool
forall e. Name -> LuaE e Bool
Lua.newmetatable Name
"pandoc pipe error"
when v $ do
pushName "__tostring"
pushHaskellFunction pipeErrorMessage
rawset (nth 3)
pipeErrorMessage :: LuaError e => LuaE e NumResults
pipeErrorMessage :: forall e. LuaError e => LuaE e NumResults
pipeErrorMessage = do
(PipeError cmd errorCode output) <- StackIndex -> LuaE e PipeError
forall e. LuaError e => StackIndex -> LuaE e PipeError
peekPipeError (CInt -> StackIndex
nthBottom CInt
1)
pushByteString . BSL.toStrict . BSL.concat $
[ BSL.pack "Error running "
, BSL.pack $ T.unpack cmd
, BSL.pack " (error code "
, BSL.pack $ show errorCode
, BSL.pack "): "
, if output == mempty then BSL.pack "<no output>" else output
]
return (NumResults 1)
peekReadEnv :: Peeker PandocError FileTree
peekReadEnv :: Peeker PandocError FileTree
peekReadEnv StackIndex
idx = do
mtime <- LuaE PandocError UTCTime -> Peek PandocError UTCTime
forall e a. LuaE e a -> Peek e a
liftLua (LuaE PandocError UTCTime -> Peek PandocError UTCTime)
-> (PandocLua UTCTime -> LuaE PandocError UTCTime)
-> PandocLua UTCTime
-> Peek PandocError UTCTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PandocLua UTCTime -> LuaE PandocError UTCTime
forall a. PandocLua a -> LuaE PandocError a
unPandocLua (PandocLua UTCTime -> Peek PandocError UTCTime)
-> PandocLua UTCTime -> Peek PandocError UTCTime
forall a b. (a -> b) -> a -> b
$ PandocLua UTCTime
forall (m :: * -> *). PandocMonad m => m UTCTime
getCurrentTime
files <- peekList peekString idx
tree1 <- liftLua $
foldM (\FileTree
tree String
fp -> IO FileTree -> LuaE PandocError FileTree
forall a. IO a -> LuaE PandocError a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileTree -> LuaE PandocError FileTree)
-> IO FileTree -> LuaE PandocError FileTree
forall a b. (a -> b) -> a -> b
$ FileTree -> String -> IO FileTree
addToFileTree FileTree
tree String
fp) mempty files
let toFileInfo ByteString
contents = FileInfo
{ infoFileMTime :: UTCTime
infoFileMTime = UTCTime
mtime
, infoFileContents :: ByteString
infoFileContents = ByteString
contents
}
pairs <- peekKeyValuePairs peekString (fmap toFileInfo . peekByteString) idx
let tree2 = ((String, FileInfo) -> FileTree -> FileTree)
-> FileTree -> [(String, FileInfo)] -> FileTree
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ((String -> FileInfo -> FileTree -> FileTree)
-> (String, FileInfo) -> FileTree -> FileTree
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry String -> FileInfo -> FileTree -> FileTree
insertInFileTree) FileTree
tree1 [(String, FileInfo)]
pairs
pure tree2