{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Foreign.Lua.Core.Error
( Exception (..)
, catchException
, throwException
, withExceptionMessage
, throwErrorAsException
, throwTopMessage
, throwTopMessageWithState
, errorMessage
, try
, throwMessage
, liftLuaThrow
) where
import Control.Applicative (Alternative (..))
import Data.Typeable (Typeable)
import Foreign.Lua.Core.Types (Lua)
import Foreign.Lua.Raw.Error (errorMessage)
import Foreign.Lua.Raw.Functions (lua_pushlstring)
import Foreign.Marshal.Alloc (alloca)
import Foreign.Ptr
import qualified Data.ByteString.Unsafe as B
import qualified Control.Exception as E
import qualified Control.Monad.Catch as Catch
import qualified Foreign.Lua.Core.Types as Lua
import qualified Foreign.Lua.Utf8 as Utf8
import qualified Foreign.Storable as F
newtype Exception = Exception { exceptionMessage :: String}
deriving (Eq, Typeable)
instance Show Exception where
show (Exception msg) = "Lua exception: " ++ msg
instance E.Exception Exception
throwException :: String -> Lua a
throwException = Catch.throwM . Exception
{-# INLINABLE throwException #-}
catchException :: Lua a -> (Exception -> Lua a) -> Lua a
catchException = Catch.catch
{-# INLINABLE catchException #-}
withExceptionMessage :: (String -> String) -> Lua a -> Lua a
withExceptionMessage modifier luaOp =
luaOp `catchException` \(Exception msg) -> throwException (modifier msg)
{-# INLINABLE withExceptionMessage #-}
try :: Lua a -> Lua (Either Exception a)
try = Catch.try
{-# INLINABLE try #-}
throwErrorAsException :: Lua a
throwErrorAsException = do
f <- Lua.errorToException <$> Lua.errorConversion
l <- Lua.state
Lua.liftIO (f l)
throwTopMessage :: Lua a
throwTopMessage = throwErrorAsException
throwMessage :: String -> Lua a
throwMessage msg = do
Lua.liftLua $ \l ->
B.unsafeUseAsCStringLen (Utf8.fromString msg) $ \(msgPtr, z) ->
lua_pushlstring l msgPtr (fromIntegral z)
Lua.errorConversion >>= Lua.liftLua . Lua.errorToException
instance Alternative Lua where
empty = throwMessage "empty"
x <|> y = do
alt <- Lua.alternative <$> Lua.errorConversion
x `alt` y
throwTopMessageWithState :: Lua.State -> IO a
throwTopMessageWithState l = do
msg <- Lua.liftIO (errorMessage l)
Catch.throwM $ Exception (Utf8.toString msg)
liftLuaThrow :: (Lua.State -> Ptr Lua.StatusCode -> IO a) -> Lua a
liftLuaThrow f = do
(result, status) <- Lua.liftLua $ \l -> alloca $ \statusPtr -> do
result <- f l statusPtr
status <- Lua.toStatus <$> F.peek statusPtr
return (result, status)
if status == Lua.OK
then return result
else throwTopMessage