{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.ServiceCatalog.Types.RecordDetail
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.ServiceCatalog.Types.RecordDetail where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import Amazonka.ServiceCatalog.Types.RecordError
import Amazonka.ServiceCatalog.Types.RecordStatus
import Amazonka.ServiceCatalog.Types.RecordTag

-- | Information about a request operation.
--
-- /See:/ 'newRecordDetail' smart constructor.
data RecordDetail = RecordDetail'
  { -- | The UTC time stamp of the creation time.
    RecordDetail -> Maybe POSIX
createdTime :: Prelude.Maybe Data.POSIX,
    -- | The ARN of the launch role associated with the provisioned product.
    RecordDetail -> Maybe Text
launchRoleArn :: Prelude.Maybe Prelude.Text,
    -- | The path identifier.
    RecordDetail -> Maybe Text
pathId :: Prelude.Maybe Prelude.Text,
    -- | The product identifier.
    RecordDetail -> Maybe Text
productId :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the provisioned product.
    RecordDetail -> Maybe Text
provisionedProductId :: Prelude.Maybe Prelude.Text,
    -- | The user-friendly name of the provisioned product.
    RecordDetail -> Maybe Text
provisionedProductName :: Prelude.Maybe Prelude.Text,
    -- | The type of provisioned product. The supported values are @CFN_STACK@
    -- and @CFN_STACKSET@.
    RecordDetail -> Maybe Text
provisionedProductType :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the provisioning artifact.
    RecordDetail -> Maybe Text
provisioningArtifactId :: Prelude.Maybe Prelude.Text,
    -- | The errors that occurred.
    RecordDetail -> Maybe [RecordError]
recordErrors :: Prelude.Maybe [RecordError],
    -- | The identifier of the record.
    RecordDetail -> Maybe Text
recordId :: Prelude.Maybe Prelude.Text,
    -- | One or more tags.
    RecordDetail -> Maybe [RecordTag]
recordTags :: Prelude.Maybe [RecordTag],
    -- | The record type.
    --
    -- -   @PROVISION_PRODUCT@
    --
    -- -   @UPDATE_PROVISIONED_PRODUCT@
    --
    -- -   @TERMINATE_PROVISIONED_PRODUCT@
    RecordDetail -> Maybe Text
recordType :: Prelude.Maybe Prelude.Text,
    -- | The status of the provisioned product.
    --
    -- -   @CREATED@ - The request was created but the operation has not
    --     started.
    --
    -- -   @IN_PROGRESS@ - The requested operation is in progress.
    --
    -- -   @IN_PROGRESS_IN_ERROR@ - The provisioned product is under change but
    --     the requested operation failed and some remediation is occurring.
    --     For example, a rollback.
    --
    -- -   @SUCCEEDED@ - The requested operation has successfully completed.
    --
    -- -   @FAILED@ - The requested operation has unsuccessfully completed.
    --     Investigate using the error messages returned.
    RecordDetail -> Maybe RecordStatus
status :: Prelude.Maybe RecordStatus,
    -- | The time when the record was last updated.
    RecordDetail -> Maybe POSIX
updatedTime :: Prelude.Maybe Data.POSIX
  }
  deriving (RecordDetail -> RecordDetail -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecordDetail -> RecordDetail -> Bool
$c/= :: RecordDetail -> RecordDetail -> Bool
== :: RecordDetail -> RecordDetail -> Bool
$c== :: RecordDetail -> RecordDetail -> Bool
Prelude.Eq, ReadPrec [RecordDetail]
ReadPrec RecordDetail
Int -> ReadS RecordDetail
ReadS [RecordDetail]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RecordDetail]
$creadListPrec :: ReadPrec [RecordDetail]
readPrec :: ReadPrec RecordDetail
$creadPrec :: ReadPrec RecordDetail
readList :: ReadS [RecordDetail]
$creadList :: ReadS [RecordDetail]
readsPrec :: Int -> ReadS RecordDetail
$creadsPrec :: Int -> ReadS RecordDetail
Prelude.Read, Int -> RecordDetail -> ShowS
[RecordDetail] -> ShowS
RecordDetail -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RecordDetail] -> ShowS
$cshowList :: [RecordDetail] -> ShowS
show :: RecordDetail -> String
$cshow :: RecordDetail -> String
showsPrec :: Int -> RecordDetail -> ShowS
$cshowsPrec :: Int -> RecordDetail -> ShowS
Prelude.Show, forall x. Rep RecordDetail x -> RecordDetail
forall x. RecordDetail -> Rep RecordDetail x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RecordDetail x -> RecordDetail
$cfrom :: forall x. RecordDetail -> Rep RecordDetail x
Prelude.Generic)

-- |
-- Create a value of 'RecordDetail' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'createdTime', 'recordDetail_createdTime' - The UTC time stamp of the creation time.
--
-- 'launchRoleArn', 'recordDetail_launchRoleArn' - The ARN of the launch role associated with the provisioned product.
--
-- 'pathId', 'recordDetail_pathId' - The path identifier.
--
-- 'productId', 'recordDetail_productId' - The product identifier.
--
-- 'provisionedProductId', 'recordDetail_provisionedProductId' - The identifier of the provisioned product.
--
-- 'provisionedProductName', 'recordDetail_provisionedProductName' - The user-friendly name of the provisioned product.
--
-- 'provisionedProductType', 'recordDetail_provisionedProductType' - The type of provisioned product. The supported values are @CFN_STACK@
-- and @CFN_STACKSET@.
--
-- 'provisioningArtifactId', 'recordDetail_provisioningArtifactId' - The identifier of the provisioning artifact.
--
-- 'recordErrors', 'recordDetail_recordErrors' - The errors that occurred.
--
-- 'recordId', 'recordDetail_recordId' - The identifier of the record.
--
-- 'recordTags', 'recordDetail_recordTags' - One or more tags.
--
-- 'recordType', 'recordDetail_recordType' - The record type.
--
-- -   @PROVISION_PRODUCT@
--
-- -   @UPDATE_PROVISIONED_PRODUCT@
--
-- -   @TERMINATE_PROVISIONED_PRODUCT@
--
-- 'status', 'recordDetail_status' - The status of the provisioned product.
--
-- -   @CREATED@ - The request was created but the operation has not
--     started.
--
-- -   @IN_PROGRESS@ - The requested operation is in progress.
--
-- -   @IN_PROGRESS_IN_ERROR@ - The provisioned product is under change but
--     the requested operation failed and some remediation is occurring.
--     For example, a rollback.
--
-- -   @SUCCEEDED@ - The requested operation has successfully completed.
--
-- -   @FAILED@ - The requested operation has unsuccessfully completed.
--     Investigate using the error messages returned.
--
-- 'updatedTime', 'recordDetail_updatedTime' - The time when the record was last updated.
newRecordDetail ::
  RecordDetail
newRecordDetail :: RecordDetail
newRecordDetail =
  RecordDetail'
    { $sel:createdTime:RecordDetail' :: Maybe POSIX
createdTime = forall a. Maybe a
Prelude.Nothing,
      $sel:launchRoleArn:RecordDetail' :: Maybe Text
launchRoleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:pathId:RecordDetail' :: Maybe Text
pathId = forall a. Maybe a
Prelude.Nothing,
      $sel:productId:RecordDetail' :: Maybe Text
productId = forall a. Maybe a
Prelude.Nothing,
      $sel:provisionedProductId:RecordDetail' :: Maybe Text
provisionedProductId = forall a. Maybe a
Prelude.Nothing,
      $sel:provisionedProductName:RecordDetail' :: Maybe Text
provisionedProductName = forall a. Maybe a
Prelude.Nothing,
      $sel:provisionedProductType:RecordDetail' :: Maybe Text
provisionedProductType = forall a. Maybe a
Prelude.Nothing,
      $sel:provisioningArtifactId:RecordDetail' :: Maybe Text
provisioningArtifactId = forall a. Maybe a
Prelude.Nothing,
      $sel:recordErrors:RecordDetail' :: Maybe [RecordError]
recordErrors = forall a. Maybe a
Prelude.Nothing,
      $sel:recordId:RecordDetail' :: Maybe Text
recordId = forall a. Maybe a
Prelude.Nothing,
      $sel:recordTags:RecordDetail' :: Maybe [RecordTag]
recordTags = forall a. Maybe a
Prelude.Nothing,
      $sel:recordType:RecordDetail' :: Maybe Text
recordType = forall a. Maybe a
Prelude.Nothing,
      $sel:status:RecordDetail' :: Maybe RecordStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:updatedTime:RecordDetail' :: Maybe POSIX
updatedTime = forall a. Maybe a
Prelude.Nothing
    }

-- | The UTC time stamp of the creation time.
recordDetail_createdTime :: Lens.Lens' RecordDetail (Prelude.Maybe Prelude.UTCTime)
recordDetail_createdTime :: Lens' RecordDetail (Maybe UTCTime)
recordDetail_createdTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RecordDetail' {Maybe POSIX
createdTime :: Maybe POSIX
$sel:createdTime:RecordDetail' :: RecordDetail -> Maybe POSIX
createdTime} -> Maybe POSIX
createdTime) (\s :: RecordDetail
s@RecordDetail' {} Maybe POSIX
a -> RecordDetail
s {$sel:createdTime:RecordDetail' :: Maybe POSIX
createdTime = Maybe POSIX
a} :: RecordDetail) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The ARN of the launch role associated with the provisioned product.
recordDetail_launchRoleArn :: Lens.Lens' RecordDetail (Prelude.Maybe Prelude.Text)
recordDetail_launchRoleArn :: Lens' RecordDetail (Maybe Text)
recordDetail_launchRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RecordDetail' {Maybe Text
launchRoleArn :: Maybe Text
$sel:launchRoleArn:RecordDetail' :: RecordDetail -> Maybe Text
launchRoleArn} -> Maybe Text
launchRoleArn) (\s :: RecordDetail
s@RecordDetail' {} Maybe Text
a -> RecordDetail
s {$sel:launchRoleArn:RecordDetail' :: Maybe Text
launchRoleArn = Maybe Text
a} :: RecordDetail)

-- | The path identifier.
recordDetail_pathId :: Lens.Lens' RecordDetail (Prelude.Maybe Prelude.Text)
recordDetail_pathId :: Lens' RecordDetail (Maybe Text)
recordDetail_pathId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RecordDetail' {Maybe Text
pathId :: Maybe Text
$sel:pathId:RecordDetail' :: RecordDetail -> Maybe Text
pathId} -> Maybe Text
pathId) (\s :: RecordDetail
s@RecordDetail' {} Maybe Text
a -> RecordDetail
s {$sel:pathId:RecordDetail' :: Maybe Text
pathId = Maybe Text
a} :: RecordDetail)

-- | The product identifier.
recordDetail_productId :: Lens.Lens' RecordDetail (Prelude.Maybe Prelude.Text)
recordDetail_productId :: Lens' RecordDetail (Maybe Text)
recordDetail_productId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RecordDetail' {Maybe Text
productId :: Maybe Text
$sel:productId:RecordDetail' :: RecordDetail -> Maybe Text
productId} -> Maybe Text
productId) (\s :: RecordDetail
s@RecordDetail' {} Maybe Text
a -> RecordDetail
s {$sel:productId:RecordDetail' :: Maybe Text
productId = Maybe Text
a} :: RecordDetail)

-- | The identifier of the provisioned product.
recordDetail_provisionedProductId :: Lens.Lens' RecordDetail (Prelude.Maybe Prelude.Text)
recordDetail_provisionedProductId :: Lens' RecordDetail (Maybe Text)
recordDetail_provisionedProductId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RecordDetail' {Maybe Text
provisionedProductId :: Maybe Text
$sel:provisionedProductId:RecordDetail' :: RecordDetail -> Maybe Text
provisionedProductId} -> Maybe Text
provisionedProductId) (\s :: RecordDetail
s@RecordDetail' {} Maybe Text
a -> RecordDetail
s {$sel:provisionedProductId:RecordDetail' :: Maybe Text
provisionedProductId = Maybe Text
a} :: RecordDetail)

-- | The user-friendly name of the provisioned product.
recordDetail_provisionedProductName :: Lens.Lens' RecordDetail (Prelude.Maybe Prelude.Text)
recordDetail_provisionedProductName :: Lens' RecordDetail (Maybe Text)
recordDetail_provisionedProductName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RecordDetail' {Maybe Text
provisionedProductName :: Maybe Text
$sel:provisionedProductName:RecordDetail' :: RecordDetail -> Maybe Text
provisionedProductName} -> Maybe Text
provisionedProductName) (\s :: RecordDetail
s@RecordDetail' {} Maybe Text
a -> RecordDetail
s {$sel:provisionedProductName:RecordDetail' :: Maybe Text
provisionedProductName = Maybe Text
a} :: RecordDetail)

-- | The type of provisioned product. The supported values are @CFN_STACK@
-- and @CFN_STACKSET@.
recordDetail_provisionedProductType :: Lens.Lens' RecordDetail (Prelude.Maybe Prelude.Text)
recordDetail_provisionedProductType :: Lens' RecordDetail (Maybe Text)
recordDetail_provisionedProductType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RecordDetail' {Maybe Text
provisionedProductType :: Maybe Text
$sel:provisionedProductType:RecordDetail' :: RecordDetail -> Maybe Text
provisionedProductType} -> Maybe Text
provisionedProductType) (\s :: RecordDetail
s@RecordDetail' {} Maybe Text
a -> RecordDetail
s {$sel:provisionedProductType:RecordDetail' :: Maybe Text
provisionedProductType = Maybe Text
a} :: RecordDetail)

-- | The identifier of the provisioning artifact.
recordDetail_provisioningArtifactId :: Lens.Lens' RecordDetail (Prelude.Maybe Prelude.Text)
recordDetail_provisioningArtifactId :: Lens' RecordDetail (Maybe Text)
recordDetail_provisioningArtifactId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RecordDetail' {Maybe Text
provisioningArtifactId :: Maybe Text
$sel:provisioningArtifactId:RecordDetail' :: RecordDetail -> Maybe Text
provisioningArtifactId} -> Maybe Text
provisioningArtifactId) (\s :: RecordDetail
s@RecordDetail' {} Maybe Text
a -> RecordDetail
s {$sel:provisioningArtifactId:RecordDetail' :: Maybe Text
provisioningArtifactId = Maybe Text
a} :: RecordDetail)

-- | The errors that occurred.
recordDetail_recordErrors :: Lens.Lens' RecordDetail (Prelude.Maybe [RecordError])
recordDetail_recordErrors :: Lens' RecordDetail (Maybe [RecordError])
recordDetail_recordErrors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RecordDetail' {Maybe [RecordError]
recordErrors :: Maybe [RecordError]
$sel:recordErrors:RecordDetail' :: RecordDetail -> Maybe [RecordError]
recordErrors} -> Maybe [RecordError]
recordErrors) (\s :: RecordDetail
s@RecordDetail' {} Maybe [RecordError]
a -> RecordDetail
s {$sel:recordErrors:RecordDetail' :: Maybe [RecordError]
recordErrors = Maybe [RecordError]
a} :: RecordDetail) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The identifier of the record.
recordDetail_recordId :: Lens.Lens' RecordDetail (Prelude.Maybe Prelude.Text)
recordDetail_recordId :: Lens' RecordDetail (Maybe Text)
recordDetail_recordId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RecordDetail' {Maybe Text
recordId :: Maybe Text
$sel:recordId:RecordDetail' :: RecordDetail -> Maybe Text
recordId} -> Maybe Text
recordId) (\s :: RecordDetail
s@RecordDetail' {} Maybe Text
a -> RecordDetail
s {$sel:recordId:RecordDetail' :: Maybe Text
recordId = Maybe Text
a} :: RecordDetail)

-- | One or more tags.
recordDetail_recordTags :: Lens.Lens' RecordDetail (Prelude.Maybe [RecordTag])
recordDetail_recordTags :: Lens' RecordDetail (Maybe [RecordTag])
recordDetail_recordTags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RecordDetail' {Maybe [RecordTag]
recordTags :: Maybe [RecordTag]
$sel:recordTags:RecordDetail' :: RecordDetail -> Maybe [RecordTag]
recordTags} -> Maybe [RecordTag]
recordTags) (\s :: RecordDetail
s@RecordDetail' {} Maybe [RecordTag]
a -> RecordDetail
s {$sel:recordTags:RecordDetail' :: Maybe [RecordTag]
recordTags = Maybe [RecordTag]
a} :: RecordDetail) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The record type.
--
-- -   @PROVISION_PRODUCT@
--
-- -   @UPDATE_PROVISIONED_PRODUCT@
--
-- -   @TERMINATE_PROVISIONED_PRODUCT@
recordDetail_recordType :: Lens.Lens' RecordDetail (Prelude.Maybe Prelude.Text)
recordDetail_recordType :: Lens' RecordDetail (Maybe Text)
recordDetail_recordType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RecordDetail' {Maybe Text
recordType :: Maybe Text
$sel:recordType:RecordDetail' :: RecordDetail -> Maybe Text
recordType} -> Maybe Text
recordType) (\s :: RecordDetail
s@RecordDetail' {} Maybe Text
a -> RecordDetail
s {$sel:recordType:RecordDetail' :: Maybe Text
recordType = Maybe Text
a} :: RecordDetail)

-- | The status of the provisioned product.
--
-- -   @CREATED@ - The request was created but the operation has not
--     started.
--
-- -   @IN_PROGRESS@ - The requested operation is in progress.
--
-- -   @IN_PROGRESS_IN_ERROR@ - The provisioned product is under change but
--     the requested operation failed and some remediation is occurring.
--     For example, a rollback.
--
-- -   @SUCCEEDED@ - The requested operation has successfully completed.
--
-- -   @FAILED@ - The requested operation has unsuccessfully completed.
--     Investigate using the error messages returned.
recordDetail_status :: Lens.Lens' RecordDetail (Prelude.Maybe RecordStatus)
recordDetail_status :: Lens' RecordDetail (Maybe RecordStatus)
recordDetail_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RecordDetail' {Maybe RecordStatus
status :: Maybe RecordStatus
$sel:status:RecordDetail' :: RecordDetail -> Maybe RecordStatus
status} -> Maybe RecordStatus
status) (\s :: RecordDetail
s@RecordDetail' {} Maybe RecordStatus
a -> RecordDetail
s {$sel:status:RecordDetail' :: Maybe RecordStatus
status = Maybe RecordStatus
a} :: RecordDetail)

-- | The time when the record was last updated.
recordDetail_updatedTime :: Lens.Lens' RecordDetail (Prelude.Maybe Prelude.UTCTime)
recordDetail_updatedTime :: Lens' RecordDetail (Maybe UTCTime)
recordDetail_updatedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RecordDetail' {Maybe POSIX
updatedTime :: Maybe POSIX
$sel:updatedTime:RecordDetail' :: RecordDetail -> Maybe POSIX
updatedTime} -> Maybe POSIX
updatedTime) (\s :: RecordDetail
s@RecordDetail' {} Maybe POSIX
a -> RecordDetail
s {$sel:updatedTime:RecordDetail' :: Maybe POSIX
updatedTime = Maybe POSIX
a} :: RecordDetail) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Data.FromJSON RecordDetail where
  parseJSON :: Value -> Parser RecordDetail
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"RecordDetail"
      ( \Object
x ->
          Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [RecordError]
-> Maybe Text
-> Maybe [RecordTag]
-> Maybe Text
-> Maybe RecordStatus
-> Maybe POSIX
-> RecordDetail
RecordDetail'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CreatedTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"LaunchRoleArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"PathId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ProductId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ProvisionedProductId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ProvisionedProductName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ProvisionedProductType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ProvisioningArtifactId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"RecordErrors" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"RecordId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"RecordTags" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"RecordType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"UpdatedTime")
      )

instance Prelude.Hashable RecordDetail where
  hashWithSalt :: Int -> RecordDetail -> Int
hashWithSalt Int
_salt RecordDetail' {Maybe [RecordError]
Maybe [RecordTag]
Maybe Text
Maybe POSIX
Maybe RecordStatus
updatedTime :: Maybe POSIX
status :: Maybe RecordStatus
recordType :: Maybe Text
recordTags :: Maybe [RecordTag]
recordId :: Maybe Text
recordErrors :: Maybe [RecordError]
provisioningArtifactId :: Maybe Text
provisionedProductType :: Maybe Text
provisionedProductName :: Maybe Text
provisionedProductId :: Maybe Text
productId :: Maybe Text
pathId :: Maybe Text
launchRoleArn :: Maybe Text
createdTime :: Maybe POSIX
$sel:updatedTime:RecordDetail' :: RecordDetail -> Maybe POSIX
$sel:status:RecordDetail' :: RecordDetail -> Maybe RecordStatus
$sel:recordType:RecordDetail' :: RecordDetail -> Maybe Text
$sel:recordTags:RecordDetail' :: RecordDetail -> Maybe [RecordTag]
$sel:recordId:RecordDetail' :: RecordDetail -> Maybe Text
$sel:recordErrors:RecordDetail' :: RecordDetail -> Maybe [RecordError]
$sel:provisioningArtifactId:RecordDetail' :: RecordDetail -> Maybe Text
$sel:provisionedProductType:RecordDetail' :: RecordDetail -> Maybe Text
$sel:provisionedProductName:RecordDetail' :: RecordDetail -> Maybe Text
$sel:provisionedProductId:RecordDetail' :: RecordDetail -> Maybe Text
$sel:productId:RecordDetail' :: RecordDetail -> Maybe Text
$sel:pathId:RecordDetail' :: RecordDetail -> Maybe Text
$sel:launchRoleArn:RecordDetail' :: RecordDetail -> Maybe Text
$sel:createdTime:RecordDetail' :: RecordDetail -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
launchRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pathId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
productId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
provisionedProductId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
provisionedProductName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
provisionedProductType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
provisioningArtifactId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [RecordError]
recordErrors
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
recordId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [RecordTag]
recordTags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
recordType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RecordStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
updatedTime

instance Prelude.NFData RecordDetail where
  rnf :: RecordDetail -> ()
rnf RecordDetail' {Maybe [RecordError]
Maybe [RecordTag]
Maybe Text
Maybe POSIX
Maybe RecordStatus
updatedTime :: Maybe POSIX
status :: Maybe RecordStatus
recordType :: Maybe Text
recordTags :: Maybe [RecordTag]
recordId :: Maybe Text
recordErrors :: Maybe [RecordError]
provisioningArtifactId :: Maybe Text
provisionedProductType :: Maybe Text
provisionedProductName :: Maybe Text
provisionedProductId :: Maybe Text
productId :: Maybe Text
pathId :: Maybe Text
launchRoleArn :: Maybe Text
createdTime :: Maybe POSIX
$sel:updatedTime:RecordDetail' :: RecordDetail -> Maybe POSIX
$sel:status:RecordDetail' :: RecordDetail -> Maybe RecordStatus
$sel:recordType:RecordDetail' :: RecordDetail -> Maybe Text
$sel:recordTags:RecordDetail' :: RecordDetail -> Maybe [RecordTag]
$sel:recordId:RecordDetail' :: RecordDetail -> Maybe Text
$sel:recordErrors:RecordDetail' :: RecordDetail -> Maybe [RecordError]
$sel:provisioningArtifactId:RecordDetail' :: RecordDetail -> Maybe Text
$sel:provisionedProductType:RecordDetail' :: RecordDetail -> Maybe Text
$sel:provisionedProductName:RecordDetail' :: RecordDetail -> Maybe Text
$sel:provisionedProductId:RecordDetail' :: RecordDetail -> Maybe Text
$sel:productId:RecordDetail' :: RecordDetail -> Maybe Text
$sel:pathId:RecordDetail' :: RecordDetail -> Maybe Text
$sel:launchRoleArn:RecordDetail' :: RecordDetail -> Maybe Text
$sel:createdTime:RecordDetail' :: RecordDetail -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
launchRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pathId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
productId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
provisionedProductId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
provisionedProductName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
provisionedProductType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
provisioningArtifactId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [RecordError]
recordErrors
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
recordId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [RecordTag]
recordTags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
recordType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RecordStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
updatedTime