-- | Working with Bugsnag's 'event_metaData' field
module Network.Bugsnag.MetaData
  ( MetaData (..)
  , metaData
  ) where

import Prelude

import Data.Aeson.Compat (Object, Value (Object), object, (.=))
import qualified Data.Aeson.Compat as Aeson

newtype MetaData = MetaData
  { MetaData -> Object
unMetaData :: Object
  }
  deriving stock (MetaData -> MetaData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MetaData -> MetaData -> Bool
$c/= :: MetaData -> MetaData -> Bool
== :: MetaData -> MetaData -> Bool
$c== :: MetaData -> MetaData -> Bool
Eq, Int -> MetaData -> ShowS
[MetaData] -> ShowS
MetaData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MetaData] -> ShowS
$cshowList :: [MetaData] -> ShowS
show :: MetaData -> String
$cshow :: MetaData -> String
showsPrec :: Int -> MetaData -> ShowS
$cshowsPrec :: Int -> MetaData -> ShowS
Show)

instance Semigroup MetaData where
  -- \| /Right/-biased, recursive union
  --
  -- The chosen bias ensures that adding metadata in smaller scopes (later)
  -- overrides values from larger scopes.
  MetaData Object
x <> :: MetaData -> MetaData -> MetaData
<> MetaData Object
y = Object -> MetaData
MetaData forall a b. (a -> b) -> a -> b
$ Object -> Object -> Object
unionObjects Object
y Object
x
   where
    unionObjects :: Object -> Object -> Object
    unionObjects :: Object -> Object -> Object
unionObjects = forall v. (v -> v -> v) -> KeyMap v -> KeyMap v -> KeyMap v
Aeson.unionWith Value -> Value -> Value
unionValues

    unionValues :: Value -> Value -> Value
unionValues (Object Object
a) (Object Object
b) = Object -> Value
Object forall a b. (a -> b) -> a -> b
$ Object -> Object -> Object
unionObjects Object
a Object
b
    unionValues Value
a Value
_ = Value
a

instance Monoid MetaData where
  mempty :: MetaData
mempty = Object -> MetaData
MetaData forall a. Monoid a => a
mempty

-- | Construct 'MetaData' from 'Pair's
metaData
  :: Aeson.Key
  -- ^ The Tab within which the values will display
  -> [Aeson.Pair]
  -- ^ The Key-Values themselves
  -> MetaData
metaData :: Key -> [(Key, Value)] -> MetaData
metaData Key
key = Object -> MetaData
MetaData forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v. [(Key, v)] -> KeyMap v
Aeson.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key
key forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.=) forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Key, Value)] -> Value
object

-- $details
--
-- From <https://bugsnagerrorreportingapi.docs.apiary.io/#reference/0/notify/send-error-reports>
--
-- @events[].metaData@
--
-- > An object containing any further data you wish to attach to this error
-- > event. This should contain one or more objects, with each object being
-- > displayed in its own tab on the event details on Bugsnag.
-- >
-- > {
-- >     // Custom user data to be displayed in the User tab along with standard
-- >     // user fields on the Bugsnag website.
-- >     "user": {
-- >        ...
-- >     },
-- >
-- >     // Custom app data to be displayed in the App tab along with standard
-- >     // app fields on the Bugsnag website.
-- >     "app": {
-- >        ...
-- >     },
-- >
-- >     // Custom device data to be displayed in the Device tab along with
-- >     //standard device fields on the Bugsnag website.
-- >     "device": {
-- >        ...
-- >     },
-- >
-- >     Custom request data to be displayed in the Request tab along with
-- >     standard request fields on the Bugsnag website.
-- >     "request": {
-- >        ...
-- >     },
-- >
-- >     // This will be displayed as an extra tab on the Bugsnag website.
-- >     "Some data": {
-- >
-- >         // A key value pair that will be displayed in the first tab.
-- >         "key": "value",
-- >
-- >         // Key value pairs can be contained in nested objects which helps
-- >         // to organise the information presented in the tab.
-- >         "setOfKeys": {
-- >             "key": "value",
-- >             "key2": "value"
-- >         }
-- >     },
-- >
-- >     // This would be the second extra tab on the Bugsnag website.
-- >     "Some more data": {
-- >         ...
-- >     }
-- > }