{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Foreign.Lua.Core.Error
( Exception (..)
, catchException
, throwException
, withExceptionMessage
, throwTopMessage
, try
, Failable (..)
, fromFailable
, throwOnError
, boolFromFailable
, hsluaErrorRegistryField
) where
import Control.Applicative (Alternative (..))
import Data.Typeable (Typeable)
import Foreign.C (CChar, CInt (CInt), CSize)
import Foreign.Marshal.Alloc (alloca)
import Foreign.Ptr (Ptr, nullPtr)
import Foreign.Lua.Core.Types (Lua, StackIndex, fromLuaBool)
import qualified Control.Exception as E
import qualified Control.Monad.Catch as Catch
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as Char8
import qualified Foreign.Storable as Storable
import qualified Foreign.Lua.Core.Types as Lua
import qualified Foreign.Lua.Utf8 as Utf8
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 #-}
instance Alternative Lua where
empty = throwException "empty"
x <|> y = either (const y) return =<< try x
throwTopMessage :: Lua a
throwTopMessage = do
l <- Lua.state
msg <- Lua.liftIO (errorMessage l)
throwException (Utf8.toString msg)
errorMessage :: Lua.State -> IO B.ByteString
errorMessage l = alloca $ \lenPtr -> do
cstr <- hsluaL_tolstring l Lua.stackTop lenPtr
if cstr == nullPtr
then return $ Char8.pack ("An error occurred, but the error object " ++
"cannot be converted into a string.")
else do
cstrLen <- Storable.peek lenPtr
msg <- B.packCStringLen (cstr, fromIntegral cstrLen)
lua_pop l 2
return msg
foreign import ccall safe "error-conversion.h hsluaL_tolstring"
hsluaL_tolstring :: Lua.State -> StackIndex -> Ptr CSize -> IO (Ptr CChar)
foreign import capi unsafe "lua.h lua_pop"
lua_pop :: Lua.State -> CInt -> IO ()
hsluaErrorRegistryField :: String
hsluaErrorRegistryField = "HSLUA_ERR"
newtype Failable a = Failable CInt
fromFailable :: (CInt -> a) -> Failable a -> Lua a
fromFailable fromCInt (Failable x) =
if x < 0
then throwTopMessage
else return (fromCInt x)
throwOnError :: Failable () -> Lua ()
throwOnError = fromFailable (const ())
boolFromFailable :: Failable Lua.LuaBool -> Lua Bool
boolFromFailable = fmap fromLuaBool . fromFailable Lua.LuaBool