module Patrol.Type.NativeDebugImage 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/#nativedebugimage>
data NativeDebugImage = NativeDebugImage
  { NativeDebugImage -> Text
arch :: Text.Text,
    NativeDebugImage -> Text
codeFile :: Text.Text,
    NativeDebugImage -> Text
codeId :: Text.Text,
    NativeDebugImage -> Text
debugFile :: Text.Text,
    NativeDebugImage -> Text
debugId :: Text.Text,
    NativeDebugImage -> Text
imageAddr :: Text.Text,
    NativeDebugImage -> Maybe Int
imageSize :: Maybe Int,
    NativeDebugImage -> Text
imageVmaddr :: Text.Text,
    NativeDebugImage -> Text
type_ :: Text.Text
  }
  deriving (NativeDebugImage -> NativeDebugImage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NativeDebugImage -> NativeDebugImage -> Bool
$c/= :: NativeDebugImage -> NativeDebugImage -> Bool
== :: NativeDebugImage -> NativeDebugImage -> Bool
$c== :: NativeDebugImage -> NativeDebugImage -> Bool
Eq, Int -> NativeDebugImage -> ShowS
[NativeDebugImage] -> ShowS
NativeDebugImage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NativeDebugImage] -> ShowS
$cshowList :: [NativeDebugImage] -> ShowS
show :: NativeDebugImage -> String
$cshow :: NativeDebugImage -> String
showsPrec :: Int -> NativeDebugImage -> ShowS
$cshowsPrec :: Int -> NativeDebugImage -> ShowS
Show)

instance Aeson.ToJSON NativeDebugImage where
  toJSON :: NativeDebugImage -> Value
toJSON NativeDebugImage
nativeDebugImage =
    [Pair] -> Value
Aeson.intoObject
      [ forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"arch" forall a b. (a -> b) -> a -> b
$ NativeDebugImage -> Text
arch NativeDebugImage
nativeDebugImage,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"code_file" forall a b. (a -> b) -> a -> b
$ NativeDebugImage -> Text
codeFile NativeDebugImage
nativeDebugImage,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"code_id" forall a b. (a -> b) -> a -> b
$ NativeDebugImage -> Text
codeId NativeDebugImage
nativeDebugImage,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"debug_file" forall a b. (a -> b) -> a -> b
$ NativeDebugImage -> Text
debugFile NativeDebugImage
nativeDebugImage,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"debug_id" forall a b. (a -> b) -> a -> b
$ NativeDebugImage -> Text
debugId NativeDebugImage
nativeDebugImage,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"image_addr" forall a b. (a -> b) -> a -> b
$ NativeDebugImage -> Text
imageAddr NativeDebugImage
nativeDebugImage,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"image_size" forall a b. (a -> b) -> a -> b
$ NativeDebugImage -> Maybe Int
imageSize NativeDebugImage
nativeDebugImage,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"image_vmaddr" forall a b. (a -> b) -> a -> b
$ NativeDebugImage -> Text
imageVmaddr NativeDebugImage
nativeDebugImage,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"type" forall a b. (a -> b) -> a -> b
$ NativeDebugImage -> Text
type_ NativeDebugImage
nativeDebugImage
      ]

empty :: NativeDebugImage
empty :: NativeDebugImage
empty =
  NativeDebugImage
    { arch :: Text
arch = Text
Text.empty,
      codeFile :: Text
codeFile = Text
Text.empty,
      codeId :: Text
codeId = Text
Text.empty,
      debugFile :: Text
debugFile = Text
Text.empty,
      debugId :: Text
debugId = Text
Text.empty,
      imageAddr :: Text
imageAddr = Text
Text.empty,
      imageSize :: Maybe Int
imageSize = forall a. Maybe a
Nothing,
      imageVmaddr :: Text
imageVmaddr = Text
Text.empty,
      type_ :: Text
type_ = Text
Text.empty
    }