module Patrol.Type.Exception where
import qualified Control.Monad.Catch as Catch
import qualified Data.Aeson as Aeson
import qualified Data.Text as Text
import qualified Data.Typeable as Typeable
import qualified Patrol.Extra.Aeson as Aeson
import qualified Patrol.Type.Mechanism as Mechanism
import qualified Patrol.Type.Stacktrace as Stacktrace
data Exception = Exception
  { Exception -> Maybe Mechanism
mechanism :: Maybe Mechanism.Mechanism,
    Exception -> Text
module_ :: Text.Text,
    Exception -> Maybe Stacktrace
stacktrace :: Maybe Stacktrace.Stacktrace,
    Exception -> Text
threadId :: Text.Text,
    Exception -> Text
type_ :: Text.Text,
    Exception -> Text
value :: Text.Text
  }
  deriving (Exception -> Exception -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Exception -> Exception -> Bool
$c/= :: Exception -> Exception -> Bool
== :: Exception -> Exception -> Bool
$c== :: Exception -> Exception -> Bool
Eq, Int -> Exception -> ShowS
[Exception] -> ShowS
Exception -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Exception] -> ShowS
$cshowList :: [Exception] -> ShowS
show :: Exception -> String
$cshow :: Exception -> String
showsPrec :: Int -> Exception -> ShowS
$cshowsPrec :: Int -> Exception -> ShowS
Show)
instance Aeson.ToJSON Exception where
  toJSON :: Exception -> Value
toJSON Exception
exception =
    [Pair] -> Value
Aeson.intoObject
      [ forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"mechanism" forall a b. (a -> b) -> a -> b
$ Exception -> Maybe Mechanism
mechanism Exception
exception,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"module" forall a b. (a -> b) -> a -> b
$ Exception -> Text
module_ Exception
exception,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"stacktrace" forall a b. (a -> b) -> a -> b
$ Exception -> Maybe Stacktrace
stacktrace Exception
exception,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"thread_id" forall a b. (a -> b) -> a -> b
$ Exception -> Text
threadId Exception
exception,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"type" forall a b. (a -> b) -> a -> b
$ Exception -> Text
type_ Exception
exception,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"value" forall a b. (a -> b) -> a -> b
$ Exception -> Text
value Exception
exception
      ]
empty :: Exception
empty :: Exception
empty =
  Exception
    { mechanism :: Maybe Mechanism
mechanism = forall a. Maybe a
Nothing,
      module_ :: Text
module_ = Text
Text.empty,
      stacktrace :: Maybe Stacktrace
stacktrace = forall a. Maybe a
Nothing,
      threadId :: Text
threadId = Text
Text.empty,
      type_ :: Text
type_ = Text
Text.empty,
      value :: Text
value = Text
Text.empty
    }
fromSomeException :: Catch.SomeException -> Exception
fromSomeException :: SomeException -> Exception
fromSomeException (Catch.SomeException e
e) =
  Exception
empty
    { type_ :: Text
type_ = String -> Text
Text.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ forall a. Typeable a => a -> TypeRep
Typeable.typeOf e
e,
      value :: Text
value = String -> Text
Text.pack forall a b. (a -> b) -> a -> b
$ forall e. Exception e => e -> String
Catch.displayException e
e
    }