module Patrol.Type.ProguardDebugImage 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/#proguarddebugimage>
newtype ProguardDebugImage = ProguardDebugImage
  { ProguardDebugImage -> Text
uuid :: Text.Text
  }
  deriving (ProguardDebugImage -> ProguardDebugImage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProguardDebugImage -> ProguardDebugImage -> Bool
$c/= :: ProguardDebugImage -> ProguardDebugImage -> Bool
== :: ProguardDebugImage -> ProguardDebugImage -> Bool
$c== :: ProguardDebugImage -> ProguardDebugImage -> Bool
Eq, Int -> ProguardDebugImage -> ShowS
[ProguardDebugImage] -> ShowS
ProguardDebugImage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProguardDebugImage] -> ShowS
$cshowList :: [ProguardDebugImage] -> ShowS
show :: ProguardDebugImage -> String
$cshow :: ProguardDebugImage -> String
showsPrec :: Int -> ProguardDebugImage -> ShowS
$cshowsPrec :: Int -> ProguardDebugImage -> ShowS
Show)

instance Aeson.ToJSON ProguardDebugImage where
  toJSON :: ProguardDebugImage -> Value
toJSON ProguardDebugImage
proguardDebugImage =
    [Pair] -> Value
Aeson.intoObject
      [ forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"uuid" forall a b. (a -> b) -> a -> b
$ ProguardDebugImage -> Text
uuid ProguardDebugImage
proguardDebugImage
      ]

empty :: ProguardDebugImage
empty :: ProguardDebugImage
empty =
  ProguardDebugImage
    { uuid :: Text
uuid = Text
Text.empty
    }