{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
module Text.Pandoc.Lua.Module.Pandoc
( pushModule
) where
import Prelude hiding (read)
import Control.Applicative (optional)
import Control.Monad ((>=>), forM_, when)
import Control.Monad.Catch (catch, throwM)
import Control.Monad.Except (throwError)
import Data.Default (Default (..))
import Data.Maybe (fromMaybe)
import HsLua as Lua hiding (pushModule)
import HsLua.Class.Peekable (PeekError)
import System.Exit (ExitCode (..))
import Text.Pandoc.Class.PandocIO (runIO)
import Text.Pandoc.Definition
import Text.Pandoc.Lua.Filter (SingletonsList (..), walkInlines,
walkInlineLists, walkBlocks, walkBlockLists)
import Text.Pandoc.Lua.Marshaling ()
import Text.Pandoc.Lua.Marshaling.AST
import Text.Pandoc.Lua.Marshaling.Attr (mkAttr, mkAttributeList)
import Text.Pandoc.Lua.Marshaling.List (List (..))
import Text.Pandoc.Lua.PandocLua (PandocLua, addFunction, liftPandocLua,
loadDefaultModule)
import Text.Pandoc.Options (ReaderOptions (readerExtensions))
import Text.Pandoc.Process (pipeProcess)
import Text.Pandoc.Readers (Reader (..), getReader)
import Text.Pandoc.Walk (Walkable)
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BSL
import qualified Data.Text as T
import qualified Text.Pandoc.Lua.Util as LuaUtil
import Text.Pandoc.Error
pushModule :: PandocLua NumResults
pushModule :: PandocLua NumResults
pushModule = do
String -> PandocLua NumResults
loadDefaultModule String
"pandoc"
Name
-> (Text -> Optional Text -> PandocLua NumResults) -> PandocLua ()
forall a. Exposable PandocError a => Name -> a -> PandocLua ()
addFunction Name
"read" Text -> Optional Text -> PandocLua NumResults
read
Name
-> (String -> [String] -> ByteString -> PandocLua NumResults)
-> PandocLua ()
forall a. Exposable PandocError a => Name -> a -> PandocLua ()
addFunction Name
"pipe" String -> [String] -> ByteString -> PandocLua NumResults
pipe
Name -> LuaE PandocError NumResults -> PandocLua ()
forall a. Exposable PandocError a => Name -> a -> PandocLua ()
addFunction Name
"walk_block" (Peeker PandocError Block
-> Pusher PandocError Block -> LuaE PandocError NumResults
forall a.
(Walkable (SingletonsList Inline) a,
Walkable (SingletonsList Block) a, Walkable (List Inline) a,
Walkable (List Block) a) =>
Peeker PandocError a
-> Pusher PandocError a -> LuaE PandocError NumResults
walkElement Peeker PandocError Block
forall e. LuaError e => Peeker e Block
peekBlock Pusher PandocError Block
forall e. LuaError e => Block -> LuaE e ()
pushBlock)
Name -> LuaE PandocError NumResults -> PandocLua ()
forall a. Exposable PandocError a => Name -> a -> PandocLua ()
addFunction Name
"walk_inline" (Peeker PandocError Inline
-> Pusher PandocError Inline -> LuaE PandocError NumResults
forall a.
(Walkable (SingletonsList Inline) a,
Walkable (SingletonsList Block) a, Walkable (List Inline) a,
Walkable (List Block) a) =>
Peeker PandocError a
-> Pusher PandocError a -> LuaE PandocError NumResults
walkElement Peeker PandocError Inline
forall e. LuaError e => Peeker e Inline
peekInline Pusher PandocError Inline
forall e. LuaError e => Inline -> LuaE e ()
pushInline)
Name -> PandocLua NumResults -> PandocLua ()
forall a. Exposable PandocError a => Name -> a -> PandocLua ()
addFunction Name
"Attr" (LuaE PandocError NumResults -> PandocLua NumResults
forall a. LuaE PandocError a -> PandocLua a
liftPandocLua LuaE PandocError NumResults
forall e. LuaError e => LuaE e NumResults
mkAttr)
Name -> PandocLua NumResults -> PandocLua ()
forall a. Exposable PandocError a => Name -> a -> PandocLua ()
addFunction Name
"AttributeList" (LuaE PandocError NumResults -> PandocLua NumResults
forall a. LuaE PandocError a -> PandocLua a
liftPandocLua LuaE PandocError NumResults
forall e. LuaError e => LuaE e NumResults
mkAttributeList)
Name -> PandocLua NumResults -> PandocLua ()
forall a. Exposable PandocError a => Name -> a -> PandocLua ()
addFunction Name
"Pandoc" PandocLua NumResults
mkPandoc
LuaE PandocError () -> PandocLua ()
forall a. LuaE PandocError a -> PandocLua a
liftPandocLua (LuaE PandocError () -> PandocLua ())
-> LuaE PandocError () -> PandocLua ()
forall a b. (a -> b) -> a -> b
$ do
let addConstr :: DocumentedFunction e -> LuaE e ()
addConstr DocumentedFunction e
fn = do
Name -> LuaE e ()
forall e. Name -> LuaE e ()
pushName (DocumentedFunction e -> Name
forall e. DocumentedFunction e -> Name
functionName DocumentedFunction e
fn)
DocumentedFunction e -> LuaE e ()
forall e. LuaError e => DocumentedFunction e -> LuaE e ()
pushDocumentedFunction DocumentedFunction e
fn
StackIndex -> LuaE e ()
forall e. LuaError e => StackIndex -> LuaE e ()
rawset (CInt -> StackIndex
nth CInt
3)
[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]
forall e. LuaError e => [DocumentedFunction e]
inlineConstructors DocumentedFunction PandocError -> LuaE PandocError ()
forall e. LuaError e => DocumentedFunction e -> LuaE e ()
addConstr
LuaE PandocError ()
forall e. LuaE e ()
newtable
[DocumentedFunction PandocError]
-> (DocumentedFunction PandocError -> LuaE PandocError ())
-> LuaE PandocError ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (LuaError PandocError => [DocumentedFunction PandocError]
forall e. LuaError e => [DocumentedFunction e]
inlineConstructors @PandocError) ((DocumentedFunction PandocError -> LuaE PandocError ())
-> LuaE PandocError ())
-> (DocumentedFunction PandocError -> LuaE PandocError ())
-> LuaE PandocError ()
forall a b. (a -> b) -> a -> b
$ \DocumentedFunction PandocError
fn -> do
let name :: Name
name = DocumentedFunction PandocError -> Name
forall e. DocumentedFunction e -> Name
functionName DocumentedFunction PandocError
fn
Name -> LuaE PandocError ()
forall e. Name -> LuaE e ()
pushName Name
name
Name -> LuaE PandocError ()
forall e. Name -> LuaE e ()
pushName Name
name
StackIndex -> LuaE PandocError ()
forall e. LuaError e => StackIndex -> LuaE e ()
rawget (CInt -> StackIndex
nth CInt
4)
StackIndex -> LuaE PandocError ()
forall e. LuaError e => StackIndex -> LuaE e ()
rawset (CInt -> StackIndex
nth CInt
3)
Name -> LuaE PandocError ()
forall e. Name -> LuaE e ()
pushName Name
"Inline"
LuaE PandocError ()
forall e. LuaE e ()
newtable LuaE PandocError () -> LuaE PandocError () -> LuaE PandocError ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Name -> LuaE PandocError ()
forall e. Name -> LuaE e ()
pushName Name
"constructor" LuaE PandocError () -> LuaE PandocError () -> LuaE PandocError ()
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
4) LuaE PandocError () -> LuaE PandocError () -> LuaE PandocError ()
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
3)
StackIndex -> LuaE PandocError ()
forall e. LuaError e => StackIndex -> LuaE e ()
rawset (CInt -> StackIndex
nth CInt
4)
Int -> LuaE PandocError ()
forall e. Int -> LuaE e ()
pop Int
1
NumResults -> PandocLua NumResults
forall (m :: * -> *) a. Monad m => a -> m a
return NumResults
1
inlineConstructors :: LuaError e => [DocumentedFunction e]
inlineConstructors :: [DocumentedFunction e]
inlineConstructors =
[ Name
-> ([Citation] -> [Inline] -> LuaE e Inline)
-> HsFnPrecursor e ([Citation] -> [Inline] -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Cite"
### liftPure2 Cite
HsFnPrecursor e ([Citation] -> [Inline] -> LuaE e Inline)
-> Parameter e [Citation]
-> HsFnPrecursor e ([Inline] -> LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [Citation]
-> Text -> Text -> Text -> Parameter e [Citation]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (Peeker e Citation -> Peeker e [Citation]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker e Citation
forall e. LuaError e => Peeker e Citation
peekCitation) Text
"citations" Text
"list of Citations" Text
""
HsFnPrecursor e ([Inline] -> LuaE e Inline)
-> Parameter e [Inline] -> HsFnPrecursor e (LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [Inline] -> Text -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekFuzzyInlines Text
"content" Text
"Inline" Text
"placeholder content"
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Inline -> LuaE e ()
pushInline Text
"Inline" Text
"cite element"
, Name
-> (Text -> Attr -> LuaE e Inline)
-> HsFnPrecursor e (Text -> Attr -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Code"
### liftPure2 (flip Code)
HsFnPrecursor e (Text -> Attr -> LuaE e Inline)
-> Parameter e Text -> HsFnPrecursor e (Attr -> LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Text -> Text -> Text -> Text -> Parameter e Text
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Text
forall e. Peeker e Text
peekText Text
"code" Text
"string" Text
"code string"
HsFnPrecursor e (Attr -> LuaE e Inline)
-> Parameter e Attr -> HsFnPrecursor e (LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Attr -> Text -> Text -> Text -> Parameter e Attr
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Attr
forall e. LuaError e => Peeker e Attr
peekAttr Text
"attr" Text
"Attr" Text
"additional attributes"
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Inline -> LuaE e ()
pushInline Text
"Inline" Text
"code element"
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall e.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr Name
"Emph" [Inline] -> Inline
Emph
, Name
-> ([Inline] -> Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
-> HsFnPrecursor
e ([Inline] -> Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Image"
### liftPure4 (\caption src mtitle mattr ->
let attr = fromMaybe nullAttr mattr
title = fromMaybe mempty mtitle
in Image attr caption (src, title))
HsFnPrecursor
e ([Inline] -> Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
-> Parameter e [Inline]
-> HsFnPrecursor
e (Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [Inline] -> Text -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekFuzzyInlines Text
"Inlines" Text
"caption" Text
"image caption / alt"
HsFnPrecursor e (Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
-> Parameter e Text
-> HsFnPrecursor e (Maybe Text -> Maybe Attr -> LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Text -> Text -> Text -> Text -> Parameter e Text
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Text
forall e. Peeker e Text
peekText Text
"string" Text
"src" Text
"path/URL of the image file"
HsFnPrecursor e (Maybe Text -> Maybe Attr -> LuaE e Inline)
-> Parameter e (Maybe Text)
-> HsFnPrecursor e (Maybe Attr -> LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Text -> Text -> Text -> Text -> Parameter e (Maybe Text)
forall e a.
Peeker e a -> Text -> Text -> Text -> Parameter e (Maybe a)
optionalParameter Peeker e Text
forall e. Peeker e Text
peekText Text
"string" Text
"title" Text
"brief image description"
HsFnPrecursor e (Maybe Attr -> LuaE e Inline)
-> Parameter e (Maybe Attr) -> HsFnPrecursor e (LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Attr -> Text -> Text -> Text -> Parameter e (Maybe Attr)
forall e a.
Peeker e a -> Text -> Text -> Text -> Parameter e (Maybe a)
optionalParameter Peeker e Attr
forall e. LuaError e => Peeker e Attr
peekAttr Text
"Attr" Text
"attr" Text
"image attributes"
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Inline -> LuaE e ()
pushInline Text
"Inline" Text
"image element"
, Name -> LuaE e Inline -> HsFnPrecursor e (LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"LineBreak"
### return LineBreak
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Inline -> LuaE e ()
pushInline Text
"Inline" Text
"line break"
, Name
-> ([Inline] -> Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
-> HsFnPrecursor
e ([Inline] -> Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Link"
### liftPure4 (\content target mtitle mattr ->
let attr = fromMaybe nullAttr mattr
title = fromMaybe mempty mtitle
in Link attr content (target, title))
HsFnPrecursor
e ([Inline] -> Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
-> Parameter e [Inline]
-> HsFnPrecursor
e (Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [Inline] -> Text -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekFuzzyInlines Text
"Inlines" Text
"content" Text
"text for this link"
HsFnPrecursor e (Text -> Maybe Text -> Maybe Attr -> LuaE e Inline)
-> Parameter e Text
-> HsFnPrecursor e (Maybe Text -> Maybe Attr -> LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Text -> Text -> Text -> Text -> Parameter e Text
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Text
forall e. Peeker e Text
peekText Text
"string" Text
"target" Text
"the link target"
HsFnPrecursor e (Maybe Text -> Maybe Attr -> LuaE e Inline)
-> Parameter e (Maybe Text)
-> HsFnPrecursor e (Maybe Attr -> LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Text -> Text -> Text -> Text -> Parameter e (Maybe Text)
forall e a.
Peeker e a -> Text -> Text -> Text -> Parameter e (Maybe a)
optionalParameter Peeker e Text
forall e. Peeker e Text
peekText Text
"string" Text
"title" Text
"brief link description"
HsFnPrecursor e (Maybe Attr -> LuaE e Inline)
-> Parameter e (Maybe Attr) -> HsFnPrecursor e (LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Attr -> Text -> Text -> Text -> Parameter e (Maybe Attr)
forall e a.
Peeker e a -> Text -> Text -> Text -> Parameter e (Maybe a)
optionalParameter Peeker e Attr
forall e. LuaError e => Peeker e Attr
peekAttr Text
"Attr" Text
"attr" Text
"link attributes"
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Inline -> LuaE e ()
pushInline Text
"Inline" Text
"link element"
, Name
-> (MathType -> Text -> LuaE e Inline)
-> HsFnPrecursor e (MathType -> Text -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Math"
### liftPure2 Math
HsFnPrecursor e (MathType -> Text -> LuaE e Inline)
-> Parameter e MathType -> HsFnPrecursor e (Text -> LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e MathType -> Text -> Text -> Text -> Parameter e MathType
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e MathType
forall e. LuaError e => Peeker e MathType
peekMathType Text
"quotetype" Text
"Math" Text
"rendering method"
HsFnPrecursor e (Text -> LuaE e Inline)
-> Parameter e Text -> HsFnPrecursor e (LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Text -> Text -> Text -> Text -> Parameter e Text
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Text
forall e. Peeker e Text
peekText Text
"text" Text
"string" Text
"math content"
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Inline -> LuaE e ()
pushInline Text
"Inline" Text
"math element"
, Name
-> ([Block] -> LuaE e Inline)
-> HsFnPrecursor e ([Block] -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Note"
### liftPure Note
HsFnPrecursor e ([Block] -> LuaE e Inline)
-> Parameter e [Block] -> HsFnPrecursor e (LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [Block] -> Text -> Text -> Text -> Parameter e [Block]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e [Block]
forall e. LuaError e => Peeker e [Block]
peekFuzzyBlocks Text
"content" Text
"Blocks" Text
"note content"
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Inline -> LuaE e ()
pushInline Text
"Inline" Text
"note"
, Name
-> (QuoteType -> [Inline] -> LuaE e Inline)
-> HsFnPrecursor e (QuoteType -> [Inline] -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Quoted"
### liftPure2 Quoted
HsFnPrecursor e (QuoteType -> [Inline] -> LuaE e Inline)
-> Parameter e QuoteType
-> HsFnPrecursor e ([Inline] -> LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e QuoteType -> Text -> Text -> Text -> Parameter e QuoteType
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e QuoteType
forall e. LuaError e => Peeker e QuoteType
peekQuoteType Text
"quotetype" Text
"QuoteType" Text
"type of quotes"
HsFnPrecursor e ([Inline] -> LuaE e Inline)
-> Parameter e [Inline] -> HsFnPrecursor e (LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [Inline] -> Text -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekFuzzyInlines Text
"content" Text
"Inlines" Text
"inlines in quotes"
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Inline -> LuaE e ()
pushInline Text
"Inline" Text
"quoted element"
, Name
-> (Format -> Text -> LuaE e Inline)
-> HsFnPrecursor e (Format -> Text -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"RawInline"
### liftPure2 RawInline
HsFnPrecursor e (Format -> Text -> LuaE e Inline)
-> Parameter e Format -> HsFnPrecursor e (Text -> LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Format -> Text -> Text -> Text -> Parameter e Format
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Format
forall e. LuaError e => Peeker e Format
peekFormat Text
"format" Text
"Format" Text
"format of content"
HsFnPrecursor e (Text -> LuaE e Inline)
-> Parameter e Text -> HsFnPrecursor e (LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Text -> Text -> Text -> Text -> Parameter e Text
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Text
forall e. Peeker e Text
peekText Text
"text" Text
"string" Text
"string content"
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Inline -> LuaE e ()
pushInline Text
"Inline" Text
"raw inline element"
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall e.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr Name
"SmallCaps" [Inline] -> Inline
SmallCaps
, Name -> LuaE e Inline -> HsFnPrecursor e (LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"SoftSpace"
### return SoftBreak
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Inline -> LuaE e ()
pushInline Text
"Inline" Text
"soft break"
, Name -> LuaE e Inline -> HsFnPrecursor e (LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Space"
### return Space
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Inline -> LuaE e ()
pushInline Text
"Inline" Text
"new space"
, Name
-> ([Inline] -> Maybe Attr -> LuaE e Inline)
-> HsFnPrecursor e ([Inline] -> Maybe Attr -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Span"
### liftPure2 (\inlns mattr -> Span (fromMaybe nullAttr mattr) inlns)
HsFnPrecursor e ([Inline] -> Maybe Attr -> LuaE e Inline)
-> Parameter e [Inline]
-> HsFnPrecursor e (Maybe Attr -> LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [Inline] -> Text -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekFuzzyInlines Text
"content" Text
"Inlines" Text
"inline content"
HsFnPrecursor e (Maybe Attr -> LuaE e Inline)
-> Parameter e (Maybe Attr) -> HsFnPrecursor e (LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Attr -> Text -> Text -> Text -> Parameter e (Maybe Attr)
forall e a.
Peeker e a -> Text -> Text -> Text -> Parameter e (Maybe a)
optionalParameter Peeker e Attr
forall e. LuaError e => Peeker e Attr
peekAttr Text
"attr" Text
"Attr" Text
"additional attributes"
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Inline -> LuaE e ()
pushInline Text
"Inline" Text
"span element"
, Name
-> (Text -> LuaE e Inline)
-> HsFnPrecursor e (Text -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Str"
### liftPure (\s -> s `seq` Str s)
HsFnPrecursor e (Text -> LuaE e Inline)
-> Parameter e Text -> HsFnPrecursor e (LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Text -> Text -> Text -> Text -> Parameter e Text
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Text
forall e. Peeker e Text
peekText Text
"text" Text
"string" Text
""
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Inline -> LuaE e ()
pushInline Text
"Inline" Text
"new Str object"
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall e.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr Name
"Strong" [Inline] -> Inline
Strong
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall e.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr Name
"Strikeout" [Inline] -> Inline
Strikeout
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall e.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr Name
"Subscript" [Inline] -> Inline
Subscript
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall e.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr Name
"Superscript" [Inline] -> Inline
Superscript
, Name -> ([Inline] -> Inline) -> DocumentedFunction e
forall e.
LuaError e =>
Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr Name
"Underline" [Inline] -> Inline
Underline
]
mkInlinesConstr :: LuaError e
=> Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr :: Name -> ([Inline] -> Inline) -> DocumentedFunction e
mkInlinesConstr Name
name [Inline] -> Inline
constr = Name
-> ([Inline] -> LuaE e Inline)
-> HsFnPrecursor e ([Inline] -> LuaE e Inline)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
name
### liftPure (\x -> x `seq` constr x)
HsFnPrecursor e ([Inline] -> LuaE e Inline)
-> Parameter e [Inline] -> HsFnPrecursor e (LuaE e Inline)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [Inline] -> Text -> Text -> Text -> Parameter e [Inline]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekFuzzyInlines Text
"content" Text
"Inlines" Text
""
HsFnPrecursor e (LuaE e Inline)
-> FunctionResults e Inline -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Inline -> Text -> Text -> FunctionResults e Inline
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Inline
forall e. LuaError e => Inline -> LuaE e ()
pushInline Text
"Inline" Text
"new object"
walkElement :: (Walkable (SingletonsList Inline) a,
Walkable (SingletonsList Block) a,
Walkable (List Inline) a,
Walkable (List Block) a)
=> Peeker PandocError a -> Pusher PandocError a
-> LuaE PandocError NumResults
walkElement :: Peeker PandocError a
-> Pusher PandocError a -> LuaE PandocError NumResults
walkElement Peeker PandocError a
peek' Pusher PandocError a
push' = do
a
x <- Peek PandocError a -> LuaE PandocError a
forall e a. LuaError e => Peek e a -> LuaE e a
forcePeek (Peek PandocError a -> LuaE PandocError a)
-> Peek PandocError a -> LuaE PandocError a
forall a b. (a -> b) -> a -> b
$ Peeker PandocError a
peek' (CInt -> StackIndex
nthBottom CInt
1)
LuaFilter
f <- StackIndex -> LuaE PandocError LuaFilter
forall a e. (Peekable a, PeekError e) => StackIndex -> LuaE e a
peek (CInt -> StackIndex
nthBottom CInt
2)
let walk' :: a -> LuaE PandocError a
walk' = LuaFilter -> a -> LuaE PandocError a
forall a.
Walkable (SingletonsList Inline) a =>
LuaFilter -> a -> LuaE PandocError a
walkInlines LuaFilter
f
(a -> LuaE PandocError a)
-> (a -> LuaE PandocError a) -> a -> LuaE PandocError a
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> LuaFilter -> a -> LuaE PandocError a
forall a.
Walkable (List Inline) a =>
LuaFilter -> a -> LuaE PandocError a
walkInlineLists LuaFilter
f
(a -> LuaE PandocError a)
-> (a -> LuaE PandocError a) -> a -> LuaE PandocError a
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> LuaFilter -> a -> LuaE PandocError a
forall a.
Walkable (SingletonsList Block) a =>
LuaFilter -> a -> LuaE PandocError a
walkBlocks LuaFilter
f
(a -> LuaE PandocError a)
-> (a -> LuaE PandocError a) -> a -> LuaE PandocError a
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> LuaFilter -> a -> LuaE PandocError a
forall a.
Walkable (List Block) a =>
LuaFilter -> a -> LuaE PandocError a
walkBlockLists LuaFilter
f
a -> LuaE PandocError a
walk' a
x LuaE PandocError a -> Pusher PandocError a -> LuaE PandocError ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Pusher PandocError a
push'
NumResults -> LuaE PandocError NumResults
forall (m :: * -> *) a. Monad m => a -> m a
return (CInt -> NumResults
NumResults CInt
1)
read :: T.Text -> Optional T.Text -> PandocLua NumResults
read :: Text -> Optional Text -> PandocLua NumResults
read Text
content Optional Text
formatSpecOrNil = LuaE PandocError NumResults -> PandocLua NumResults
forall a. LuaE PandocError a -> PandocLua a
liftPandocLua (LuaE PandocError NumResults -> PandocLua NumResults)
-> LuaE PandocError NumResults -> PandocLua NumResults
forall a b. (a -> b) -> a -> b
$ do
let formatSpec :: Text
formatSpec = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"markdown" (Optional Text -> Maybe Text
forall a. Optional a -> Maybe a
Lua.fromOptional Optional Text
formatSpecOrNil)
Either PandocError Pandoc
res <- IO (Either PandocError Pandoc)
-> LuaE PandocError (Either PandocError Pandoc)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
Lua.liftIO (IO (Either PandocError Pandoc)
-> LuaE PandocError (Either PandocError Pandoc))
-> (PandocIO Pandoc -> IO (Either PandocError Pandoc))
-> PandocIO Pandoc
-> LuaE PandocError (Either PandocError Pandoc)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PandocIO Pandoc -> IO (Either PandocError Pandoc)
forall a. PandocIO a -> IO (Either PandocError a)
runIO (PandocIO Pandoc -> LuaE PandocError (Either PandocError Pandoc))
-> PandocIO Pandoc -> LuaE PandocError (Either PandocError Pandoc)
forall a b. (a -> b) -> a -> b
$
Text -> PandocIO (Reader PandocIO, Extensions)
forall (m :: * -> *).
PandocMonad m =>
Text -> m (Reader m, Extensions)
getReader Text
formatSpec PandocIO (Reader PandocIO, Extensions)
-> ((Reader PandocIO, Extensions) -> PandocIO Pandoc)
-> PandocIO Pandoc
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \(Reader PandocIO
rdr,Extensions
es) ->
case Reader PandocIO
rdr of
TextReader forall a. ToSources a => ReaderOptions -> a -> PandocIO Pandoc
r ->
ReaderOptions -> Text -> PandocIO Pandoc
forall a. ToSources a => ReaderOptions -> a -> PandocIO Pandoc
r ReaderOptions
forall a. Default a => a
def{ readerExtensions :: Extensions
readerExtensions = Extensions
es } Text
content
Reader PandocIO
_ -> PandocError -> PandocIO Pandoc
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> PandocIO Pandoc) -> PandocError -> PandocIO Pandoc
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocSomeError
Text
"Only textual formats are supported"
case Either PandocError Pandoc
res of
Right Pandoc
pd -> (NumResults
1 :: NumResults) NumResults -> LuaE PandocError () -> LuaE PandocError NumResults
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Pandoc -> LuaE PandocError ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
Lua.push Pandoc
pd
Left (PandocUnknownReaderError Text
f) -> Text -> LuaE PandocError NumResults
forall e a. (PeekError e, Pushable a) => a -> LuaE e NumResults
Lua.raiseError (Text -> LuaE PandocError NumResults)
-> Text -> LuaE PandocError NumResults
forall a b. (a -> b) -> a -> b
$
Text
"Unknown reader: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
f
Left (PandocUnsupportedExtensionError Text
e Text
f) -> Text -> LuaE PandocError NumResults
forall e a. (PeekError e, Pushable a) => a -> LuaE e NumResults
Lua.raiseError (Text -> LuaE PandocError NumResults)
-> Text -> LuaE PandocError NumResults
forall a b. (a -> b) -> a -> b
$
Text
"Extension " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
e Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" not supported for " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
f
Left PandocError
e -> String -> LuaE PandocError NumResults
forall e a. (PeekError e, Pushable a) => a -> LuaE e NumResults
Lua.raiseError (String -> LuaE PandocError NumResults)
-> String -> LuaE PandocError NumResults
forall a b. (a -> b) -> a -> b
$ PandocError -> String
forall a. Show a => a -> String
show PandocError
e
pipe :: String
-> [String]
-> BL.ByteString
-> PandocLua NumResults
pipe :: String -> [String] -> ByteString -> PandocLua NumResults
pipe String
command [String]
args ByteString
input = LuaE PandocError NumResults -> PandocLua NumResults
forall a. LuaE PandocError a -> PandocLua a
liftPandocLua (LuaE PandocError NumResults -> PandocLua NumResults)
-> LuaE PandocError NumResults -> PandocLua NumResults
forall a b. (a -> b) -> a -> b
$ do
(ExitCode
ec, ByteString
output) <- IO (ExitCode, ByteString)
-> LuaE PandocError (ExitCode, ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
Lua.liftIO (IO (ExitCode, ByteString)
-> LuaE PandocError (ExitCode, ByteString))
-> IO (ExitCode, ByteString)
-> LuaE PandocError (ExitCode, ByteString)
forall a b. (a -> b) -> a -> b
$ Maybe [(String, String)]
-> String -> [String] -> ByteString -> IO (ExitCode, ByteString)
pipeProcess Maybe [(String, String)]
forall a. Maybe a
Nothing String
command [String]
args ByteString
input
IO (ExitCode, ByteString)
-> (IOError -> IO (ExitCode, ByteString))
-> IO (ExitCode, ByteString)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` (PandocError -> IO (ExitCode, ByteString)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (PandocError -> IO (ExitCode, ByteString))
-> (IOError -> PandocError) -> IOError -> IO (ExitCode, ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> IOError -> PandocError
PandocIOError Text
"pipe")
case ExitCode
ec of
ExitCode
ExitSuccess -> NumResults
1 NumResults -> LuaE PandocError () -> LuaE PandocError NumResults
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ByteString -> LuaE PandocError ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
Lua.push ByteString
output
ExitFailure Int
n -> do
Pusher PandocError PipeError
forall e. PeekError e => Pusher e PipeError
pushPipeError (Text -> Int -> ByteString -> PipeError
PipeError (String -> Text
T.pack String
command) Int
n ByteString
output)
LuaE PandocError NumResults
forall e. LuaE e NumResults
Lua.error
data PipeError = PipeError
{ PipeError -> Text
pipeErrorCommand :: T.Text
, PipeError -> Int
pipeErrorCode :: Int
, PipeError -> ByteString
pipeErrorOutput :: BL.ByteString
}
peekPipeError :: PeekError e => StackIndex -> LuaE e PipeError
peekPipeError :: 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 (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StackIndex -> LuaE e Text
forall a e. (Peekable a, PeekError e) => StackIndex -> LuaE e a
Lua.peek (-StackIndex
1) LuaE e Text -> LuaE e () -> LuaE e Text
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 (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 (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StackIndex -> LuaE e Int
forall a e. (Peekable a, PeekError e) => StackIndex -> LuaE e a
Lua.peek (-StackIndex
1) LuaE e Int -> LuaE e () -> LuaE e Int
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 (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 (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StackIndex -> LuaE e ByteString
forall a e. (Peekable a, PeekError e) => StackIndex -> LuaE e a
Lua.peek (-StackIndex
1) LuaE e ByteString -> LuaE e () -> LuaE e ByteString
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 :: PeekError e => Pusher e PipeError
pushPipeError :: Pusher e PipeError
pushPipeError PipeError
pipeErr = do
LuaE e ()
forall e. LuaE e ()
Lua.newtable
String -> Text -> LuaE e ()
forall e a. (LuaError e, Pushable a) => String -> a -> LuaE e ()
LuaUtil.addField String
"command" (PipeError -> Text
pipeErrorCommand PipeError
pipeErr)
String -> Int -> LuaE e ()
forall e a. (LuaError e, Pushable a) => String -> a -> LuaE e ()
LuaUtil.addField String
"error_code" (PipeError -> Int
pipeErrorCode PipeError
pipeErr)
String -> ByteString -> LuaE e ()
forall e a. (LuaError e, Pushable a) => String -> a -> LuaE e ()
LuaUtil.addField String
"output" (PipeError -> ByteString
pipeErrorOutput PipeError
pipeErr)
LuaE e ()
forall e. PeekError e => LuaE e ()
pushPipeErrorMetaTable
StackIndex -> LuaE e ()
forall e. StackIndex -> LuaE e ()
Lua.setmetatable (-StackIndex
2)
where
pushPipeErrorMetaTable :: PeekError e => LuaE e ()
pushPipeErrorMetaTable :: LuaE e ()
pushPipeErrorMetaTable = do
Bool
v <- Name -> LuaE e Bool
forall e. Name -> LuaE e Bool
Lua.newmetatable Name
"pandoc pipe error"
Bool -> LuaE e () -> LuaE e ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
v (LuaE e () -> LuaE e ()) -> LuaE e () -> LuaE e ()
forall a b. (a -> b) -> a -> b
$ do
Name -> LuaE e ()
forall e. Name -> LuaE e ()
pushName Name
"__tostring"
HaskellFunction e -> LuaE e ()
forall e. LuaError e => HaskellFunction e -> LuaE e ()
pushHaskellFunction HaskellFunction e
forall e. PeekError e => LuaE e NumResults
pipeErrorMessage
StackIndex -> LuaE e ()
forall e. LuaError e => StackIndex -> LuaE e ()
rawset (CInt -> StackIndex
nth CInt
3)
pipeErrorMessage :: PeekError e => LuaE e NumResults
pipeErrorMessage :: LuaE e NumResults
pipeErrorMessage = do
(PipeError Text
cmd Int
errorCode ByteString
output) <- StackIndex -> LuaE e PipeError
forall e. PeekError e => StackIndex -> LuaE e PipeError
peekPipeError (CInt -> StackIndex
nthBottom CInt
1)
Pusher e ByteString
forall e. Pusher e ByteString
pushByteString Pusher e ByteString
-> ([ByteString] -> ByteString) -> [ByteString] -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BSL.toStrict (ByteString -> ByteString)
-> ([ByteString] -> ByteString) -> [ByteString] -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
BSL.concat ([ByteString] -> LuaE e ()) -> [ByteString] -> LuaE e ()
forall a b. (a -> b) -> a -> b
$
[ String -> ByteString
BSL.pack String
"Error running "
, String -> ByteString
BSL.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
cmd
, String -> ByteString
BSL.pack String
" (error code "
, String -> ByteString
BSL.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
errorCode
, String -> ByteString
BSL.pack String
"): "
, if ByteString
output ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
forall a. Monoid a => a
mempty then String -> ByteString
BSL.pack String
"<no output>" else ByteString
output
]
NumResults -> LuaE e NumResults
forall (m :: * -> *) a. Monad m => a -> m a
return (CInt -> NumResults
NumResults CInt
1)
mkPandoc :: PandocLua NumResults
mkPandoc :: PandocLua NumResults
mkPandoc = LuaE PandocError NumResults -> PandocLua NumResults
forall a. LuaE PandocError a -> PandocLua a
liftPandocLua (LuaE PandocError NumResults -> PandocLua NumResults)
-> LuaE PandocError NumResults -> PandocLua NumResults
forall a b. (a -> b) -> a -> b
$ do
Pandoc
doc <- Peek PandocError Pandoc -> LuaE PandocError Pandoc
forall e a. LuaError e => Peek e a -> LuaE e a
forcePeek (Peek PandocError Pandoc -> LuaE PandocError Pandoc)
-> Peek PandocError Pandoc -> LuaE PandocError Pandoc
forall a b. (a -> b) -> a -> b
$ do
[Block]
blks <- Peeker PandocError [Block]
forall e. LuaError e => Peeker e [Block]
peekBlocks (CInt -> StackIndex
nthBottom CInt
1)
Maybe Meta
mMeta <- Peek PandocError Meta -> Peek PandocError (Maybe Meta)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Peek PandocError Meta -> Peek PandocError (Maybe Meta))
-> Peek PandocError Meta -> Peek PandocError (Maybe Meta)
forall a b. (a -> b) -> a -> b
$ Peeker PandocError Meta
forall e. LuaError e => Peeker e Meta
peekMeta (CInt -> StackIndex
nthBottom CInt
2)
Pandoc -> Peek PandocError Pandoc
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Pandoc -> Peek PandocError Pandoc)
-> Pandoc -> Peek PandocError Pandoc
forall a b. (a -> b) -> a -> b
$ Meta -> [Block] -> Pandoc
Pandoc (Meta -> Maybe Meta -> Meta
forall a. a -> Maybe a -> a
fromMaybe Meta
nullMeta Maybe Meta
mMeta) [Block]
blks
Pandoc -> LuaE PandocError ()
forall e. LuaError e => Pusher e Pandoc
pushPandoc Pandoc
doc
NumResults -> LuaE PandocError NumResults
forall (m :: * -> *) a. Monad m => a -> m a
return NumResults
1