module Patrol.Type.TransactionInfo where

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

-- | <https://develop.sentry.dev/sdk/event-payloads/types/#transactioninfo>
data TransactionInfo = TransactionInfo
  { TransactionInfo -> Text
original :: Text.Text,
    TransactionInfo -> Maybe TransactionSource
source :: Maybe TransactionSource.TransactionSource
  }
  deriving (TransactionInfo -> TransactionInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransactionInfo -> TransactionInfo -> Bool
$c/= :: TransactionInfo -> TransactionInfo -> Bool
== :: TransactionInfo -> TransactionInfo -> Bool
$c== :: TransactionInfo -> TransactionInfo -> Bool
Eq, Int -> TransactionInfo -> ShowS
[TransactionInfo] -> ShowS
TransactionInfo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransactionInfo] -> ShowS
$cshowList :: [TransactionInfo] -> ShowS
show :: TransactionInfo -> String
$cshow :: TransactionInfo -> String
showsPrec :: Int -> TransactionInfo -> ShowS
$cshowsPrec :: Int -> TransactionInfo -> ShowS
Show)

instance Aeson.ToJSON TransactionInfo where
  toJSON :: TransactionInfo -> Value
toJSON TransactionInfo
transactionInfo =
    [Pair] -> Value
Aeson.intoObject
      [ forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"original" forall a b. (a -> b) -> a -> b
$ TransactionInfo -> Text
original TransactionInfo
transactionInfo,
        forall a. ToJSON a => String -> a -> Pair
Aeson.pair String
"source" forall a b. (a -> b) -> a -> b
$ TransactionInfo -> Maybe TransactionSource
source TransactionInfo
transactionInfo
      ]

empty :: TransactionInfo
empty :: TransactionInfo
empty =
  TransactionInfo
    { original :: Text
original = Text
Text.empty,
      source :: Maybe TransactionSource
source = forall a. Maybe a
Nothing
    }