{-# LANGUAGE LambdaCase           #-}
{-# LANGUAGE OverloadedStrings    #-}
{-# LANGUAGE ScopedTypeVariables  #-}
{-# LANGUAGE TypeApplications     #-}
{- |
   Module      : Text.Pandoc.Lua.Marshaling.PandocError
   Copyright   : © 2020-2021 Albert Krewinkel
   License     : GNU GPL, version 2 or above

   Maintainer  : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
   Stability   : alpha

Marshaling of @'PandocError'@ values.
-}
module Text.Pandoc.Lua.Marshaling.PandocError
  ( peekPandocError
  , pushPandocError
  , typePandocError
  )
  where

import HsLua.Core (LuaError)
import HsLua.Marshalling (Peeker, Pusher, pushString, liftLua)
import HsLua.Packaging
import Text.Pandoc.Error (PandocError (PandocLuaError))

import qualified HsLua as Lua
import qualified Text.Pandoc.UTF8 as UTF8

-- | Lua userdata type definition for PandocError.
typePandocError :: LuaError e => DocumentedType e PandocError
typePandocError :: DocumentedType e PandocError
typePandocError = Name
-> [(Operation, DocumentedFunction e)]
-> [Member e (DocumentedFunction e) PandocError]
-> DocumentedType e PandocError
forall e a.
LuaError e =>
Name
-> [(Operation, DocumentedFunction e)]
-> [Member e (DocumentedFunction e) a]
-> DocumentedType e a
deftype Name
"PandocError"
  [ Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall e.
Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
operation Operation
Tostring (DocumentedFunction e -> (Operation, DocumentedFunction e))
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall a b. (a -> b) -> a -> b
$ Name
-> (PandocError -> LuaE e String)
-> HsFnPrecursor e (PandocError -> LuaE e String)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"__tostring"
    ### liftPure (show @PandocError)
    HsFnPrecursor e (PandocError -> LuaE e String)
-> Parameter e PandocError -> HsFnPrecursor e (LuaE e String)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> DocumentedType e PandocError
-> Text -> Text -> Parameter e PandocError
forall e a itemtype.
LuaError e =>
DocumentedTypeWithList e a itemtype
-> Text -> Text -> Parameter e a
udparam DocumentedType e PandocError
forall e. LuaError e => DocumentedType e PandocError
typePandocError Text
"obj" Text
"PandocError object"
    HsFnPrecursor e (LuaE e String)
-> FunctionResults e String -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e String -> Text -> Text -> FunctionResults e String
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e String
forall e. String -> LuaE e ()
pushString Text
"string" Text
"string representation of error."
  ]
  [Member e (DocumentedFunction e) PandocError]
forall a. Monoid a => a
mempty -- no members

-- | Peek a @'PandocError'@ element to the Lua stack.
pushPandocError :: LuaError e => Pusher e PandocError
pushPandocError :: Pusher e PandocError
pushPandocError = UDTypeWithList e (DocumentedFunction e) PandocError Void
-> Pusher e PandocError
forall e fn a itemtype.
LuaError e =>
UDTypeWithList e fn a itemtype -> a -> LuaE e ()
pushUD UDTypeWithList e (DocumentedFunction e) PandocError Void
forall e. LuaError e => DocumentedType e PandocError
typePandocError

-- | Retrieve a @'PandocError'@ from the Lua stack.
peekPandocError :: LuaError e => Peeker e PandocError
peekPandocError :: Peeker e PandocError
peekPandocError StackIndex
idx = Name -> Peek e PandocError -> Peek e PandocError
forall e a. Name -> Peek e a -> Peek e a
Lua.retrieving Name
"PandocError" (Peek e PandocError -> Peek e PandocError)
-> Peek e PandocError -> Peek e PandocError
forall a b. (a -> b) -> a -> b
$
  LuaE e Type -> Peek e Type
forall e a. LuaE e a -> Peek e a
liftLua (StackIndex -> LuaE e Type
forall e. StackIndex -> LuaE e Type
Lua.ltype StackIndex
idx) Peek e Type -> (Type -> Peek e PandocError) -> Peek e PandocError
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    Type
Lua.TypeUserdata -> UDTypeWithList e (DocumentedFunction e) PandocError Void
-> Peeker e PandocError
forall e fn a itemtype.
LuaError e =>
UDTypeWithList e fn a itemtype -> Peeker e a
peekUD UDTypeWithList e (DocumentedFunction e) PandocError Void
forall e. LuaError e => DocumentedType e PandocError
typePandocError StackIndex
idx
    Type
_ -> do
      ByteString
msg <- LuaE e ByteString -> Peek e ByteString
forall e a. LuaE e a -> Peek e a
liftLua (LuaE e ByteString -> Peek e ByteString)
-> LuaE e ByteString -> Peek e ByteString
forall a b. (a -> b) -> a -> b
$ LuaE e State
forall e. LuaE e State
Lua.state LuaE e State -> (State -> LuaE e ByteString) -> LuaE e ByteString
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \State
l -> IO ByteString -> LuaE e ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
Lua.liftIO (State -> IO ByteString
Lua.popErrorMessage State
l)
      PandocError -> Peek e PandocError
forall (m :: * -> *) a. Monad m => a -> m a
return (PandocError -> Peek e PandocError)
-> PandocError -> Peek e PandocError
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocLuaError (ByteString -> Text
UTF8.toText ByteString
msg)