module Patrol.Type.Exceptions where

import qualified Data.Aeson as Aeson
import qualified Patrol.Extra.Aeson as Aeson
import qualified Patrol.Type.Exception as Exception

-- | <https://develop.sentry.dev/sdk/event-payloads/types/#exception>
newtype Exceptions = Exceptions
  { Exceptions -> [Exception]
values :: [Exception.Exception]
  }
  deriving (Exceptions -> Exceptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Exceptions -> Exceptions -> Bool
$c/= :: Exceptions -> Exceptions -> Bool
== :: Exceptions -> Exceptions -> Bool
$c== :: Exceptions -> Exceptions -> Bool
Eq, Int -> Exceptions -> ShowS
[Exceptions] -> ShowS
Exceptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Exceptions] -> ShowS
$cshowList :: [Exceptions] -> ShowS
show :: Exceptions -> String
$cshow :: Exceptions -> String
showsPrec :: Int -> Exceptions -> ShowS
$cshowsPrec :: Int -> Exceptions -> ShowS
Show)

instance Aeson.ToJSON Exceptions where
  toJSON :: Exceptions -> Value
toJSON Exceptions
exceptions =
    [Pair] -> Value
Aeson.intoObject
      [ forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"values" forall a b. (a -> b) -> a -> b
$ Exceptions -> [Exception]
values Exceptions
exceptions
      ]

empty :: Exceptions
empty :: Exceptions
empty =
  Exceptions
    { values :: [Exception]
values = []
    }