{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE UnicodeSyntax #-}

{- |
Description : Projections into the Haskell exception hierarchy
Copyright   : Copyright 2022 Shea Levy.
License     : Apache-2.0
Maintainer  : shea@shealevy.com

Provides 'Exceptable' for error types which can be projected into
the Haskell exception hierarchy.
-}
module Data.Exceptable where

import Control.Exception
import Data.Typeable
import Data.Void

-- | Types which can be projected into the Haskell exception hierarchy
class Exceptable e where
  toSomeException  e  SomeException

instance Exceptable SomeException where
  toSomeException :: SomeException -> SomeException
toSomeException = SomeException -> SomeException
forall a. a -> a
id

instance Exceptable Void where
  toSomeException :: Void -> SomeException
toSomeException = Void -> SomeException
forall a. Void -> a
absurd

-- | An 'Exception' representing a failure in the 'Either' monad.
newtype EitherException e = EitherException e deriving stock (Int -> EitherException e -> ShowS
[EitherException e] -> ShowS
EitherException e -> String
(Int -> EitherException e -> ShowS)
-> (EitherException e -> String)
-> ([EitherException e] -> ShowS)
-> Show (EitherException e)
forall e. Show e => Int -> EitherException e -> ShowS
forall e. Show e => [EitherException e] -> ShowS
forall e. Show e => EitherException e -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall e. Show e => Int -> EitherException e -> ShowS
showsPrec :: Int -> EitherException e -> ShowS
$cshow :: forall e. Show e => EitherException e -> String
show :: EitherException e -> String
$cshowList :: forall e. Show e => [EitherException e] -> ShowS
showList :: [EitherException e] -> ShowS
Show)

instance (Show e, Typeable e)  Exception (EitherException e)

instance (Show e, Typeable e)  Exceptable (EitherException e) where
  toSomeException :: EitherException e -> SomeException
toSomeException = EitherException e -> SomeException
forall e. Exception e => e -> SomeException
toException

-- | An 'Exception' representing the 'Nothing' case in a 'Maybe' monad.
data NothingException = NothingException deriving (Int -> NothingException -> ShowS
[NothingException] -> ShowS
NothingException -> String
(Int -> NothingException -> ShowS)
-> (NothingException -> String)
-> ([NothingException] -> ShowS)
-> Show NothingException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NothingException -> ShowS
showsPrec :: Int -> NothingException -> ShowS
$cshow :: NothingException -> String
show :: NothingException -> String
$cshowList :: [NothingException] -> ShowS
showList :: [NothingException] -> ShowS
Show)

instance Exception NothingException

instance Exceptable e  Exceptable (Maybe e) where
  toSomeException :: Maybe e -> SomeException
toSomeException (Just e
e) = e -> SomeException
forall e. Exceptable e => e -> SomeException
toSomeException e
e
  toSomeException Maybe e
Nothing = NothingException -> SomeException
forall e. Exception e => e -> SomeException
toException NothingException
NothingException

instance (Show e, Typeable e, Exceptable e')  Exceptable (Either e e') where
  toSomeException :: Either e e' -> SomeException
toSomeException (Left e
e) = EitherException e -> SomeException
forall e. Exception e => e -> SomeException
toException (EitherException e -> SomeException)
-> EitherException e -> SomeException
forall a b. (a -> b) -> a -> b
$ e -> EitherException e
forall e. e -> EitherException e
EitherException e
e
  toSomeException (Right e'
e) = e' -> SomeException
forall e. Exceptable e => e -> SomeException
toSomeException e'
e

instance Exceptable e  Exceptable (e, s) where
  toSomeException :: (e, s) -> SomeException
toSomeException (e
e, s
_) = e -> SomeException
forall e. Exceptable e => e -> SomeException
toSomeException e
e

instance Exceptable e  Exceptable (e, s, w) where
  toSomeException :: (e, s, w) -> SomeException
toSomeException (e
e, s
_, w
_) = e -> SomeException
forall e. Exceptable e => e -> SomeException
toSomeException e
e