{-# LANGUAGE LambdaCase          #-}
{-# LANGUAGE OverloadedStrings   #-}
module Text.Pandoc.Readers.Custom ( readCustom ) where
import Control.Exception
import Control.Monad (when)
import Control.Monad.IO.Class (MonadIO)
import Data.Maybe (fromMaybe)
import HsLua as Lua hiding (Operation (Div))
import Text.Pandoc.Definition
import Text.Pandoc.Class (PandocMonad, findFileWithDataFallback, report)
import Text.Pandoc.Logging
import Text.Pandoc.Lua (Global (..), runLua, setGlobals)
import Text.Pandoc.Lua.PandocLua
import Text.Pandoc.Lua.Marshal.Pandoc (peekPandoc)
import Text.Pandoc.Options
import Text.Pandoc.Sources (ToSources(..), sourcesToText)
import qualified Data.Text as T
readCustom :: (PandocMonad m, MonadIO m, ToSources s)
            => FilePath -> ReaderOptions -> s -> m Pandoc
readCustom :: forall (m :: * -> *) s.
(PandocMonad m, MonadIO m, ToSources s) =>
FilePath -> ReaderOptions -> s -> m Pandoc
readCustom FilePath
luaFile ReaderOptions
opts s
srcs = do
  let globals :: [Global]
globals = [ FilePath -> Global
PANDOC_SCRIPT_FILE FilePath
luaFile ]
  FilePath
luaFile' <- forall a. a -> Maybe a -> a
fromMaybe FilePath
luaFile forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *).
PandocMonad m =>
FilePath -> FilePath -> m (Maybe FilePath)
findFileWithDataFallback FilePath
"readers" FilePath
luaFile
  Either PandocError Pandoc
res <- forall (m :: * -> *) a.
(PandocMonad m, MonadIO m) =>
LuaE PandocError a -> m (Either PandocError a)
runLua forall a b. (a -> b) -> a -> b
$ do
    [Global] -> LuaE PandocError ()
setGlobals [Global]
globals
    Status
stat <- forall e. FilePath -> LuaE e Status
dofileTrace FilePath
luaFile'
    
    
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Status
stat forall a. Eq a => a -> a -> Bool
/= Status
Lua.OK)
      forall e a. LuaError e => LuaE e a
Lua.throwErrorAsException
    LuaE PandocError Pandoc
parseCustom
  case Either PandocError Pandoc
res of
    Left PandocError
msg -> forall a e. Exception e => e -> a
throw PandocError
msg
    Right Pandoc
doc -> forall (m :: * -> *) a. Monad m => a -> m a
return Pandoc
doc
 where
  parseCustom :: LuaE PandocError Pandoc
parseCustom = do
    let input :: Sources
input = forall a. ToSources a => a -> Sources
toSources s
srcs
    forall e. LuaError e => Name -> LuaE e Type
getglobal Name
"Reader"
    forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
push Sources
input
    forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
push ReaderOptions
opts
    forall e. NumArgs -> NumResults -> LuaE e Status
pcallTrace NumArgs
2 NumResults
1 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
      Status
OK -> forall e a. LuaError e => Peek e a -> LuaE e a
forcePeek forall a b. (a -> b) -> a -> b
$ forall e. LuaError e => Peeker e Pandoc
peekPandoc StackIndex
top
      Status
ErrRun -> do
        
        
        forall e a. Peek e a -> LuaE e (Result a)
runPeek (forall e. Peeker e Text
peekText StackIndex
top) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
          Failure {} ->
            
            forall e a. LuaError e => LuaE e a
throwErrorAsException
          Success Text
errmsg -> do
            if Text
"string expected, got pandoc Sources" Text -> Text -> Bool
`T.isInfixOf` Text
errmsg
              then do
                forall e. Int -> LuaE e ()
pop Int
1
                ()
_ <- forall a. PandocLua a -> LuaE PandocError a
unPandocLua forall a b. (a -> b) -> a -> b
$ do
                  forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report forall a b. (a -> b) -> a -> b
$ Text -> Text -> LogMessage
Deprecated Text
"old Reader function signature" forall a b. (a -> b) -> a -> b
$
                    [Text] -> Text
T.unlines
                    [ Text
"Reader functions should accept a sources list; "
                    , Text
"functions expecting `string` input are deprecated. "
                    , Text
"Use `tostring` to convert the first argument to a "
                    , Text
"string."
                    ]
                forall e. LuaError e => Name -> LuaE e Type
getglobal Name
"Reader"
                forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
push forall a b. (a -> b) -> a -> b
$ Sources -> Text
sourcesToText Sources
input  
                forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
push ReaderOptions
opts
                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 forall a b. (a -> b) -> a -> b
$ forall e. LuaError e => Peeker e Pandoc
peekPandoc StackIndex
top
              else
                
                forall e a. LuaError e => LuaE e a
throwErrorAsException
      Status
_ ->  
        forall e a. LuaError e => LuaE e a
throwErrorAsException