{-# 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.CancelRotateSecret
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Turns off automatic rotation, and if a rotation is currently in
-- progress, cancels the rotation.
--
-- If you cancel a rotation in progress, it can leave the @VersionStage@
-- labels in an unexpected state. You might need to remove the staging
-- label @AWSPENDING@ from the partially created version. You also need to
-- determine whether to roll back to the previous version of the secret by
-- moving the staging label @AWSCURRENT@ to the version that has
-- @AWSPENDING@. To determine which version has a specific staging label,
-- call ListSecretVersionIds. Then use UpdateSecretVersionStage to change
-- staging labels. For more information, see
-- <https://docs.aws.amazon.com/secretsmanager/latest/userguide/rotate-secrets_how.html How rotation works>.
--
-- To turn on automatic rotation again, call RotateSecret.
--
-- 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:CancelRotateSecret@. 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.CancelRotateSecret
  ( -- * Creating a Request
    CancelRotateSecret (..),
    newCancelRotateSecret,

    -- * Request Lenses
    cancelRotateSecret_secretId,

    -- * Destructuring the Response
    CancelRotateSecretResponse (..),
    newCancelRotateSecretResponse,

    -- * Response Lenses
    cancelRotateSecretResponse_arn,
    cancelRotateSecretResponse_name,
    cancelRotateSecretResponse_versionId,
    cancelRotateSecretResponse_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:/ 'newCancelRotateSecret' smart constructor.
data CancelRotateSecret = CancelRotateSecret'
  { -- | The ARN or name of the secret.
    --
    -- For an ARN, we recommend that you specify a complete ARN rather than a
    -- partial ARN. See
    -- <https://docs.aws.amazon.com/secretsmanager/latest/userguide/troubleshoot.html#ARN_secretnamehyphen Finding a secret from a partial ARN>.
    CancelRotateSecret -> Text
secretId :: Prelude.Text
  }
  deriving (CancelRotateSecret -> CancelRotateSecret -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelRotateSecret -> CancelRotateSecret -> Bool
$c/= :: CancelRotateSecret -> CancelRotateSecret -> Bool
== :: CancelRotateSecret -> CancelRotateSecret -> Bool
$c== :: CancelRotateSecret -> CancelRotateSecret -> Bool
Prelude.Eq, ReadPrec [CancelRotateSecret]
ReadPrec CancelRotateSecret
Int -> ReadS CancelRotateSecret
ReadS [CancelRotateSecret]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CancelRotateSecret]
$creadListPrec :: ReadPrec [CancelRotateSecret]
readPrec :: ReadPrec CancelRotateSecret
$creadPrec :: ReadPrec CancelRotateSecret
readList :: ReadS [CancelRotateSecret]
$creadList :: ReadS [CancelRotateSecret]
readsPrec :: Int -> ReadS CancelRotateSecret
$creadsPrec :: Int -> ReadS CancelRotateSecret
Prelude.Read, Int -> CancelRotateSecret -> ShowS
[CancelRotateSecret] -> ShowS
CancelRotateSecret -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelRotateSecret] -> ShowS
$cshowList :: [CancelRotateSecret] -> ShowS
show :: CancelRotateSecret -> String
$cshow :: CancelRotateSecret -> String
showsPrec :: Int -> CancelRotateSecret -> ShowS
$cshowsPrec :: Int -> CancelRotateSecret -> ShowS
Prelude.Show, forall x. Rep CancelRotateSecret x -> CancelRotateSecret
forall x. CancelRotateSecret -> Rep CancelRotateSecret x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CancelRotateSecret x -> CancelRotateSecret
$cfrom :: forall x. CancelRotateSecret -> Rep CancelRotateSecret x
Prelude.Generic)

-- |
-- Create a value of 'CancelRotateSecret' 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', 'cancelRotateSecret_secretId' - The ARN or name of the secret.
--
-- For an ARN, we recommend that you specify a complete ARN rather than a
-- partial ARN. See
-- <https://docs.aws.amazon.com/secretsmanager/latest/userguide/troubleshoot.html#ARN_secretnamehyphen Finding a secret from a partial ARN>.
newCancelRotateSecret ::
  -- | 'secretId'
  Prelude.Text ->
  CancelRotateSecret
newCancelRotateSecret :: Text -> CancelRotateSecret
newCancelRotateSecret Text
pSecretId_ =
  CancelRotateSecret' {$sel:secretId:CancelRotateSecret' :: Text
secretId = Text
pSecretId_}

-- | The ARN or name of the secret.
--
-- For an ARN, we recommend that you specify a complete ARN rather than a
-- partial ARN. See
-- <https://docs.aws.amazon.com/secretsmanager/latest/userguide/troubleshoot.html#ARN_secretnamehyphen Finding a secret from a partial ARN>.
cancelRotateSecret_secretId :: Lens.Lens' CancelRotateSecret Prelude.Text
cancelRotateSecret_secretId :: Lens' CancelRotateSecret Text
cancelRotateSecret_secretId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelRotateSecret' {Text
secretId :: Text
$sel:secretId:CancelRotateSecret' :: CancelRotateSecret -> Text
secretId} -> Text
secretId) (\s :: CancelRotateSecret
s@CancelRotateSecret' {} Text
a -> CancelRotateSecret
s {$sel:secretId:CancelRotateSecret' :: Text
secretId = Text
a} :: CancelRotateSecret)

instance Core.AWSRequest CancelRotateSecret where
  type
    AWSResponse CancelRotateSecret =
      CancelRotateSecretResponse
  request :: (Service -> Service)
-> CancelRotateSecret -> Request CancelRotateSecret
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 CancelRotateSecret
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CancelRotateSecret)))
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 Text -> Maybe Text -> Int -> CancelRotateSecretResponse
CancelRotateSecretResponse'
            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
"Name")
            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
"VersionId")
            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 CancelRotateSecret where
  hashWithSalt :: Int -> CancelRotateSecret -> Int
hashWithSalt Int
_salt CancelRotateSecret' {Text
secretId :: Text
$sel:secretId:CancelRotateSecret' :: CancelRotateSecret -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
secretId

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

instance Data.ToHeaders CancelRotateSecret where
  toHeaders :: CancelRotateSecret -> 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.CancelRotateSecret" ::
                          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 CancelRotateSecret where
  toJSON :: CancelRotateSecret -> Value
toJSON CancelRotateSecret' {Text
secretId :: Text
$sel:secretId:CancelRotateSecret' :: CancelRotateSecret -> 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 CancelRotateSecret where
  toPath :: CancelRotateSecret -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newCancelRotateSecretResponse' smart constructor.
data CancelRotateSecretResponse = CancelRotateSecretResponse'
  { -- | The ARN of the secret.
    CancelRotateSecretResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The name of the secret.
    CancelRotateSecretResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier of the version of the secret created during the
    -- rotation. This version might not be complete, and should be evaluated
    -- for possible deletion. We recommend that you remove the @VersionStage@
    -- value @AWSPENDING@ from this version so that Secrets Manager can delete
    -- it. Failing to clean up a cancelled rotation can block you from starting
    -- future rotations.
    CancelRotateSecretResponse -> Maybe Text
versionId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CancelRotateSecretResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CancelRotateSecretResponse -> CancelRotateSecretResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelRotateSecretResponse -> CancelRotateSecretResponse -> Bool
$c/= :: CancelRotateSecretResponse -> CancelRotateSecretResponse -> Bool
== :: CancelRotateSecretResponse -> CancelRotateSecretResponse -> Bool
$c== :: CancelRotateSecretResponse -> CancelRotateSecretResponse -> Bool
Prelude.Eq, ReadPrec [CancelRotateSecretResponse]
ReadPrec CancelRotateSecretResponse
Int -> ReadS CancelRotateSecretResponse
ReadS [CancelRotateSecretResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CancelRotateSecretResponse]
$creadListPrec :: ReadPrec [CancelRotateSecretResponse]
readPrec :: ReadPrec CancelRotateSecretResponse
$creadPrec :: ReadPrec CancelRotateSecretResponse
readList :: ReadS [CancelRotateSecretResponse]
$creadList :: ReadS [CancelRotateSecretResponse]
readsPrec :: Int -> ReadS CancelRotateSecretResponse
$creadsPrec :: Int -> ReadS CancelRotateSecretResponse
Prelude.Read, Int -> CancelRotateSecretResponse -> ShowS
[CancelRotateSecretResponse] -> ShowS
CancelRotateSecretResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelRotateSecretResponse] -> ShowS
$cshowList :: [CancelRotateSecretResponse] -> ShowS
show :: CancelRotateSecretResponse -> String
$cshow :: CancelRotateSecretResponse -> String
showsPrec :: Int -> CancelRotateSecretResponse -> ShowS
$cshowsPrec :: Int -> CancelRotateSecretResponse -> ShowS
Prelude.Show, forall x.
Rep CancelRotateSecretResponse x -> CancelRotateSecretResponse
forall x.
CancelRotateSecretResponse -> Rep CancelRotateSecretResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CancelRotateSecretResponse x -> CancelRotateSecretResponse
$cfrom :: forall x.
CancelRotateSecretResponse -> Rep CancelRotateSecretResponse x
Prelude.Generic)

-- |
-- Create a value of 'CancelRotateSecretResponse' 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', 'cancelRotateSecretResponse_arn' - The ARN of the secret.
--
-- 'name', 'cancelRotateSecretResponse_name' - The name of the secret.
--
-- 'versionId', 'cancelRotateSecretResponse_versionId' - The unique identifier of the version of the secret created during the
-- rotation. This version might not be complete, and should be evaluated
-- for possible deletion. We recommend that you remove the @VersionStage@
-- value @AWSPENDING@ from this version so that Secrets Manager can delete
-- it. Failing to clean up a cancelled rotation can block you from starting
-- future rotations.
--
-- 'httpStatus', 'cancelRotateSecretResponse_httpStatus' - The response's http status code.
newCancelRotateSecretResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CancelRotateSecretResponse
newCancelRotateSecretResponse :: Int -> CancelRotateSecretResponse
newCancelRotateSecretResponse Int
pHttpStatus_ =
  CancelRotateSecretResponse'
    { $sel:arn:CancelRotateSecretResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CancelRotateSecretResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:versionId:CancelRotateSecretResponse' :: Maybe Text
versionId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CancelRotateSecretResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | The name of the secret.
cancelRotateSecretResponse_name :: Lens.Lens' CancelRotateSecretResponse (Prelude.Maybe Prelude.Text)
cancelRotateSecretResponse_name :: Lens' CancelRotateSecretResponse (Maybe Text)
cancelRotateSecretResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelRotateSecretResponse' {Maybe Text
name :: Maybe Text
$sel:name:CancelRotateSecretResponse' :: CancelRotateSecretResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: CancelRotateSecretResponse
s@CancelRotateSecretResponse' {} Maybe Text
a -> CancelRotateSecretResponse
s {$sel:name:CancelRotateSecretResponse' :: Maybe Text
name = Maybe Text
a} :: CancelRotateSecretResponse)

-- | The unique identifier of the version of the secret created during the
-- rotation. This version might not be complete, and should be evaluated
-- for possible deletion. We recommend that you remove the @VersionStage@
-- value @AWSPENDING@ from this version so that Secrets Manager can delete
-- it. Failing to clean up a cancelled rotation can block you from starting
-- future rotations.
cancelRotateSecretResponse_versionId :: Lens.Lens' CancelRotateSecretResponse (Prelude.Maybe Prelude.Text)
cancelRotateSecretResponse_versionId :: Lens' CancelRotateSecretResponse (Maybe Text)
cancelRotateSecretResponse_versionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelRotateSecretResponse' {Maybe Text
versionId :: Maybe Text
$sel:versionId:CancelRotateSecretResponse' :: CancelRotateSecretResponse -> Maybe Text
versionId} -> Maybe Text
versionId) (\s :: CancelRotateSecretResponse
s@CancelRotateSecretResponse' {} Maybe Text
a -> CancelRotateSecretResponse
s {$sel:versionId:CancelRotateSecretResponse' :: Maybe Text
versionId = Maybe Text
a} :: CancelRotateSecretResponse)

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

instance Prelude.NFData CancelRotateSecretResponse where
  rnf :: CancelRotateSecretResponse -> ()
rnf CancelRotateSecretResponse' {Int
Maybe Text
httpStatus :: Int
versionId :: Maybe Text
name :: Maybe Text
arn :: Maybe Text
$sel:httpStatus:CancelRotateSecretResponse' :: CancelRotateSecretResponse -> Int
$sel:versionId:CancelRotateSecretResponse' :: CancelRotateSecretResponse -> Maybe Text
$sel:name:CancelRotateSecretResponse' :: CancelRotateSecretResponse -> Maybe Text
$sel:arn:CancelRotateSecretResponse' :: CancelRotateSecretResponse -> 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 Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
versionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus