{-# LANGUAGE OverloadedStrings #-}
module Capnp.Rpc.Errors
(
wrapException
, eMethodUnimplemented
, eUnimplemented
, eDisconnected
, eFailed
, throwFailed
) where
import Data.Default (Default(def))
import Data.Maybe (fromMaybe)
import Data.String (fromString)
import Data.Text (Text)
import qualified Control.Exception.Safe as E
import Capnp.Gen.Capnp.Rpc.Pure (Exception(..), Exception'Type(..))
eFailed :: Text -> Exception
eFailed reason = def
{ type_ = Exception'Type'failed
, reason = reason
}
eDisconnected :: Exception
eDisconnected = def
{ type_ = Exception'Type'disconnected
, reason = "Disconnected"
}
eMethodUnimplemented :: Exception
eMethodUnimplemented =
eUnimplemented "Method unimplemented"
eUnimplemented :: Text -> Exception
eUnimplemented reason = def
{ type_ = Exception'Type'unimplemented
, reason = reason
}
instance E.Exception Exception
wrapException :: Bool -> E.SomeException -> Exception
wrapException debugMode e = fromMaybe
def { type_ = Exception'Type'failed
, reason =
if debugMode then
"Unhandled exception: " <> fromString (show e)
else
"Unhandled exception"
}
(E.fromException e)
throwFailed :: E.MonadThrow m => Text -> m a
throwFailed = E.throwM . eFailed