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

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

-- |
-- Module      : Amazonka.Proton.NotifyResourceDeploymentStatusChange
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Notify Proton of status changes to a provisioned resource when you use
-- self-managed provisioning.
--
-- For more information, see
-- <https://docs.aws.amazon.com/proton/latest/userguide/ag-works-prov-methods.html#ag-works-prov-methods-self Self-managed provisioning>
-- in the /Proton User Guide/.
module Amazonka.Proton.NotifyResourceDeploymentStatusChange
  ( -- * Creating a Request
    NotifyResourceDeploymentStatusChange (..),
    newNotifyResourceDeploymentStatusChange,

    -- * Request Lenses
    notifyResourceDeploymentStatusChange_deploymentId,
    notifyResourceDeploymentStatusChange_outputs,
    notifyResourceDeploymentStatusChange_status,
    notifyResourceDeploymentStatusChange_statusMessage,
    notifyResourceDeploymentStatusChange_resourceArn,

    -- * Destructuring the Response
    NotifyResourceDeploymentStatusChangeResponse (..),
    newNotifyResourceDeploymentStatusChangeResponse,

    -- * Response Lenses
    notifyResourceDeploymentStatusChangeResponse_httpStatus,
  )
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.Proton.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newNotifyResourceDeploymentStatusChange' smart constructor.
data NotifyResourceDeploymentStatusChange = NotifyResourceDeploymentStatusChange'
  { -- | The deployment ID for your provisioned resource.
    NotifyResourceDeploymentStatusChange -> Maybe Text
deploymentId :: Prelude.Maybe Prelude.Text,
    -- | The provisioned resource state change detail data that\'s returned by
    -- Proton.
    NotifyResourceDeploymentStatusChange -> Maybe [Sensitive Output]
outputs :: Prelude.Maybe [Data.Sensitive Output],
    -- | The status of your provisioned resource.
    NotifyResourceDeploymentStatusChange
-> Maybe ResourceDeploymentStatus
status :: Prelude.Maybe ResourceDeploymentStatus,
    -- | The deployment status message for your provisioned resource.
    NotifyResourceDeploymentStatusChange -> Maybe (Sensitive Text)
statusMessage :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The provisioned resource Amazon Resource Name (ARN).
    NotifyResourceDeploymentStatusChange -> Text
resourceArn :: Prelude.Text
  }
  deriving (NotifyResourceDeploymentStatusChange
-> NotifyResourceDeploymentStatusChange -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NotifyResourceDeploymentStatusChange
-> NotifyResourceDeploymentStatusChange -> Bool
$c/= :: NotifyResourceDeploymentStatusChange
-> NotifyResourceDeploymentStatusChange -> Bool
== :: NotifyResourceDeploymentStatusChange
-> NotifyResourceDeploymentStatusChange -> Bool
$c== :: NotifyResourceDeploymentStatusChange
-> NotifyResourceDeploymentStatusChange -> Bool
Prelude.Eq, Int -> NotifyResourceDeploymentStatusChange -> ShowS
[NotifyResourceDeploymentStatusChange] -> ShowS
NotifyResourceDeploymentStatusChange -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NotifyResourceDeploymentStatusChange] -> ShowS
$cshowList :: [NotifyResourceDeploymentStatusChange] -> ShowS
show :: NotifyResourceDeploymentStatusChange -> String
$cshow :: NotifyResourceDeploymentStatusChange -> String
showsPrec :: Int -> NotifyResourceDeploymentStatusChange -> ShowS
$cshowsPrec :: Int -> NotifyResourceDeploymentStatusChange -> ShowS
Prelude.Show, forall x.
Rep NotifyResourceDeploymentStatusChange x
-> NotifyResourceDeploymentStatusChange
forall x.
NotifyResourceDeploymentStatusChange
-> Rep NotifyResourceDeploymentStatusChange x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep NotifyResourceDeploymentStatusChange x
-> NotifyResourceDeploymentStatusChange
$cfrom :: forall x.
NotifyResourceDeploymentStatusChange
-> Rep NotifyResourceDeploymentStatusChange x
Prelude.Generic)

-- |
-- Create a value of 'NotifyResourceDeploymentStatusChange' 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:
--
-- 'deploymentId', 'notifyResourceDeploymentStatusChange_deploymentId' - The deployment ID for your provisioned resource.
--
-- 'outputs', 'notifyResourceDeploymentStatusChange_outputs' - The provisioned resource state change detail data that\'s returned by
-- Proton.
--
-- 'status', 'notifyResourceDeploymentStatusChange_status' - The status of your provisioned resource.
--
-- 'statusMessage', 'notifyResourceDeploymentStatusChange_statusMessage' - The deployment status message for your provisioned resource.
--
-- 'resourceArn', 'notifyResourceDeploymentStatusChange_resourceArn' - The provisioned resource Amazon Resource Name (ARN).
newNotifyResourceDeploymentStatusChange ::
  -- | 'resourceArn'
  Prelude.Text ->
  NotifyResourceDeploymentStatusChange
newNotifyResourceDeploymentStatusChange :: Text -> NotifyResourceDeploymentStatusChange
newNotifyResourceDeploymentStatusChange Text
pResourceArn_ =
  NotifyResourceDeploymentStatusChange'
    { $sel:deploymentId:NotifyResourceDeploymentStatusChange' :: Maybe Text
deploymentId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:outputs:NotifyResourceDeploymentStatusChange' :: Maybe [Sensitive Output]
outputs = forall a. Maybe a
Prelude.Nothing,
      $sel:status:NotifyResourceDeploymentStatusChange' :: Maybe ResourceDeploymentStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:statusMessage:NotifyResourceDeploymentStatusChange' :: Maybe (Sensitive Text)
statusMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceArn:NotifyResourceDeploymentStatusChange' :: Text
resourceArn = Text
pResourceArn_
    }

-- | The deployment ID for your provisioned resource.
notifyResourceDeploymentStatusChange_deploymentId :: Lens.Lens' NotifyResourceDeploymentStatusChange (Prelude.Maybe Prelude.Text)
notifyResourceDeploymentStatusChange_deploymentId :: Lens' NotifyResourceDeploymentStatusChange (Maybe Text)
notifyResourceDeploymentStatusChange_deploymentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NotifyResourceDeploymentStatusChange' {Maybe Text
deploymentId :: Maybe Text
$sel:deploymentId:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange -> Maybe Text
deploymentId} -> Maybe Text
deploymentId) (\s :: NotifyResourceDeploymentStatusChange
s@NotifyResourceDeploymentStatusChange' {} Maybe Text
a -> NotifyResourceDeploymentStatusChange
s {$sel:deploymentId:NotifyResourceDeploymentStatusChange' :: Maybe Text
deploymentId = Maybe Text
a} :: NotifyResourceDeploymentStatusChange)

-- | The provisioned resource state change detail data that\'s returned by
-- Proton.
notifyResourceDeploymentStatusChange_outputs :: Lens.Lens' NotifyResourceDeploymentStatusChange (Prelude.Maybe [Output])
notifyResourceDeploymentStatusChange_outputs :: Lens' NotifyResourceDeploymentStatusChange (Maybe [Output])
notifyResourceDeploymentStatusChange_outputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NotifyResourceDeploymentStatusChange' {Maybe [Sensitive Output]
outputs :: Maybe [Sensitive Output]
$sel:outputs:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange -> Maybe [Sensitive Output]
outputs} -> Maybe [Sensitive Output]
outputs) (\s :: NotifyResourceDeploymentStatusChange
s@NotifyResourceDeploymentStatusChange' {} Maybe [Sensitive Output]
a -> NotifyResourceDeploymentStatusChange
s {$sel:outputs:NotifyResourceDeploymentStatusChange' :: Maybe [Sensitive Output]
outputs = Maybe [Sensitive Output]
a} :: NotifyResourceDeploymentStatusChange) 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 status of your provisioned resource.
notifyResourceDeploymentStatusChange_status :: Lens.Lens' NotifyResourceDeploymentStatusChange (Prelude.Maybe ResourceDeploymentStatus)
notifyResourceDeploymentStatusChange_status :: Lens'
  NotifyResourceDeploymentStatusChange
  (Maybe ResourceDeploymentStatus)
notifyResourceDeploymentStatusChange_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NotifyResourceDeploymentStatusChange' {Maybe ResourceDeploymentStatus
status :: Maybe ResourceDeploymentStatus
$sel:status:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange
-> Maybe ResourceDeploymentStatus
status} -> Maybe ResourceDeploymentStatus
status) (\s :: NotifyResourceDeploymentStatusChange
s@NotifyResourceDeploymentStatusChange' {} Maybe ResourceDeploymentStatus
a -> NotifyResourceDeploymentStatusChange
s {$sel:status:NotifyResourceDeploymentStatusChange' :: Maybe ResourceDeploymentStatus
status = Maybe ResourceDeploymentStatus
a} :: NotifyResourceDeploymentStatusChange)

-- | The deployment status message for your provisioned resource.
notifyResourceDeploymentStatusChange_statusMessage :: Lens.Lens' NotifyResourceDeploymentStatusChange (Prelude.Maybe Prelude.Text)
notifyResourceDeploymentStatusChange_statusMessage :: Lens' NotifyResourceDeploymentStatusChange (Maybe Text)
notifyResourceDeploymentStatusChange_statusMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NotifyResourceDeploymentStatusChange' {Maybe (Sensitive Text)
statusMessage :: Maybe (Sensitive Text)
$sel:statusMessage:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange -> Maybe (Sensitive Text)
statusMessage} -> Maybe (Sensitive Text)
statusMessage) (\s :: NotifyResourceDeploymentStatusChange
s@NotifyResourceDeploymentStatusChange' {} Maybe (Sensitive Text)
a -> NotifyResourceDeploymentStatusChange
s {$sel:statusMessage:NotifyResourceDeploymentStatusChange' :: Maybe (Sensitive Text)
statusMessage = Maybe (Sensitive Text)
a} :: NotifyResourceDeploymentStatusChange) 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. Iso' (Sensitive a) a
Data._Sensitive

-- | The provisioned resource Amazon Resource Name (ARN).
notifyResourceDeploymentStatusChange_resourceArn :: Lens.Lens' NotifyResourceDeploymentStatusChange Prelude.Text
notifyResourceDeploymentStatusChange_resourceArn :: Lens' NotifyResourceDeploymentStatusChange Text
notifyResourceDeploymentStatusChange_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NotifyResourceDeploymentStatusChange' {Text
resourceArn :: Text
$sel:resourceArn:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange -> Text
resourceArn} -> Text
resourceArn) (\s :: NotifyResourceDeploymentStatusChange
s@NotifyResourceDeploymentStatusChange' {} Text
a -> NotifyResourceDeploymentStatusChange
s {$sel:resourceArn:NotifyResourceDeploymentStatusChange' :: Text
resourceArn = Text
a} :: NotifyResourceDeploymentStatusChange)

instance
  Core.AWSRequest
    NotifyResourceDeploymentStatusChange
  where
  type
    AWSResponse NotifyResourceDeploymentStatusChange =
      NotifyResourceDeploymentStatusChangeResponse
  request :: (Service -> Service)
-> NotifyResourceDeploymentStatusChange
-> Request NotifyResourceDeploymentStatusChange
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy NotifyResourceDeploymentStatusChange
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse NotifyResourceDeploymentStatusChange)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> NotifyResourceDeploymentStatusChangeResponse
NotifyResourceDeploymentStatusChangeResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance
  Prelude.Hashable
    NotifyResourceDeploymentStatusChange
  where
  hashWithSalt :: Int -> NotifyResourceDeploymentStatusChange -> Int
hashWithSalt
    Int
_salt
    NotifyResourceDeploymentStatusChange' {Maybe [Sensitive Output]
Maybe Text
Maybe (Sensitive Text)
Maybe ResourceDeploymentStatus
Text
resourceArn :: Text
statusMessage :: Maybe (Sensitive Text)
status :: Maybe ResourceDeploymentStatus
outputs :: Maybe [Sensitive Output]
deploymentId :: Maybe Text
$sel:resourceArn:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange -> Text
$sel:statusMessage:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange -> Maybe (Sensitive Text)
$sel:status:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange
-> Maybe ResourceDeploymentStatus
$sel:outputs:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange -> Maybe [Sensitive Output]
$sel:deploymentId:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange -> Maybe Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
deploymentId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Sensitive Output]
outputs
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResourceDeploymentStatus
status
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
statusMessage
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceArn

instance
  Prelude.NFData
    NotifyResourceDeploymentStatusChange
  where
  rnf :: NotifyResourceDeploymentStatusChange -> ()
rnf NotifyResourceDeploymentStatusChange' {Maybe [Sensitive Output]
Maybe Text
Maybe (Sensitive Text)
Maybe ResourceDeploymentStatus
Text
resourceArn :: Text
statusMessage :: Maybe (Sensitive Text)
status :: Maybe ResourceDeploymentStatus
outputs :: Maybe [Sensitive Output]
deploymentId :: Maybe Text
$sel:resourceArn:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange -> Text
$sel:statusMessage:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange -> Maybe (Sensitive Text)
$sel:status:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange
-> Maybe ResourceDeploymentStatus
$sel:outputs:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange -> Maybe [Sensitive Output]
$sel:deploymentId:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
deploymentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Sensitive Output]
outputs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ResourceDeploymentStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
statusMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
resourceArn

instance
  Data.ToHeaders
    NotifyResourceDeploymentStatusChange
  where
  toHeaders :: NotifyResourceDeploymentStatusChange -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AwsProton20200720.NotifyResourceDeploymentStatusChange" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance
  Data.ToJSON
    NotifyResourceDeploymentStatusChange
  where
  toJSON :: NotifyResourceDeploymentStatusChange -> Value
toJSON NotifyResourceDeploymentStatusChange' {Maybe [Sensitive Output]
Maybe Text
Maybe (Sensitive Text)
Maybe ResourceDeploymentStatus
Text
resourceArn :: Text
statusMessage :: Maybe (Sensitive Text)
status :: Maybe ResourceDeploymentStatus
outputs :: Maybe [Sensitive Output]
deploymentId :: Maybe Text
$sel:resourceArn:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange -> Text
$sel:statusMessage:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange -> Maybe (Sensitive Text)
$sel:status:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange
-> Maybe ResourceDeploymentStatus
$sel:outputs:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange -> Maybe [Sensitive Output]
$sel:deploymentId:NotifyResourceDeploymentStatusChange' :: NotifyResourceDeploymentStatusChange -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"deploymentId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
deploymentId,
            (Key
"outputs" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Sensitive Output]
outputs,
            (Key
"status" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ResourceDeploymentStatus
status,
            (Key
"statusMessage" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Sensitive Text)
statusMessage,
            forall a. a -> Maybe a
Prelude.Just (Key
"resourceArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
resourceArn)
          ]
      )

instance
  Data.ToPath
    NotifyResourceDeploymentStatusChange
  where
  toPath :: NotifyResourceDeploymentStatusChange -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance
  Data.ToQuery
    NotifyResourceDeploymentStatusChange
  where
  toQuery :: NotifyResourceDeploymentStatusChange -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newNotifyResourceDeploymentStatusChangeResponse' smart constructor.
data NotifyResourceDeploymentStatusChangeResponse = NotifyResourceDeploymentStatusChangeResponse'
  { -- | The response's http status code.
    NotifyResourceDeploymentStatusChangeResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (NotifyResourceDeploymentStatusChangeResponse
-> NotifyResourceDeploymentStatusChangeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NotifyResourceDeploymentStatusChangeResponse
-> NotifyResourceDeploymentStatusChangeResponse -> Bool
$c/= :: NotifyResourceDeploymentStatusChangeResponse
-> NotifyResourceDeploymentStatusChangeResponse -> Bool
== :: NotifyResourceDeploymentStatusChangeResponse
-> NotifyResourceDeploymentStatusChangeResponse -> Bool
$c== :: NotifyResourceDeploymentStatusChangeResponse
-> NotifyResourceDeploymentStatusChangeResponse -> Bool
Prelude.Eq, ReadPrec [NotifyResourceDeploymentStatusChangeResponse]
ReadPrec NotifyResourceDeploymentStatusChangeResponse
Int -> ReadS NotifyResourceDeploymentStatusChangeResponse
ReadS [NotifyResourceDeploymentStatusChangeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NotifyResourceDeploymentStatusChangeResponse]
$creadListPrec :: ReadPrec [NotifyResourceDeploymentStatusChangeResponse]
readPrec :: ReadPrec NotifyResourceDeploymentStatusChangeResponse
$creadPrec :: ReadPrec NotifyResourceDeploymentStatusChangeResponse
readList :: ReadS [NotifyResourceDeploymentStatusChangeResponse]
$creadList :: ReadS [NotifyResourceDeploymentStatusChangeResponse]
readsPrec :: Int -> ReadS NotifyResourceDeploymentStatusChangeResponse
$creadsPrec :: Int -> ReadS NotifyResourceDeploymentStatusChangeResponse
Prelude.Read, Int -> NotifyResourceDeploymentStatusChangeResponse -> ShowS
[NotifyResourceDeploymentStatusChangeResponse] -> ShowS
NotifyResourceDeploymentStatusChangeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NotifyResourceDeploymentStatusChangeResponse] -> ShowS
$cshowList :: [NotifyResourceDeploymentStatusChangeResponse] -> ShowS
show :: NotifyResourceDeploymentStatusChangeResponse -> String
$cshow :: NotifyResourceDeploymentStatusChangeResponse -> String
showsPrec :: Int -> NotifyResourceDeploymentStatusChangeResponse -> ShowS
$cshowsPrec :: Int -> NotifyResourceDeploymentStatusChangeResponse -> ShowS
Prelude.Show, forall x.
Rep NotifyResourceDeploymentStatusChangeResponse x
-> NotifyResourceDeploymentStatusChangeResponse
forall x.
NotifyResourceDeploymentStatusChangeResponse
-> Rep NotifyResourceDeploymentStatusChangeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep NotifyResourceDeploymentStatusChangeResponse x
-> NotifyResourceDeploymentStatusChangeResponse
$cfrom :: forall x.
NotifyResourceDeploymentStatusChangeResponse
-> Rep NotifyResourceDeploymentStatusChangeResponse x
Prelude.Generic)

-- |
-- Create a value of 'NotifyResourceDeploymentStatusChangeResponse' 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:
--
-- 'httpStatus', 'notifyResourceDeploymentStatusChangeResponse_httpStatus' - The response's http status code.
newNotifyResourceDeploymentStatusChangeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  NotifyResourceDeploymentStatusChangeResponse
newNotifyResourceDeploymentStatusChangeResponse :: Int -> NotifyResourceDeploymentStatusChangeResponse
newNotifyResourceDeploymentStatusChangeResponse
  Int
pHttpStatus_ =
    NotifyResourceDeploymentStatusChangeResponse'
      { $sel:httpStatus:NotifyResourceDeploymentStatusChangeResponse' :: Int
httpStatus =
          Int
pHttpStatus_
      }

-- | The response's http status code.
notifyResourceDeploymentStatusChangeResponse_httpStatus :: Lens.Lens' NotifyResourceDeploymentStatusChangeResponse Prelude.Int
notifyResourceDeploymentStatusChangeResponse_httpStatus :: Lens' NotifyResourceDeploymentStatusChangeResponse Int
notifyResourceDeploymentStatusChangeResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NotifyResourceDeploymentStatusChangeResponse' {Int
httpStatus :: Int
$sel:httpStatus:NotifyResourceDeploymentStatusChangeResponse' :: NotifyResourceDeploymentStatusChangeResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: NotifyResourceDeploymentStatusChangeResponse
s@NotifyResourceDeploymentStatusChangeResponse' {} Int
a -> NotifyResourceDeploymentStatusChangeResponse
s {$sel:httpStatus:NotifyResourceDeploymentStatusChangeResponse' :: Int
httpStatus = Int
a} :: NotifyResourceDeploymentStatusChangeResponse)

instance
  Prelude.NFData
    NotifyResourceDeploymentStatusChangeResponse
  where
  rnf :: NotifyResourceDeploymentStatusChangeResponse -> ()
rnf NotifyResourceDeploymentStatusChangeResponse' {Int
httpStatus :: Int
$sel:httpStatus:NotifyResourceDeploymentStatusChangeResponse' :: NotifyResourceDeploymentStatusChangeResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus