{-# LANGUAGE ScopedTypeVariables #-}
module Functora.Witch.TryFromException where
import qualified Control.Exception as Exception
import qualified Data.Proxy as Proxy
import qualified Data.Typeable as Typeable
data TryFromException source target
= TryFromException
source
(Maybe Exception.SomeException)
instance
( Show source,
Typeable.Typeable source,
Typeable.Typeable target
) =>
Show (TryFromException source target)
where
showsPrec :: Int -> TryFromException source target -> ShowS
showsPrec Int
d (TryFromException source
x Maybe SomeException
e) =
Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
String -> ShowS
showString String
"TryFromException @"
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> TypeRep -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 (Proxy source -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Typeable.typeRep (Proxy source
forall {k} (t :: k). Proxy t
Proxy.Proxy :: Proxy.Proxy source))
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
" @"
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> TypeRep -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 (Proxy target -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
Typeable.typeRep (Proxy target
forall {k} (t :: k). Proxy t
Proxy.Proxy :: Proxy.Proxy target))
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' '
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> source -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 source
x
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' '
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Maybe SomeException -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Maybe SomeException
e
instance
( Show source,
Typeable.Typeable source,
Typeable.Typeable target
) =>
Exception.Exception (TryFromException source target)