{-# LANGUAGE LambdaCase           #-}
{-# LANGUAGE OverloadedStrings    #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Text.Pandoc.Lua.Marshal.Template
  ( pushTemplate
  , peekTemplate
  , typeTemplate
  ) where
import Data.Text (Text)
import HsLua as Lua
import HsLua.Core.Utf8 as Lua
import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.PandocLua (unPandocLua)
import Text.Pandoc.Templates (Template, compileTemplate, runWithDefaultPartials)
pushTemplate :: LuaError e => Pusher e (Template Text)
pushTemplate :: forall e. LuaError e => Pusher e (Template Text)
pushTemplate = DocumentedTypeWithList e (Template Text) Void
-> Template Text -> LuaE e ()
forall e a itemtype.
LuaError e =>
DocumentedTypeWithList e a itemtype -> a -> LuaE e ()
pushUD DocumentedTypeWithList e (Template Text) Void
forall e. LuaError e => DocumentedType e (Template Text)
typeTemplate
peekTemplate :: Peeker PandocError (Template Text)
peekTemplate :: Peeker PandocError (Template Text)
peekTemplate StackIndex
idx = LuaE PandocError Type -> Peek PandocError Type
forall e a. LuaE e a -> Peek e a
liftLua (StackIndex -> LuaE PandocError Type
forall e. StackIndex -> LuaE e Type
ltype StackIndex
idx) Peek PandocError Type
-> (Type -> Peek PandocError (Template Text))
-> Peek PandocError (Template Text)
forall a b.
Peek PandocError a
-> (a -> Peek PandocError b) -> Peek PandocError b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
  Type
TypeString -> do
    let path :: FilePath
path = FilePath
"templates/default.custom"
    let liftPM :: PandocLua a -> Peek PandocError a
liftPM = LuaE PandocError a -> Peek PandocError a
forall e a. LuaE e a -> Peek e a
liftLua (LuaE PandocError a -> Peek PandocError a)
-> (PandocLua a -> LuaE PandocError a)
-> PandocLua a
-> Peek PandocError a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PandocLua a -> LuaE PandocError a
forall a. PandocLua a -> LuaE PandocError a
unPandocLua
    Text
tmpl <- Peeker PandocError Text
forall e. Peeker e Text
peekText StackIndex
idx
    PandocLua (Either FilePath (Template Text))
-> Peek PandocError (Either FilePath (Template Text))
forall {a}. PandocLua a -> Peek PandocError a
liftPM (WithDefaultPartials PandocLua (Either FilePath (Template Text))
-> PandocLua (Either FilePath (Template Text))
forall (m :: * -> *) a. WithDefaultPartials m a -> m a
runWithDefaultPartials (FilePath
-> Text
-> WithDefaultPartials PandocLua (Either FilePath (Template Text))
forall (m :: * -> *) a.
(TemplateMonad m, TemplateTarget a) =>
FilePath -> Text -> m (Either FilePath (Template a))
compileTemplate FilePath
path Text
tmpl)) Peek PandocError (Either FilePath (Template Text))
-> (Either FilePath (Template Text)
    -> Peek PandocError (Template Text))
-> Peek PandocError (Template Text)
forall a b.
Peek PandocError a
-> (a -> Peek PandocError b) -> Peek PandocError b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
      Left FilePath
e  -> ByteString -> Peek PandocError (Template Text)
forall a e. ByteString -> Peek e a
failPeek (FilePath -> ByteString
Lua.fromString FilePath
e)
      Right Template Text
t -> Template Text -> Peek PandocError (Template Text)
forall a. a -> Peek PandocError a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Template Text
t
  Type
_ -> DocumentedTypeWithList PandocError (Template Text) Void
-> Peeker PandocError (Template Text)
forall e a itemtype.
LuaError e =>
DocumentedTypeWithList e a itemtype -> Peeker e a
peekUD DocumentedTypeWithList PandocError (Template Text) Void
forall e. LuaError e => DocumentedType e (Template Text)
typeTemplate StackIndex
idx
typeTemplate :: LuaError e => DocumentedType e (Template Text)
typeTemplate :: forall e. LuaError e => DocumentedType e (Template Text)
typeTemplate = Name
-> [(Operation, DocumentedFunction e)]
-> [Member e (DocumentedFunction e) (Template Text)]
-> DocumentedType e (Template Text)
forall e a.
LuaError e =>
Name
-> [(Operation, DocumentedFunction e)]
-> [Member e (DocumentedFunction e) a]
-> DocumentedType e a
deftype Name
"pandoc Template" [] []