{-# LANGUAGE LambdaCase          #-}
{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE TypeApplications    #-}
module Text.Pandoc.Lua.Custom ( loadCustom ) where
import Control.Exception
import Control.Monad ((<=<), (<$!>))
import Control.Monad.IO.Class (MonadIO)
import Data.Maybe (fromMaybe)
import HsLua as Lua hiding (Operation (Div))
import Text.Pandoc.Class (PandocMonad, findFileWithDataFallback)
import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.Global (Global (..), setGlobals)
import Text.Pandoc.Lua.Init (runLuaWith)
import Text.Pandoc.Lua.Marshal.Format (peekExtensionsConfig)
import Text.Pandoc.Lua.Marshal.Pandoc (peekPandoc)
import Text.Pandoc.Lua.Marshal.WriterOptions (pushWriterOptions)
import Text.Pandoc.Lua.PandocLua (unPandocLua)
import Text.Pandoc.Readers (Reader (..))
import Text.Pandoc.Sources (ToSources(..))
import Text.Pandoc.Scripting (CustomComponents (..))
import Text.Pandoc.Writers (Writer (..))
import qualified Text.Pandoc.Lua.Writer.Classic as Classic
import qualified Text.Pandoc.Class as PandocMonad
loadCustom :: (PandocMonad m, MonadIO m)
           => FilePath -> m (CustomComponents m)
loadCustom :: forall (m :: * -> *).
(PandocMonad m, MonadIO m) =>
FilePath -> m (CustomComponents m)
loadCustom FilePath
luaFile = do
  GCManagedState
luaState <- IO GCManagedState -> m GCManagedState
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO GCManagedState
newGCManagedState
  FilePath
luaFile' <- FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe FilePath
luaFile (Maybe FilePath -> FilePath) -> m (Maybe FilePath) -> m FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
              FilePath -> FilePath -> m (Maybe FilePath)
forall (m :: * -> *).
PandocMonad m =>
FilePath -> FilePath -> m (Maybe FilePath)
findFileWithDataFallback FilePath
"custom"  FilePath
luaFile
  (PandocError -> m (CustomComponents m))
-> (CustomComponents m -> m (CustomComponents m))
-> Either PandocError (CustomComponents m)
-> m (CustomComponents m)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either PandocError -> m (CustomComponents m)
forall a e. Exception e => e -> a
throw CustomComponents m -> m (CustomComponents m)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either PandocError (CustomComponents m) -> m (CustomComponents m))
-> (LuaE PandocError (CustomComponents m)
    -> m (Either PandocError (CustomComponents m)))
-> LuaE PandocError (CustomComponents m)
-> m (CustomComponents m)
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< GCManagedState
-> LuaE PandocError (CustomComponents m)
-> m (Either PandocError (CustomComponents m))
forall (m :: * -> *) a.
(PandocMonad m, MonadIO m) =>
GCManagedState -> LuaE PandocError a -> m (Either PandocError a)
runLuaWith GCManagedState
luaState (LuaE PandocError (CustomComponents m) -> m (CustomComponents m))
-> LuaE PandocError (CustomComponents m) -> m (CustomComponents m)
forall a b. (a -> b) -> a -> b
$ do
    let globals :: [Global]
globals = [ FilePath -> Global
PANDOC_SCRIPT_FILE FilePath
luaFile' ]
    [Global] -> LuaE PandocError ()
setGlobals [Global]
globals
    Maybe FilePath -> LuaE PandocError Status
forall e. Maybe FilePath -> LuaE e Status
dofileTrace (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
luaFile') LuaE PandocError Status
-> (Status -> LuaE PandocError ()) -> LuaE PandocError ()
forall a b.
LuaE PandocError a
-> (a -> LuaE PandocError b) -> LuaE PandocError b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
      Status
OK -> () -> LuaE PandocError ()
forall a. a -> LuaE PandocError a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
      Status
_  -> LuaE PandocError ()
forall e a. LuaError e => LuaE e a
throwErrorAsException
    Maybe ExtensionsConfig
mextsConf <- Name -> LuaE PandocError Type
forall e. LuaError e => Name -> LuaE e Type
rawgetglobal Name
"Extensions" LuaE PandocError Type
-> (Type -> LuaE PandocError (Maybe ExtensionsConfig))
-> LuaE PandocError (Maybe ExtensionsConfig)
forall a b.
LuaE PandocError a
-> (a -> LuaE PandocError b) -> LuaE PandocError b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
      Type
TypeNil      -> Maybe ExtensionsConfig -> LuaE PandocError (Maybe ExtensionsConfig)
forall a. a -> LuaE PandocError a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe ExtensionsConfig
forall a. Maybe a
Nothing
      Type
TypeFunction -> ExtensionsConfig -> Maybe ExtensionsConfig
forall a. a -> Maybe a
Just (ExtensionsConfig -> Maybe ExtensionsConfig)
-> LuaE PandocError ExtensionsConfig
-> LuaE PandocError (Maybe ExtensionsConfig)
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> do
        NumArgs -> NumResults -> LuaE PandocError ()
forall e. LuaError e => NumArgs -> NumResults -> LuaE e ()
callTrace NumArgs
0 NumResults
1
        Peek PandocError ExtensionsConfig
-> LuaE PandocError ExtensionsConfig
forall e a. LuaError e => Peek e a -> LuaE e a
forcePeek (Peek PandocError ExtensionsConfig
 -> LuaE PandocError ExtensionsConfig)
-> Peek PandocError ExtensionsConfig
-> LuaE PandocError ExtensionsConfig
forall a b. (a -> b) -> a -> b
$ Peeker PandocError ExtensionsConfig
forall e. LuaError e => Peeker e ExtensionsConfig
peekExtensionsConfig StackIndex
top Peek PandocError ExtensionsConfig
-> LuaE PandocError () -> Peek PandocError ExtensionsConfig
forall e a b. Peek e a -> LuaE e b -> Peek e a
`lastly` Int -> LuaE PandocError ()
forall e. Int -> LuaE e ()
pop Int
1
      Type
_            -> ExtensionsConfig -> Maybe ExtensionsConfig
forall a. a -> Maybe a
Just (ExtensionsConfig -> Maybe ExtensionsConfig)
-> LuaE PandocError ExtensionsConfig
-> LuaE PandocError (Maybe ExtensionsConfig)
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> do
        Peek PandocError ExtensionsConfig
-> LuaE PandocError ExtensionsConfig
forall e a. LuaError e => Peek e a -> LuaE e a
forcePeek (Peek PandocError ExtensionsConfig
 -> LuaE PandocError ExtensionsConfig)
-> Peek PandocError ExtensionsConfig
-> LuaE PandocError ExtensionsConfig
forall a b. (a -> b) -> a -> b
$ Peeker PandocError ExtensionsConfig
forall e. LuaError e => Peeker e ExtensionsConfig
peekExtensionsConfig StackIndex
top Peek PandocError ExtensionsConfig
-> LuaE PandocError () -> Peek PandocError ExtensionsConfig
forall e a b. Peek e a -> LuaE e b -> Peek e a
`lastly` Int -> LuaE PandocError ()
forall e. Int -> LuaE e ()
pop Int
1
    Maybe Text
mtemplate <- Name -> LuaE PandocError Type
forall e. LuaError e => Name -> LuaE e Type
rawgetglobal Name
"Template" LuaE PandocError Type
-> (Type -> LuaE PandocError (Maybe Text))
-> LuaE PandocError (Maybe Text)
forall a b.
LuaE PandocError a
-> (a -> LuaE PandocError b) -> LuaE PandocError b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
      Type
TypeNil   -> Maybe Text -> LuaE PandocError (Maybe Text)
forall a. a -> LuaE PandocError a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Text
forall a. Maybe a
Nothing
      Type
TypeFunction -> Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text)
-> LuaE PandocError Text -> LuaE PandocError (Maybe Text)
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> do
        NumArgs -> NumResults -> LuaE PandocError ()
forall e. LuaError e => NumArgs -> NumResults -> LuaE e ()
callTrace NumArgs
0 NumResults
1
        Peek PandocError Text -> LuaE PandocError Text
forall e a. LuaError e => Peek e a -> LuaE e a
forcePeek (Peek PandocError Text -> LuaE PandocError Text)
-> Peek PandocError Text -> LuaE PandocError Text
forall a b. (a -> b) -> a -> b
$ Peeker PandocError Text
forall e. Peeker e Text
peekText StackIndex
top Peek PandocError Text
-> LuaE PandocError () -> Peek PandocError Text
forall e a b. Peek e a -> LuaE e b -> Peek e a
`lastly` Int -> LuaE PandocError ()
forall e. Int -> LuaE e ()
pop Int
1
      Type
_ -> Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text)
-> LuaE PandocError Text -> LuaE PandocError (Maybe Text)
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> do
        Peek PandocError Text -> LuaE PandocError Text
forall e a. LuaError e => Peek e a -> LuaE e a
forcePeek (Peek PandocError Text -> LuaE PandocError Text)
-> Peek PandocError Text -> LuaE PandocError Text
forall a b. (a -> b) -> a -> b
$ Peeker PandocError Text
forall e. Peeker e Text
peekText StackIndex
top Peek PandocError Text
-> LuaE PandocError () -> Peek PandocError Text
forall e a b. Peek e a -> LuaE e b -> Peek e a
`lastly` Int -> LuaE PandocError ()
forall e. Int -> LuaE e ()
pop Int
1
    Maybe (Reader m)
mreader <- Name -> LuaE PandocError Type
forall e. LuaError e => Name -> LuaE e Type
rawgetglobal Name
"Reader" LuaE PandocError Type
-> (Type -> LuaE PandocError (Maybe (Reader m)))
-> LuaE PandocError (Maybe (Reader m))
forall a b.
LuaE PandocError a
-> (a -> LuaE PandocError b) -> LuaE PandocError b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
      Type
TypeNil -> do
        Int -> LuaE PandocError ()
forall e. Int -> LuaE e ()
pop Int
1
        Name -> LuaE PandocError Type
forall e. LuaError e => Name -> LuaE e Type
rawgetglobal Name
"ByteStringReader" LuaE PandocError Type
-> (Type -> LuaE PandocError (Maybe (Reader m)))
-> LuaE PandocError (Maybe (Reader m))
forall a b.
LuaE PandocError a
-> (a -> LuaE PandocError b) -> LuaE PandocError b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
          Type
TypeNil -> Maybe (Reader m) -> LuaE PandocError (Maybe (Reader m))
forall a. a -> LuaE PandocError a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (Reader m)
forall a. Maybe a
Nothing
          Type
_ -> do
            StackIndex -> Name -> LuaE PandocError ()
forall e. LuaError e => StackIndex -> Name -> LuaE e ()
setfield StackIndex
registryindex Name
readerField
            Maybe (Reader m) -> LuaE PandocError (Maybe (Reader m))
forall a. a -> LuaE PandocError a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (Reader m) -> LuaE PandocError (Maybe (Reader m)))
-> (Reader m -> Maybe (Reader m))
-> Reader m
-> LuaE PandocError (Maybe (Reader m))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Reader m -> Maybe (Reader m)
forall a. a -> Maybe a
Just (Reader m -> LuaE PandocError (Maybe (Reader m)))
-> Reader m -> LuaE PandocError (Maybe (Reader m))
forall a b. (a -> b) -> a -> b
$ GCManagedState -> Reader m
forall (m :: * -> *). MonadIO m => GCManagedState -> Reader m
byteStringReader GCManagedState
luaState
      Type
_ -> do
        StackIndex -> Name -> LuaE PandocError ()
forall e. LuaError e => StackIndex -> Name -> LuaE e ()
setfield StackIndex
registryindex Name
readerField
        Maybe (Reader m) -> LuaE PandocError (Maybe (Reader m))
forall a. a -> LuaE PandocError a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (Reader m) -> LuaE PandocError (Maybe (Reader m)))
-> (Reader m -> Maybe (Reader m))
-> Reader m
-> LuaE PandocError (Maybe (Reader m))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Reader m -> Maybe (Reader m)
forall a. a -> Maybe a
Just (Reader m -> LuaE PandocError (Maybe (Reader m)))
-> Reader m -> LuaE PandocError (Maybe (Reader m))
forall a b. (a -> b) -> a -> b
$ GCManagedState -> Reader m
forall (m :: * -> *). MonadIO m => GCManagedState -> Reader m
textReader GCManagedState
luaState
    Maybe (Writer m)
mwriter <- Name -> LuaE PandocError Type
forall e. LuaError e => Name -> LuaE e Type
rawgetglobal Name
"Writer" LuaE PandocError Type
-> (Type -> LuaE PandocError (Maybe (Writer m)))
-> LuaE PandocError (Maybe (Writer m))
forall a b.
LuaE PandocError a
-> (a -> LuaE PandocError b) -> LuaE PandocError b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
      Type
TypeNil -> Name -> LuaE PandocError Type
forall e. LuaError e => Name -> LuaE e Type
rawgetglobal Name
"ByteStringWriter" LuaE PandocError Type
-> (Type -> LuaE PandocError (Maybe (Writer m)))
-> LuaE PandocError (Maybe (Writer m))
forall a b.
LuaE PandocError a
-> (a -> LuaE PandocError b) -> LuaE PandocError b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
        Type
TypeNil -> do
          
          
          Type
docType <- Name -> LuaE PandocError Type
forall e. LuaError e => Name -> LuaE e Type
rawgetglobal Name
"Doc"
          Int -> LuaE PandocError ()
forall e. Int -> LuaE e ()
pop Int
3  
          Maybe (Writer m) -> LuaE PandocError (Maybe (Writer m))
forall a. a -> LuaE PandocError a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (Writer m) -> LuaE PandocError (Maybe (Writer m)))
-> Maybe (Writer m) -> LuaE PandocError (Maybe (Writer m))
forall a b. (a -> b) -> a -> b
$
            if Type
docType Type -> Type -> Bool
forall a. Eq a => a -> a -> Bool
/= Type
TypeFunction
            then Maybe (Writer m)
forall a. Maybe a
Nothing
            else Writer m -> Maybe (Writer m)
forall a. a -> Maybe a
Just (Writer m -> Maybe (Writer m))
-> ((WriterOptions -> Pandoc -> m Text) -> Writer m)
-> (WriterOptions -> Pandoc -> m Text)
-> Maybe (Writer m)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (WriterOptions -> Pandoc -> m Text) -> Writer m
forall (m :: * -> *).
(WriterOptions -> Pandoc -> m Text) -> Writer m
TextWriter ((WriterOptions -> Pandoc -> m Text) -> Maybe (Writer m))
-> (WriterOptions -> Pandoc -> m Text) -> Maybe (Writer m)
forall a b. (a -> b) -> a -> b
$ \WriterOptions
opts Pandoc
doc -> do
              
              CommonState
st <- m CommonState
forall (m :: * -> *). PandocMonad m => m CommonState
PandocMonad.getCommonState
              IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ GCManagedState -> LuaE PandocError Text -> IO Text
forall e a. GCManagedState -> LuaE e a -> IO a
withGCManagedState GCManagedState
luaState (LuaE PandocError Text -> IO Text)
-> LuaE PandocError Text -> IO Text
forall a b. (a -> b) -> a -> b
$
                PandocLua () -> LuaE PandocError ()
forall a. PandocLua a -> LuaE PandocError a
unPandocLua (CommonState -> PandocLua ()
forall (m :: * -> *). PandocMonad m => CommonState -> m ()
PandocMonad.putCommonState CommonState
st) LuaE PandocError ()
-> LuaE PandocError Text -> LuaE PandocError Text
forall a b.
LuaE PandocError a -> LuaE PandocError b -> LuaE PandocError b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                forall e. LuaError e => WriterOptions -> Pandoc -> LuaE e Text
Classic.runCustom @PandocError WriterOptions
opts Pandoc
doc
        Type
_ -> Writer m -> Maybe (Writer m)
forall a. a -> Maybe a
Just (Writer m -> Maybe (Writer m))
-> LuaE PandocError (Writer m)
-> LuaE PandocError (Maybe (Writer m))
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> do
          
          StackIndex -> Name -> LuaE PandocError ()
forall e. LuaError e => StackIndex -> Name -> LuaE e ()
setfield StackIndex
registryindex Name
writerField
          Writer m -> LuaE PandocError (Writer m)
forall a. a -> LuaE PandocError a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Writer m -> LuaE PandocError (Writer m))
-> Writer m -> LuaE PandocError (Writer m)
forall a b. (a -> b) -> a -> b
$ (WriterOptions -> Pandoc -> m ByteString) -> Writer m
forall (m :: * -> *).
(WriterOptions -> Pandoc -> m ByteString) -> Writer m
ByteStringWriter ((WriterOptions -> Pandoc -> m ByteString) -> Writer m)
-> (WriterOptions -> Pandoc -> m ByteString) -> Writer m
forall a b. (a -> b) -> a -> b
$ \WriterOptions
opts Pandoc
doc -> do
            
            CommonState
st <- m CommonState
forall (m :: * -> *). PandocMonad m => m CommonState
PandocMonad.getCommonState
            
            IO ByteString -> m ByteString
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> m ByteString) -> IO ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ GCManagedState -> LuaE PandocError ByteString -> IO ByteString
forall e a. GCManagedState -> LuaE e a -> IO a
withGCManagedState GCManagedState
luaState (LuaE PandocError ByteString -> IO ByteString)
-> LuaE PandocError ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$ do
              PandocLua () -> LuaE PandocError ()
forall a. PandocLua a -> LuaE PandocError a
unPandocLua (CommonState -> PandocLua ()
forall (m :: * -> *). PandocMonad m => CommonState -> m ()
PandocMonad.putCommonState CommonState
st)
              StackIndex -> Name -> LuaE PandocError Type
forall e. LuaError e => StackIndex -> Name -> LuaE e Type
getfield StackIndex
registryindex Name
writerField
              Pandoc -> LuaE PandocError ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
forall e. LuaError e => Pandoc -> LuaE e ()
push Pandoc
doc
              Pusher PandocError WriterOptions
pushWriterOptions WriterOptions
opts
              NumArgs -> NumResults -> LuaE PandocError ()
forall e. LuaError e => NumArgs -> NumResults -> LuaE e ()
callTrace NumArgs
2 NumResults
1
              forall e a. LuaError e => Peek e a -> LuaE e a
forcePeek @PandocError (Peek PandocError ByteString -> LuaE PandocError ByteString)
-> Peek PandocError ByteString -> LuaE PandocError ByteString
forall a b. (a -> b) -> a -> b
$ Peeker PandocError ByteString
forall e. Peeker e ByteString
peekLazyByteString StackIndex
top
      Type
_ -> Writer m -> Maybe (Writer m)
forall a. a -> Maybe a
Just (Writer m -> Maybe (Writer m))
-> LuaE PandocError (Writer m)
-> LuaE PandocError (Maybe (Writer m))
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> do
        
        StackIndex -> Name -> LuaE PandocError ()
forall e. LuaError e => StackIndex -> Name -> LuaE e ()
setfield StackIndex
registryindex Name
writerField
        Writer m -> LuaE PandocError (Writer m)
forall a. a -> LuaE PandocError a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Writer m -> LuaE PandocError (Writer m))
-> Writer m -> LuaE PandocError (Writer m)
forall a b. (a -> b) -> a -> b
$ (WriterOptions -> Pandoc -> m Text) -> Writer m
forall (m :: * -> *).
(WriterOptions -> Pandoc -> m Text) -> Writer m
TextWriter ((WriterOptions -> Pandoc -> m Text) -> Writer m)
-> (WriterOptions -> Pandoc -> m Text) -> Writer m
forall a b. (a -> b) -> a -> b
$ \WriterOptions
opts Pandoc
doc -> do
          
          
          
          CommonState
st <- m CommonState
forall (m :: * -> *). PandocMonad m => m CommonState
PandocMonad.getCommonState
          IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ GCManagedState -> LuaE PandocError Text -> IO Text
forall e a. GCManagedState -> LuaE e a -> IO a
withGCManagedState GCManagedState
luaState (LuaE PandocError Text -> IO Text)
-> LuaE PandocError Text -> IO Text
forall a b. (a -> b) -> a -> b
$ do
            PandocLua () -> LuaE PandocError ()
forall a. PandocLua a -> LuaE PandocError a
unPandocLua (CommonState -> PandocLua ()
forall (m :: * -> *). PandocMonad m => CommonState -> m ()
PandocMonad.putCommonState CommonState
st)
            StackIndex -> Name -> LuaE PandocError Type
forall e. LuaError e => StackIndex -> Name -> LuaE e Type
getfield StackIndex
registryindex Name
writerField
            Pandoc -> LuaE PandocError ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
forall e. LuaError e => Pandoc -> LuaE e ()
push Pandoc
doc
            Pusher PandocError WriterOptions
pushWriterOptions WriterOptions
opts
            NumArgs -> NumResults -> LuaE PandocError ()
forall e. LuaError e => NumArgs -> NumResults -> LuaE e ()
callTrace NumArgs
2 NumResults
1
            forall e a. LuaError e => Peek e a -> LuaE e a
forcePeek @PandocError (Peek PandocError Text -> LuaE PandocError Text)
-> Peek PandocError Text -> LuaE PandocError Text
forall a b. (a -> b) -> a -> b
$ Peeker PandocError Text
forall e. Peeker e Text
peekText StackIndex
top
    CustomComponents m -> LuaE PandocError (CustomComponents m)
forall a. a -> LuaE PandocError a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CustomComponents m -> LuaE PandocError (CustomComponents m))
-> CustomComponents m -> LuaE PandocError (CustomComponents m)
forall a b. (a -> b) -> a -> b
$ CustomComponents
      { customReader :: Maybe (Reader m)
customReader = Maybe (Reader m)
mreader
      , customWriter :: Maybe (Writer m)
customWriter = Maybe (Writer m)
mwriter
      , customTemplate :: Maybe Text
customTemplate = Maybe Text
mtemplate
      , customExtensions :: Maybe ExtensionsConfig
customExtensions = Maybe ExtensionsConfig
mextsConf
      }
rawgetglobal :: LuaError e => Name -> LuaE e Lua.Type
rawgetglobal :: forall e. LuaError e => Name -> LuaE e Type
rawgetglobal Name
x = do
  LuaE e ()
forall e. LuaE e ()
pushglobaltable
  Name -> LuaE e ()
forall e. Name -> LuaE e ()
pushName Name
x
  StackIndex -> LuaE e Type
forall e. LuaError e => StackIndex -> LuaE e Type
rawget (CInt -> StackIndex
nth CInt
2) LuaE e Type -> LuaE e () -> LuaE e Type
forall a b. LuaE e a -> LuaE e b -> LuaE e a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* StackIndex -> LuaE e ()
forall e. StackIndex -> LuaE e ()
remove (CInt -> StackIndex
nth CInt
2) 
readerField :: Name
readerField :: Name
readerField = Name
"Pandoc Reader function"
writerField :: Name
writerField :: Name
writerField = Name
"Pandoc Writer function"
inLua :: MonadIO m => GCManagedState -> LuaE PandocError a -> m a
inLua :: forall (m :: * -> *) a.
MonadIO m =>
GCManagedState -> LuaE PandocError a -> m a
inLua GCManagedState
st = IO a -> m a
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO a -> m a)
-> (LuaE PandocError a -> IO a) -> LuaE PandocError a -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a. GCManagedState -> LuaE e a -> IO a
withGCManagedState @PandocError GCManagedState
st
byteStringReader :: MonadIO m => GCManagedState -> Reader m
byteStringReader :: forall (m :: * -> *). MonadIO m => GCManagedState -> Reader m
byteStringReader GCManagedState
st = (ReaderOptions -> ByteString -> m Pandoc) -> Reader m
forall (m :: * -> *).
(ReaderOptions -> ByteString -> m Pandoc) -> Reader m
ByteStringReader ((ReaderOptions -> ByteString -> m Pandoc) -> Reader m)
-> (ReaderOptions -> ByteString -> m Pandoc) -> Reader m
forall a b. (a -> b) -> a -> b
$ \ReaderOptions
ropts ByteString
input -> GCManagedState -> LuaE PandocError Pandoc -> m Pandoc
forall (m :: * -> *) a.
MonadIO m =>
GCManagedState -> LuaE PandocError a -> m a
inLua GCManagedState
st (LuaE PandocError Pandoc -> m Pandoc)
-> LuaE PandocError Pandoc -> m Pandoc
forall a b. (a -> b) -> a -> b
$ do
  StackIndex -> Name -> LuaE PandocError Type
forall e. LuaError e => StackIndex -> Name -> LuaE e Type
getfield StackIndex
registryindex Name
readerField
  ByteString -> LuaE PandocError ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
forall e. LuaError e => ByteString -> LuaE e ()
push ByteString
input
  ReaderOptions -> LuaE PandocError ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
forall e. LuaError e => ReaderOptions -> LuaE e ()
push ReaderOptions
ropts
  NumArgs -> NumResults -> LuaE PandocError Status
forall e. NumArgs -> NumResults -> LuaE e Status
pcallTrace NumArgs
2 NumResults
1 LuaE PandocError Status
-> (Status -> LuaE PandocError Pandoc) -> LuaE PandocError Pandoc
forall a b.
LuaE PandocError a
-> (a -> LuaE PandocError b) -> LuaE PandocError b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    Status
OK -> 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
$ Peeker PandocError Pandoc
forall e. LuaError e => Peeker e Pandoc
peekPandoc StackIndex
top
    Status
_ -> LuaE PandocError Pandoc
forall e a. LuaError e => LuaE e a
throwErrorAsException
textReader :: MonadIO m => GCManagedState -> Reader m
textReader :: forall (m :: * -> *). MonadIO m => GCManagedState -> Reader m
textReader GCManagedState
st = (forall a. ToSources a => ReaderOptions -> a -> m Pandoc)
-> Reader m
forall (m :: * -> *).
(forall a. ToSources a => ReaderOptions -> a -> m Pandoc)
-> Reader m
TextReader ((forall a. ToSources a => ReaderOptions -> a -> m Pandoc)
 -> Reader m)
-> (forall a. ToSources a => ReaderOptions -> a -> m Pandoc)
-> Reader m
forall a b. (a -> b) -> a -> b
$ \ReaderOptions
ropts a
srcs -> GCManagedState -> LuaE PandocError Pandoc -> m Pandoc
forall (m :: * -> *) a.
MonadIO m =>
GCManagedState -> LuaE PandocError a -> m a
inLua GCManagedState
st (LuaE PandocError Pandoc -> m Pandoc)
-> LuaE PandocError Pandoc -> m Pandoc
forall a b. (a -> b) -> a -> b
$ do
  let input :: Sources
input = a -> Sources
forall a. ToSources a => a -> Sources
toSources a
srcs
  StackIndex -> Name -> LuaE PandocError Type
forall e. LuaError e => StackIndex -> Name -> LuaE e Type
getfield StackIndex
registryindex Name
readerField
  Sources -> LuaE PandocError ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
forall e. LuaError e => Sources -> LuaE e ()
push Sources
input
  ReaderOptions -> LuaE PandocError ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
forall e. LuaError e => ReaderOptions -> LuaE e ()
push ReaderOptions
ropts
  NumArgs -> NumResults -> LuaE PandocError Status
forall e. NumArgs -> NumResults -> LuaE e Status
pcallTrace NumArgs
2 NumResults
1 LuaE PandocError Status
-> (Status -> LuaE PandocError Pandoc) -> LuaE PandocError Pandoc
forall a b.
LuaE PandocError a
-> (a -> LuaE PandocError b) -> LuaE PandocError b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    Status
OK -> 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
$ Peeker PandocError Pandoc
forall e. LuaError e => Peeker e Pandoc
peekPandoc StackIndex
top
    Status
_ -> LuaE PandocError Pandoc
forall e a. LuaError e => LuaE e a
throwErrorAsException