blob: f698704e06bc77fffb20d54dd35c18b3a02932be (
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
52
53
54
55
56
57
58
59
60
61
62
63
64
65
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{- |
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
)
where
import Foreign.Lua (Lua, Peekable, Pushable, StackIndex)
import Text.Pandoc.Error (PandocError (PandocLuaError))
import qualified Foreign.Lua as Lua
import qualified Foreign.Lua.Userdata as Lua
import qualified Text.Pandoc.Lua.Util as LuaUtil
import qualified Text.Pandoc.UTF8 as UTF8
-- | Userdata name used by Lua for the @PandocError@ type.
pandocErrorName :: String
pandocErrorName = "pandoc error"
-- | Peek a @'PandocError'@ element to the Lua stack.
pushPandocError :: PandocError -> Lua ()
pushPandocError = Lua.pushAnyWithMetatable pushPandocErrorMT
where
pushPandocErrorMT = Lua.ensureUserdataMetatable pandocErrorName $
LuaUtil.addFunction "__tostring" __tostring
-- | Retrieve a @'PandocError'@ from the Lua stack.
peekPandocError :: StackIndex -> Lua PandocError
peekPandocError idx = Lua.ltype idx >>= \case
Lua.TypeUserdata -> do
errMb <- Lua.toAnyWithName idx pandocErrorName
return $ case errMb of
Just err -> err
Nothing -> PandocLuaError "could not retrieve original error"
_ -> do
Lua.pushvalue idx
msg <- Lua.state >>= \l -> Lua.liftIO (Lua.errorMessage l)
return $ PandocLuaError (UTF8.toText msg)
-- | Convert to string.
__tostring :: PandocError -> Lua String
__tostring = return . show
--
-- Instances
--
instance Pushable PandocError where
push = pushPandocError
instance Peekable PandocError where
peek = peekPandocError
|