{-# 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.StopReplicationToReplica
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes the link between the replica secret and the primary secret and
-- promotes the replica to a primary secret in the replica Region.
--
-- You must call this operation from the Region in which you want to
-- promote the replica to a primary secret.
--
-- 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:StopReplicationToReplica@. 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.StopReplicationToReplica
  ( -- * Creating a Request
    StopReplicationToReplica (..),
    newStopReplicationToReplica,

    -- * Request Lenses
    stopReplicationToReplica_secretId,

    -- * Destructuring the Response
    StopReplicationToReplicaResponse (..),
    newStopReplicationToReplicaResponse,

    -- * Response Lenses
    stopReplicationToReplicaResponse_arn,
    stopReplicationToReplicaResponse_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:/ 'newStopReplicationToReplica' smart constructor.
data StopReplicationToReplica = StopReplicationToReplica'
  { -- | The ARN of the primary secret.
    StopReplicationToReplica -> Text
secretId :: Prelude.Text
  }
  deriving (StopReplicationToReplica -> StopReplicationToReplica -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopReplicationToReplica -> StopReplicationToReplica -> Bool
$c/= :: StopReplicationToReplica -> StopReplicationToReplica -> Bool
== :: StopReplicationToReplica -> StopReplicationToReplica -> Bool
$c== :: StopReplicationToReplica -> StopReplicationToReplica -> Bool
Prelude.Eq, ReadPrec [StopReplicationToReplica]
ReadPrec StopReplicationToReplica
Int -> ReadS StopReplicationToReplica
ReadS [StopReplicationToReplica]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopReplicationToReplica]
$creadListPrec :: ReadPrec [StopReplicationToReplica]
readPrec :: ReadPrec StopReplicationToReplica
$creadPrec :: ReadPrec StopReplicationToReplica
readList :: ReadS [StopReplicationToReplica]
$creadList :: ReadS [StopReplicationToReplica]
readsPrec :: Int -> ReadS StopReplicationToReplica
$creadsPrec :: Int -> ReadS StopReplicationToReplica
Prelude.Read, Int -> StopReplicationToReplica -> ShowS
[StopReplicationToReplica] -> ShowS
StopReplicationToReplica -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopReplicationToReplica] -> ShowS
$cshowList :: [StopReplicationToReplica] -> ShowS
show :: StopReplicationToReplica -> String
$cshow :: StopReplicationToReplica -> String
showsPrec :: Int -> StopReplicationToReplica -> ShowS
$cshowsPrec :: Int -> StopReplicationToReplica -> ShowS
Prelude.Show, forall x.
Rep StopReplicationToReplica x -> StopReplicationToReplica
forall x.
StopReplicationToReplica -> Rep StopReplicationToReplica x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StopReplicationToReplica x -> StopReplicationToReplica
$cfrom :: forall x.
StopReplicationToReplica -> Rep StopReplicationToReplica x
Prelude.Generic)

-- |
-- Create a value of 'StopReplicationToReplica' 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', 'stopReplicationToReplica_secretId' - The ARN of the primary secret.
newStopReplicationToReplica ::
  -- | 'secretId'
  Prelude.Text ->
  StopReplicationToReplica
newStopReplicationToReplica :: Text -> StopReplicationToReplica
newStopReplicationToReplica Text
pSecretId_ =
  StopReplicationToReplica' {$sel:secretId:StopReplicationToReplica' :: Text
secretId = Text
pSecretId_}

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

instance Core.AWSRequest StopReplicationToReplica where
  type
    AWSResponse StopReplicationToReplica =
      StopReplicationToReplicaResponse
  request :: (Service -> Service)
-> StopReplicationToReplica -> Request StopReplicationToReplica
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 StopReplicationToReplica
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StopReplicationToReplica)))
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 -> Int -> StopReplicationToReplicaResponse
StopReplicationToReplicaResponse'
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable StopReplicationToReplica where
  hashWithSalt :: Int -> StopReplicationToReplica -> Int
hashWithSalt Int
_salt StopReplicationToReplica' {Text
secretId :: Text
$sel:secretId:StopReplicationToReplica' :: StopReplicationToReplica -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
secretId

instance Prelude.NFData StopReplicationToReplica where
  rnf :: StopReplicationToReplica -> ()
rnf StopReplicationToReplica' {Text
secretId :: Text
$sel:secretId:StopReplicationToReplica' :: StopReplicationToReplica -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
secretId

instance Data.ToHeaders StopReplicationToReplica where
  toHeaders :: StopReplicationToReplica -> 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.StopReplicationToReplica" ::
                          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 StopReplicationToReplica where
  toJSON :: StopReplicationToReplica -> Value
toJSON StopReplicationToReplica' {Text
secretId :: Text
$sel:secretId:StopReplicationToReplica' :: StopReplicationToReplica -> 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)]
      )

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

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

-- | /See:/ 'newStopReplicationToReplicaResponse' smart constructor.
data StopReplicationToReplicaResponse = StopReplicationToReplicaResponse'
  { -- | The ARN of the promoted secret. The ARN is the same as the original
    -- primary secret except the Region is changed.
    StopReplicationToReplicaResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    StopReplicationToReplicaResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StopReplicationToReplicaResponse
-> StopReplicationToReplicaResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopReplicationToReplicaResponse
-> StopReplicationToReplicaResponse -> Bool
$c/= :: StopReplicationToReplicaResponse
-> StopReplicationToReplicaResponse -> Bool
== :: StopReplicationToReplicaResponse
-> StopReplicationToReplicaResponse -> Bool
$c== :: StopReplicationToReplicaResponse
-> StopReplicationToReplicaResponse -> Bool
Prelude.Eq, ReadPrec [StopReplicationToReplicaResponse]
ReadPrec StopReplicationToReplicaResponse
Int -> ReadS StopReplicationToReplicaResponse
ReadS [StopReplicationToReplicaResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopReplicationToReplicaResponse]
$creadListPrec :: ReadPrec [StopReplicationToReplicaResponse]
readPrec :: ReadPrec StopReplicationToReplicaResponse
$creadPrec :: ReadPrec StopReplicationToReplicaResponse
readList :: ReadS [StopReplicationToReplicaResponse]
$creadList :: ReadS [StopReplicationToReplicaResponse]
readsPrec :: Int -> ReadS StopReplicationToReplicaResponse
$creadsPrec :: Int -> ReadS StopReplicationToReplicaResponse
Prelude.Read, Int -> StopReplicationToReplicaResponse -> ShowS
[StopReplicationToReplicaResponse] -> ShowS
StopReplicationToReplicaResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopReplicationToReplicaResponse] -> ShowS
$cshowList :: [StopReplicationToReplicaResponse] -> ShowS
show :: StopReplicationToReplicaResponse -> String
$cshow :: StopReplicationToReplicaResponse -> String
showsPrec :: Int -> StopReplicationToReplicaResponse -> ShowS
$cshowsPrec :: Int -> StopReplicationToReplicaResponse -> ShowS
Prelude.Show, forall x.
Rep StopReplicationToReplicaResponse x
-> StopReplicationToReplicaResponse
forall x.
StopReplicationToReplicaResponse
-> Rep StopReplicationToReplicaResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StopReplicationToReplicaResponse x
-> StopReplicationToReplicaResponse
$cfrom :: forall x.
StopReplicationToReplicaResponse
-> Rep StopReplicationToReplicaResponse x
Prelude.Generic)

-- |
-- Create a value of 'StopReplicationToReplicaResponse' 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', 'stopReplicationToReplicaResponse_arn' - The ARN of the promoted secret. The ARN is the same as the original
-- primary secret except the Region is changed.
--
-- 'httpStatus', 'stopReplicationToReplicaResponse_httpStatus' - The response's http status code.
newStopReplicationToReplicaResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StopReplicationToReplicaResponse
newStopReplicationToReplicaResponse :: Int -> StopReplicationToReplicaResponse
newStopReplicationToReplicaResponse Int
pHttpStatus_ =
  StopReplicationToReplicaResponse'
    { $sel:arn:StopReplicationToReplicaResponse' :: Maybe Text
arn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StopReplicationToReplicaResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the promoted secret. The ARN is the same as the original
-- primary secret except the Region is changed.
stopReplicationToReplicaResponse_arn :: Lens.Lens' StopReplicationToReplicaResponse (Prelude.Maybe Prelude.Text)
stopReplicationToReplicaResponse_arn :: Lens' StopReplicationToReplicaResponse (Maybe Text)
stopReplicationToReplicaResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopReplicationToReplicaResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:StopReplicationToReplicaResponse' :: StopReplicationToReplicaResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: StopReplicationToReplicaResponse
s@StopReplicationToReplicaResponse' {} Maybe Text
a -> StopReplicationToReplicaResponse
s {$sel:arn:StopReplicationToReplicaResponse' :: Maybe Text
arn = Maybe Text
a} :: StopReplicationToReplicaResponse)

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

instance
  Prelude.NFData
    StopReplicationToReplicaResponse
  where
  rnf :: StopReplicationToReplicaResponse -> ()
rnf StopReplicationToReplicaResponse' {Int
Maybe Text
httpStatus :: Int
arn :: Maybe Text
$sel:httpStatus:StopReplicationToReplicaResponse' :: StopReplicationToReplicaResponse -> Int
$sel:arn:StopReplicationToReplicaResponse' :: StopReplicationToReplicaResponse -> 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 Int
httpStatus