module Patrol.Type.RuntimeContext where

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

-- | <https://develop.sentry.dev/sdk/event-payloads/types/#runtimecontext>
data RuntimeContext = RuntimeContext
  { RuntimeContext -> Text
build :: Text.Text,
    RuntimeContext -> Text
name :: Text.Text,
    RuntimeContext -> Text
rawDescription :: Text.Text,
    RuntimeContext -> Text
version :: Text.Text
  }
  deriving (RuntimeContext -> RuntimeContext -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RuntimeContext -> RuntimeContext -> Bool
$c/= :: RuntimeContext -> RuntimeContext -> Bool
== :: RuntimeContext -> RuntimeContext -> Bool
$c== :: RuntimeContext -> RuntimeContext -> Bool
Eq, Int -> RuntimeContext -> ShowS
[RuntimeContext] -> ShowS
RuntimeContext -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RuntimeContext] -> ShowS
$cshowList :: [RuntimeContext] -> ShowS
show :: RuntimeContext -> String
$cshow :: RuntimeContext -> String
showsPrec :: Int -> RuntimeContext -> ShowS
$cshowsPrec :: Int -> RuntimeContext -> ShowS
Show)

instance Aeson.ToJSON RuntimeContext where
  toJSON :: RuntimeContext -> Value
toJSON RuntimeContext
runtimeContext =
    [Pair] -> Value
Aeson.intoObject
      [ forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"build" forall a b. (a -> b) -> a -> b
$ RuntimeContext -> Text
build RuntimeContext
runtimeContext,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"name" forall a b. (a -> b) -> a -> b
$ RuntimeContext -> Text
name RuntimeContext
runtimeContext,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"raw_description" forall a b. (a -> b) -> a -> b
$ RuntimeContext -> Text
rawDescription RuntimeContext
runtimeContext,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"version" forall a b. (a -> b) -> a -> b
$ RuntimeContext -> Text
version RuntimeContext
runtimeContext
      ]

empty :: RuntimeContext
empty :: RuntimeContext
empty =
  RuntimeContext
    { build :: Text
build = Text
Text.empty,
      name :: Text
name = Text
Text.empty,
      rawDescription :: Text
rawDescription = Text
Text.empty,
      version :: Text
version = Text
Text.empty
    }