blob: 6f29a5c89fcb92cbd41769cbd30ac91002acdb9a (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
|
{-# 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 = deftype "PandocError"
[ operation Tostring $ defun "__tostring"
### liftPure (show @PandocError)
<#> udparam typePandocError "obj" "PandocError object"
=#> functionResult pushString "string" "string representation of error."
]
mempty -- no members
-- | Peek a @'PandocError'@ element to the Lua stack.
pushPandocError :: LuaError e => Pusher e PandocError
pushPandocError = pushUD typePandocError
-- | Retrieve a @'PandocError'@ from the Lua stack.
peekPandocError :: LuaError e => Peeker e PandocError
peekPandocError idx = Lua.retrieving "PandocError" $
liftLua (Lua.ltype idx) >>= \case
Lua.TypeUserdata -> peekUD typePandocError idx
_ -> do
msg <- liftLua $ Lua.state >>= \l -> Lua.liftIO (Lua.popErrorMessage l)
return $ PandocLuaError (UTF8.toText msg)
|