{-# 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.SecretsManager.RemoveRegionsFromReplication
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- For a secret that is replicated to other Regions, deletes the secret
-- replicas from the Regions you specify.
--
-- Secrets Manager generates a CloudTrail log entry when you call this
-- action. Do not include sensitive information in request parameters
-- because it might be logged. For more information, see
-- <https://docs.aws.amazon.com/secretsmanager/latest/userguide/retrieve-ct-entries.html Logging Secrets Manager events with CloudTrail>.
--
-- __Required permissions:__ @secretsmanager:RemoveRegionsFromReplication@.
-- For more information, see
-- <https://docs.aws.amazon.com/secretsmanager/latest/userguide/reference_iam-permissions.html#reference_iam-permissions_actions IAM policy actions for Secrets Manager>
-- and
-- <https://docs.aws.amazon.com/secretsmanager/latest/userguide/auth-and-access.html Authentication and access control in Secrets Manager>.
module Amazonka.SecretsManager.RemoveRegionsFromReplication
  ( -- * Creating a Request
    RemoveRegionsFromReplication (..),
    newRemoveRegionsFromReplication,

    -- * Request Lenses
    removeRegionsFromReplication_secretId,
    removeRegionsFromReplication_removeReplicaRegions,

    -- * Destructuring the Response
    RemoveRegionsFromReplicationResponse (..),
    newRemoveRegionsFromReplicationResponse,

    -- * Response Lenses
    removeRegionsFromReplicationResponse_arn,
    removeRegionsFromReplicationResponse_replicationStatus,
    removeRegionsFromReplicationResponse_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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.SecretsManager.Types

-- | /See:/ 'newRemoveRegionsFromReplication' smart constructor.
data RemoveRegionsFromReplication = RemoveRegionsFromReplication'
  { -- | The ARN or name of the secret.
    RemoveRegionsFromReplication -> Text
secretId :: Prelude.Text,
    -- | The Regions of the replicas to remove.
    RemoveRegionsFromReplication -> NonEmpty Text
removeReplicaRegions :: Prelude.NonEmpty Prelude.Text
  }
  deriving (RemoveRegionsFromReplication
-> RemoveRegionsFromReplication -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveRegionsFromReplication
-> RemoveRegionsFromReplication -> Bool
$c/= :: RemoveRegionsFromReplication
-> RemoveRegionsFromReplication -> Bool
== :: RemoveRegionsFromReplication
-> RemoveRegionsFromReplication -> Bool
$c== :: RemoveRegionsFromReplication
-> RemoveRegionsFromReplication -> Bool
Prelude.Eq, ReadPrec [RemoveRegionsFromReplication]
ReadPrec RemoveRegionsFromReplication
Int -> ReadS RemoveRegionsFromReplication
ReadS [RemoveRegionsFromReplication]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RemoveRegionsFromReplication]
$creadListPrec :: ReadPrec [RemoveRegionsFromReplication]
readPrec :: ReadPrec RemoveRegionsFromReplication
$creadPrec :: ReadPrec RemoveRegionsFromReplication
readList :: ReadS [RemoveRegionsFromReplication]
$creadList :: ReadS [RemoveRegionsFromReplication]
readsPrec :: Int -> ReadS RemoveRegionsFromReplication
$creadsPrec :: Int -> ReadS RemoveRegionsFromReplication
Prelude.Read, Int -> RemoveRegionsFromReplication -> ShowS
[RemoveRegionsFromReplication] -> ShowS
RemoveRegionsFromReplication -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveRegionsFromReplication] -> ShowS
$cshowList :: [RemoveRegionsFromReplication] -> ShowS
show :: RemoveRegionsFromReplication -> String
$cshow :: RemoveRegionsFromReplication -> String
showsPrec :: Int -> RemoveRegionsFromReplication -> ShowS
$cshowsPrec :: Int -> RemoveRegionsFromReplication -> ShowS
Prelude.Show, forall x.
Rep RemoveRegionsFromReplication x -> RemoveRegionsFromReplication
forall x.
RemoveRegionsFromReplication -> Rep RemoveRegionsFromReplication x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RemoveRegionsFromReplication x -> RemoveRegionsFromReplication
$cfrom :: forall x.
RemoveRegionsFromReplication -> Rep RemoveRegionsFromReplication x
Prelude.Generic)

-- |
-- Create a value of 'RemoveRegionsFromReplication' 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:
--
-- 'secretId', 'removeRegionsFromReplication_secretId' - The ARN or name of the secret.
--
-- 'removeReplicaRegions', 'removeRegionsFromReplication_removeReplicaRegions' - The Regions of the replicas to remove.
newRemoveRegionsFromReplication ::
  -- | 'secretId'
  Prelude.Text ->
  -- | 'removeReplicaRegions'
  Prelude.NonEmpty Prelude.Text ->
  RemoveRegionsFromReplication
newRemoveRegionsFromReplication :: Text -> NonEmpty Text -> RemoveRegionsFromReplication
newRemoveRegionsFromReplication
  Text
pSecretId_
  NonEmpty Text
pRemoveReplicaRegions_ =
    RemoveRegionsFromReplication'
      { $sel:secretId:RemoveRegionsFromReplication' :: Text
secretId =
          Text
pSecretId_,
        $sel:removeReplicaRegions:RemoveRegionsFromReplication' :: NonEmpty Text
removeReplicaRegions =
          forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty Text
pRemoveReplicaRegions_
      }

-- | The ARN or name of the secret.
removeRegionsFromReplication_secretId :: Lens.Lens' RemoveRegionsFromReplication Prelude.Text
removeRegionsFromReplication_secretId :: Lens' RemoveRegionsFromReplication Text
removeRegionsFromReplication_secretId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveRegionsFromReplication' {Text
secretId :: Text
$sel:secretId:RemoveRegionsFromReplication' :: RemoveRegionsFromReplication -> Text
secretId} -> Text
secretId) (\s :: RemoveRegionsFromReplication
s@RemoveRegionsFromReplication' {} Text
a -> RemoveRegionsFromReplication
s {$sel:secretId:RemoveRegionsFromReplication' :: Text
secretId = Text
a} :: RemoveRegionsFromReplication)

-- | The Regions of the replicas to remove.
removeRegionsFromReplication_removeReplicaRegions :: Lens.Lens' RemoveRegionsFromReplication (Prelude.NonEmpty Prelude.Text)
removeRegionsFromReplication_removeReplicaRegions :: Lens' RemoveRegionsFromReplication (NonEmpty Text)
removeRegionsFromReplication_removeReplicaRegions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveRegionsFromReplication' {NonEmpty Text
removeReplicaRegions :: NonEmpty Text
$sel:removeReplicaRegions:RemoveRegionsFromReplication' :: RemoveRegionsFromReplication -> NonEmpty Text
removeReplicaRegions} -> NonEmpty Text
removeReplicaRegions) (\s :: RemoveRegionsFromReplication
s@RemoveRegionsFromReplication' {} NonEmpty Text
a -> RemoveRegionsFromReplication
s {$sel:removeReplicaRegions:RemoveRegionsFromReplication' :: NonEmpty Text
removeReplicaRegions = NonEmpty Text
a} :: RemoveRegionsFromReplication) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest RemoveRegionsFromReplication where
  type
    AWSResponse RemoveRegionsFromReplication =
      RemoveRegionsFromReplicationResponse
  request :: (Service -> Service)
-> RemoveRegionsFromReplication
-> Request RemoveRegionsFromReplication
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 RemoveRegionsFromReplication
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse RemoveRegionsFromReplication)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe [ReplicationStatusType]
-> Int
-> RemoveRegionsFromReplicationResponse
RemoveRegionsFromReplicationResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ARN")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ReplicationStatus"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => 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
    RemoveRegionsFromReplication
  where
  hashWithSalt :: Int -> RemoveRegionsFromReplication -> Int
hashWithSalt Int
_salt RemoveRegionsFromReplication' {NonEmpty Text
Text
removeReplicaRegions :: NonEmpty Text
secretId :: Text
$sel:removeReplicaRegions:RemoveRegionsFromReplication' :: RemoveRegionsFromReplication -> NonEmpty Text
$sel:secretId:RemoveRegionsFromReplication' :: RemoveRegionsFromReplication -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
secretId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Text
removeReplicaRegions

instance Prelude.NFData RemoveRegionsFromReplication where
  rnf :: RemoveRegionsFromReplication -> ()
rnf RemoveRegionsFromReplication' {NonEmpty Text
Text
removeReplicaRegions :: NonEmpty Text
secretId :: Text
$sel:removeReplicaRegions:RemoveRegionsFromReplication' :: RemoveRegionsFromReplication -> NonEmpty Text
$sel:secretId:RemoveRegionsFromReplication' :: RemoveRegionsFromReplication -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
secretId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Text
removeReplicaRegions

instance Data.ToHeaders RemoveRegionsFromReplication where
  toHeaders :: RemoveRegionsFromReplication -> 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
"secretsmanager.RemoveRegionsFromReplication" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON RemoveRegionsFromReplication where
  toJSON :: RemoveRegionsFromReplication -> Value
toJSON RemoveRegionsFromReplication' {NonEmpty Text
Text
removeReplicaRegions :: NonEmpty Text
secretId :: Text
$sel:removeReplicaRegions:RemoveRegionsFromReplication' :: RemoveRegionsFromReplication -> NonEmpty Text
$sel:secretId:RemoveRegionsFromReplication' :: RemoveRegionsFromReplication -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"SecretId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
secretId),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"RemoveReplicaRegions"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty Text
removeReplicaRegions
              )
          ]
      )

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

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

-- | /See:/ 'newRemoveRegionsFromReplicationResponse' smart constructor.
data RemoveRegionsFromReplicationResponse = RemoveRegionsFromReplicationResponse'
  { -- | The ARN of the primary secret.
    RemoveRegionsFromReplicationResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The status of replicas for this secret after you remove Regions.
    RemoveRegionsFromReplicationResponse
-> Maybe [ReplicationStatusType]
replicationStatus :: Prelude.Maybe [ReplicationStatusType],
    -- | The response's http status code.
    RemoveRegionsFromReplicationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (RemoveRegionsFromReplicationResponse
-> RemoveRegionsFromReplicationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveRegionsFromReplicationResponse
-> RemoveRegionsFromReplicationResponse -> Bool
$c/= :: RemoveRegionsFromReplicationResponse
-> RemoveRegionsFromReplicationResponse -> Bool
== :: RemoveRegionsFromReplicationResponse
-> RemoveRegionsFromReplicationResponse -> Bool
$c== :: RemoveRegionsFromReplicationResponse
-> RemoveRegionsFromReplicationResponse -> Bool
Prelude.Eq, ReadPrec [RemoveRegionsFromReplicationResponse]
ReadPrec RemoveRegionsFromReplicationResponse
Int -> ReadS RemoveRegionsFromReplicationResponse
ReadS [RemoveRegionsFromReplicationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RemoveRegionsFromReplicationResponse]
$creadListPrec :: ReadPrec [RemoveRegionsFromReplicationResponse]
readPrec :: ReadPrec RemoveRegionsFromReplicationResponse
$creadPrec :: ReadPrec RemoveRegionsFromReplicationResponse
readList :: ReadS [RemoveRegionsFromReplicationResponse]
$creadList :: ReadS [RemoveRegionsFromReplicationResponse]
readsPrec :: Int -> ReadS RemoveRegionsFromReplicationResponse
$creadsPrec :: Int -> ReadS RemoveRegionsFromReplicationResponse
Prelude.Read, Int -> RemoveRegionsFromReplicationResponse -> ShowS
[RemoveRegionsFromReplicationResponse] -> ShowS
RemoveRegionsFromReplicationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveRegionsFromReplicationResponse] -> ShowS
$cshowList :: [RemoveRegionsFromReplicationResponse] -> ShowS
show :: RemoveRegionsFromReplicationResponse -> String
$cshow :: RemoveRegionsFromReplicationResponse -> String
showsPrec :: Int -> RemoveRegionsFromReplicationResponse -> ShowS
$cshowsPrec :: Int -> RemoveRegionsFromReplicationResponse -> ShowS
Prelude.Show, forall x.
Rep RemoveRegionsFromReplicationResponse x
-> RemoveRegionsFromReplicationResponse
forall x.
RemoveRegionsFromReplicationResponse
-> Rep RemoveRegionsFromReplicationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RemoveRegionsFromReplicationResponse x
-> RemoveRegionsFromReplicationResponse
$cfrom :: forall x.
RemoveRegionsFromReplicationResponse
-> Rep RemoveRegionsFromReplicationResponse x
Prelude.Generic)

-- |
-- Create a value of 'RemoveRegionsFromReplicationResponse' 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:
--
-- 'arn', 'removeRegionsFromReplicationResponse_arn' - The ARN of the primary secret.
--
-- 'replicationStatus', 'removeRegionsFromReplicationResponse_replicationStatus' - The status of replicas for this secret after you remove Regions.
--
-- 'httpStatus', 'removeRegionsFromReplicationResponse_httpStatus' - The response's http status code.
newRemoveRegionsFromReplicationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RemoveRegionsFromReplicationResponse
newRemoveRegionsFromReplicationResponse :: Int -> RemoveRegionsFromReplicationResponse
newRemoveRegionsFromReplicationResponse Int
pHttpStatus_ =
  RemoveRegionsFromReplicationResponse'
    { $sel:arn:RemoveRegionsFromReplicationResponse' :: Maybe Text
arn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:replicationStatus:RemoveRegionsFromReplicationResponse' :: Maybe [ReplicationStatusType]
replicationStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RemoveRegionsFromReplicationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the primary secret.
removeRegionsFromReplicationResponse_arn :: Lens.Lens' RemoveRegionsFromReplicationResponse (Prelude.Maybe Prelude.Text)
removeRegionsFromReplicationResponse_arn :: Lens' RemoveRegionsFromReplicationResponse (Maybe Text)
removeRegionsFromReplicationResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveRegionsFromReplicationResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:RemoveRegionsFromReplicationResponse' :: RemoveRegionsFromReplicationResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: RemoveRegionsFromReplicationResponse
s@RemoveRegionsFromReplicationResponse' {} Maybe Text
a -> RemoveRegionsFromReplicationResponse
s {$sel:arn:RemoveRegionsFromReplicationResponse' :: Maybe Text
arn = Maybe Text
a} :: RemoveRegionsFromReplicationResponse)

-- | The status of replicas for this secret after you remove Regions.
removeRegionsFromReplicationResponse_replicationStatus :: Lens.Lens' RemoveRegionsFromReplicationResponse (Prelude.Maybe [ReplicationStatusType])
removeRegionsFromReplicationResponse_replicationStatus :: Lens'
  RemoveRegionsFromReplicationResponse
  (Maybe [ReplicationStatusType])
removeRegionsFromReplicationResponse_replicationStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveRegionsFromReplicationResponse' {Maybe [ReplicationStatusType]
replicationStatus :: Maybe [ReplicationStatusType]
$sel:replicationStatus:RemoveRegionsFromReplicationResponse' :: RemoveRegionsFromReplicationResponse
-> Maybe [ReplicationStatusType]
replicationStatus} -> Maybe [ReplicationStatusType]
replicationStatus) (\s :: RemoveRegionsFromReplicationResponse
s@RemoveRegionsFromReplicationResponse' {} Maybe [ReplicationStatusType]
a -> RemoveRegionsFromReplicationResponse
s {$sel:replicationStatus:RemoveRegionsFromReplicationResponse' :: Maybe [ReplicationStatusType]
replicationStatus = Maybe [ReplicationStatusType]
a} :: RemoveRegionsFromReplicationResponse) 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 response's http status code.
removeRegionsFromReplicationResponse_httpStatus :: Lens.Lens' RemoveRegionsFromReplicationResponse Prelude.Int
removeRegionsFromReplicationResponse_httpStatus :: Lens' RemoveRegionsFromReplicationResponse Int
removeRegionsFromReplicationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveRegionsFromReplicationResponse' {Int
httpStatus :: Int
$sel:httpStatus:RemoveRegionsFromReplicationResponse' :: RemoveRegionsFromReplicationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: RemoveRegionsFromReplicationResponse
s@RemoveRegionsFromReplicationResponse' {} Int
a -> RemoveRegionsFromReplicationResponse
s {$sel:httpStatus:RemoveRegionsFromReplicationResponse' :: Int
httpStatus = Int
a} :: RemoveRegionsFromReplicationResponse)

instance
  Prelude.NFData
    RemoveRegionsFromReplicationResponse
  where
  rnf :: RemoveRegionsFromReplicationResponse -> ()
rnf RemoveRegionsFromReplicationResponse' {Int
Maybe [ReplicationStatusType]
Maybe Text
httpStatus :: Int
replicationStatus :: Maybe [ReplicationStatusType]
arn :: Maybe Text
$sel:httpStatus:RemoveRegionsFromReplicationResponse' :: RemoveRegionsFromReplicationResponse -> Int
$sel:replicationStatus:RemoveRegionsFromReplicationResponse' :: RemoveRegionsFromReplicationResponse
-> Maybe [ReplicationStatusType]
$sel:arn:RemoveRegionsFromReplicationResponse' :: RemoveRegionsFromReplicationResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ReplicationStatusType]
replicationStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus