module Patrol.Type.OsContext 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/#oscontext>
data OsContext = OsContext
  { OsContext -> Text
build :: Text.Text,
    OsContext -> Text
kernelVersion :: Text.Text,
    OsContext -> Text
name :: Text.Text,
    OsContext -> Text
rawDescription :: Text.Text,
    OsContext -> Maybe Bool
rooted :: Maybe Bool,
    OsContext -> Text
version :: Text.Text
  }
  deriving (OsContext -> OsContext -> Bool
(OsContext -> OsContext -> Bool)
-> (OsContext -> OsContext -> Bool) -> Eq OsContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OsContext -> OsContext -> Bool
== :: OsContext -> OsContext -> Bool
$c/= :: OsContext -> OsContext -> Bool
/= :: OsContext -> OsContext -> Bool
Eq, Int -> OsContext -> ShowS
[OsContext] -> ShowS
OsContext -> String
(Int -> OsContext -> ShowS)
-> (OsContext -> String)
-> ([OsContext] -> ShowS)
-> Show OsContext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OsContext -> ShowS
showsPrec :: Int -> OsContext -> ShowS
$cshow :: OsContext -> String
show :: OsContext -> String
$cshowList :: [OsContext] -> ShowS
showList :: [OsContext] -> ShowS
Show)

instance Aeson.ToJSON OsContext where
  toJSON :: OsContext -> Value
toJSON OsContext
osContext =
    [Pair] -> Value
Aeson.intoObject
      [ String -> Text -> Pair
forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"build" (Text -> Pair) -> Text -> Pair
forall a b. (a -> b) -> a -> b
$ OsContext -> Text
build OsContext
osContext,
        String -> Text -> Pair
forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"kernel_version" (Text -> Pair) -> Text -> Pair
forall a b. (a -> b) -> a -> b
$ OsContext -> Text
kernelVersion OsContext
osContext,
        String -> Text -> Pair
forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"name" (Text -> Pair) -> Text -> Pair
forall a b. (a -> b) -> a -> b
$ OsContext -> Text
name OsContext
osContext,
        String -> Text -> Pair
forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"raw_description" (Text -> Pair) -> Text -> Pair
forall a b. (a -> b) -> a -> b
$ OsContext -> Text
rawDescription OsContext
osContext,
        String -> Maybe Bool -> Pair
forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"rooted" (Maybe Bool -> Pair) -> Maybe Bool -> Pair
forall a b. (a -> b) -> a -> b
$ OsContext -> Maybe Bool
rooted OsContext
osContext,
        String -> Text -> Pair
forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"version" (Text -> Pair) -> Text -> Pair
forall a b. (a -> b) -> a -> b
$ OsContext -> Text
version OsContext
osContext
      ]

empty :: OsContext
empty :: OsContext
empty =
  OsContext
    { build :: Text
build = Text
Text.empty,
      kernelVersion :: Text
kernelVersion = Text
Text.empty,
      name :: Text
name = Text
Text.empty,
      rawDescription :: Text
rawDescription = Text
Text.empty,
      rooted :: Maybe Bool
rooted = Maybe Bool
forall a. Maybe a
Nothing,
      version :: Text
version = Text
Text.empty
    }