{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Serokell.Util.Exceptions
( TextException (..)
, throwText
, EmptyException (..)
, throwEmpty
, eitherToFail
) where
import Control.Exception (Exception, SomeException,
fromException)
import Control.Monad.Catch (MonadThrow, throwM)
import Data.Text (Text)
import Data.Text.Buildable (Buildable (build))
import qualified Data.Text.Format as F
import Data.Text.Lazy.Builder (Builder)
import Data.Typeable (Typeable)
instance Buildable SomeException where
build e =
maybe (build $ F.Shown e) (build :: TextException -> Builder) $
fromException e
newtype TextException = TextException
{ teMessage :: Text
} deriving (Show,Typeable)
instance Exception TextException
instance Buildable TextException where
build = F.build "TextException: {}" . F.Only . teMessage
throwText :: MonadThrow m
=> Text -> m a
throwText = throwM . TextException
data EmptyException = EmptyException
deriving (Show, Typeable)
instance Exception EmptyException
throwEmpty :: MonadThrow m => m a
throwEmpty = throwM EmptyException
eitherToFail :: (Monad m, e ~ SomeException) => Either e a -> m a
eitherToFail = either (fail . show) return