From fb54f3d6792d2f8e7b05e458b59142f8ae6bb3e2 Mon Sep 17 00:00:00 2001
From: Albert Krewinkel <albert@zeitkraut.de>
Date: Wed, 25 Mar 2020 22:16:27 +0100
Subject: API change: use PandocError for exceptions in Lua subsystem

The PandocError type is used throughout the Lua subsystem, all Lua
functions throw an exception of this type if an error occurs. The
`LuaException` type is removed and no longer exported from
`Text.Pandoc.Lua`. In its place, a new constructor `PandocLuaError` is
added to PandocError.
---
 src/Text/Pandoc/Lua/Module/Utils.hs | 19 +++++++++++--------
 1 file changed, 11 insertions(+), 8 deletions(-)

(limited to 'src/Text/Pandoc/Lua/Module')

diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs
index 11a0bda84..36bb2f59c 100644
--- a/src/Text/Pandoc/Lua/Module/Utils.hs
+++ b/src/Text/Pandoc/Lua/Module/Utils.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE ScopedTypeVariables #-}
 {- |
    Module      : Text.Pandoc.Lua.Module.Utils
    Copyright   : Copyright © 2017-2020 Albert Krewinkel
@@ -13,6 +14,7 @@ module Text.Pandoc.Lua.Module.Utils
   ) where
 
 import Control.Applicative ((<|>))
+import Control.Monad.Catch (try)
 import Data.Default (def)
 import Data.Version (Version)
 import Foreign.Lua (Peekable, Lua, NumResults)
@@ -20,6 +22,7 @@ import Text.Pandoc.Class.PandocIO (runIO)
 import Text.Pandoc.Class.PandocMonad (setUserDataDir)
 import Text.Pandoc.Definition ( Pandoc, Meta, MetaValue (..), Block, Inline
                               , Citation, Attr, ListAttributes)
+import Text.Pandoc.Error (PandocError)
 import Text.Pandoc.Lua.Marshaling ()
 import Text.Pandoc.Lua.Util (addFunction)
 
@@ -125,16 +128,16 @@ data AstElement
 
 instance Peekable AstElement where
   peek idx  = do
-    res <- Lua.try $  (PandocElement <$> Lua.peek idx)
-                  <|> (InlineElement <$> Lua.peek idx)
-                  <|> (BlockElement <$> Lua.peek idx)
-                  <|> (AttrElement <$> Lua.peek idx)
-                  <|> (ListAttributesElement <$> Lua.peek idx)
-                  <|> (MetaElement <$> Lua.peek idx)
-                  <|> (MetaValueElement <$> Lua.peek idx)
+    res <- try $  (PandocElement <$> Lua.peek idx)
+              <|> (InlineElement <$> Lua.peek idx)
+              <|> (BlockElement <$> Lua.peek idx)
+              <|> (AttrElement <$> Lua.peek idx)
+              <|> (ListAttributesElement <$> Lua.peek idx)
+              <|> (MetaElement <$> Lua.peek idx)
+              <|> (MetaValueElement <$> Lua.peek idx)
     case res of
       Right x -> return x
-      Left _ -> Lua.throwException
+      Left (_ :: PandocError) -> Lua.throwMessage
         "Expected an AST element, but could not parse value as such."
 
 -- | Convert a number < 4000 to uppercase roman numeral.
-- 
cgit v1.2.3