module B9.B9Error
( throwSomeException,
throwSomeException_,
throwB9Error,
throwB9Error_,
errorOnException,
ExcB9,
WithIoExceptions,
runExcB9,
B9Error (MkB9Error),
fromB9Error,
catchB9Error,
catchB9ErrorAsEither,
finallyB9,
)
where
import Control.Eff as Eff
import Control.Eff.Exception as Eff
import Control.Exception
( Exception,
SomeException,
toException,
)
import qualified Control.Exception as IOExc
import Control.Monad
import Data.String (IsString (..))
type ExcB9 = Exc SomeException
type WithIoExceptions e = SetMember Exc (Exc SomeException) e
newtype B9Error = MkB9Error {fromB9Error :: String}
deriving (IsString)
instance Show B9Error where
show (MkB9Error msg) = "B9 internal error: " ++ msg
instance Exception B9Error
runExcB9 :: Eff (ExcB9 ': e) a -> Eff e (Either SomeException a)
runExcB9 = runError
errorOnException :: Lifted IO e => Eff (ExcB9 ': e) a -> Eff e a
errorOnException = runError >=> either (lift . IOExc.throw) pure
throwSomeException :: (Member ExcB9 e, Exception x) => x -> Eff e a
throwSomeException = throwError . toException
throwSomeException_ :: (Member ExcB9 e, Exception x) => x -> Eff e ()
throwSomeException_ = throwError_ . toException
throwB9Error :: Member ExcB9 e => String -> Eff e a
throwB9Error = throwSomeException . MkB9Error
throwB9Error_ :: Member ExcB9 e => String -> Eff e ()
throwB9Error_ = throwSomeException_ . MkB9Error
catchB9Error ::
Member ExcB9 e => Eff e a -> (SomeException -> Eff e a) -> Eff e a
catchB9Error = catchError
catchB9ErrorAsEither ::
Member ExcB9 e => Eff e a -> Eff e (Either SomeException a)
catchB9ErrorAsEither x = catchB9Error (Right <$> x) (pure . Left)
finallyB9 :: Member ExcB9 e => Eff e a -> Eff e () -> Eff e a
finallyB9 mainAction cleanupAction =
catchB9Error
( do
res <- mainAction
cleanupAction
return res
)
(\e -> cleanupAction >> throwSomeException e)