module Patrol.Type.AppContext where

import qualified Data.Aeson as Aeson
import qualified Data.Text as Text
import qualified Data.Time as Time
import qualified Patrol.Extra.Aeson as Aeson

-- | <https://develop.sentry.dev/sdk/event-payloads/types/#appcontext>
data AppContext = AppContext
  { AppContext -> Text
appBuild :: Text.Text,
    AppContext -> Text
appIdentifier :: Text.Text,
    AppContext -> Maybe Int
appMemory :: Maybe Int,
    AppContext -> Text
appName :: Text.Text,
    AppContext -> Maybe UTCTime
appStartTime :: Maybe Time.UTCTime,
    AppContext -> Text
appVersion :: Text.Text,
    AppContext -> Text
buildType :: Text.Text,
    AppContext -> Text
deviceAppHash :: Text.Text
  }
  deriving (AppContext -> AppContext -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AppContext -> AppContext -> Bool
$c/= :: AppContext -> AppContext -> Bool
== :: AppContext -> AppContext -> Bool
$c== :: AppContext -> AppContext -> Bool
Eq, Int -> AppContext -> ShowS
[AppContext] -> ShowS
AppContext -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AppContext] -> ShowS
$cshowList :: [AppContext] -> ShowS
show :: AppContext -> String
$cshow :: AppContext -> String
showsPrec :: Int -> AppContext -> ShowS
$cshowsPrec :: Int -> AppContext -> ShowS
Show)

instance Aeson.ToJSON AppContext where
  toJSON :: AppContext -> Value
toJSON AppContext
appContext =
    [Pair] -> Value
Aeson.intoObject
      [ forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"app_build" forall a b. (a -> b) -> a -> b
$ AppContext -> Text
appBuild AppContext
appContext,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"app_identifier" forall a b. (a -> b) -> a -> b
$ AppContext -> Text
appIdentifier AppContext
appContext,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"app_memory" forall a b. (a -> b) -> a -> b
$ AppContext -> Maybe Int
appMemory AppContext
appContext,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"app_name" forall a b. (a -> b) -> a -> b
$ AppContext -> Text
appName AppContext
appContext,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"app_start_time" forall a b. (a -> b) -> a -> b
$ AppContext -> Maybe UTCTime
appStartTime AppContext
appContext,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"app_version" forall a b. (a -> b) -> a -> b
$ AppContext -> Text
appVersion AppContext
appContext,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"build_type" forall a b. (a -> b) -> a -> b
$ AppContext -> Text
buildType AppContext
appContext,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"device_app_hash" forall a b. (a -> b) -> a -> b
$ AppContext -> Text
deviceAppHash AppContext
appContext
      ]

empty :: AppContext
empty :: AppContext
empty =
  AppContext
    { appBuild :: Text
appBuild = Text
Text.empty,
      appIdentifier :: Text
appIdentifier = Text
Text.empty,
      appMemory :: Maybe Int
appMemory = forall a. Maybe a
Nothing,
      appName :: Text
appName = Text
Text.empty,
      appStartTime :: Maybe UTCTime
appStartTime = forall a. Maybe a
Nothing,
      appVersion :: Text
appVersion = Text
Text.empty,
      buildType :: Text
buildType = Text
Text.empty,
      deviceAppHash :: Text
deviceAppHash = Text
Text.empty
    }