{-# 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.IoT.CancelCertificateTransfer
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Cancels a pending transfer for the specified certificate.
--
-- __Note__ Only the transfer source account can use this operation to
-- cancel a transfer. (Transfer destinations can use
-- RejectCertificateTransfer instead.) After transfer, IoT returns the
-- certificate to the source account in the INACTIVE state. After the
-- destination account has accepted the transfer, the transfer cannot be
-- cancelled.
--
-- After a certificate transfer is cancelled, the status of the certificate
-- changes from PENDING_TRANSFER to INACTIVE.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions CancelCertificateTransfer>
-- action.
module Amazonka.IoT.CancelCertificateTransfer
  ( -- * Creating a Request
    CancelCertificateTransfer (..),
    newCancelCertificateTransfer,

    -- * Request Lenses
    cancelCertificateTransfer_certificateId,

    -- * Destructuring the Response
    CancelCertificateTransferResponse (..),
    newCancelCertificateTransferResponse,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IoT.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | The input for the CancelCertificateTransfer operation.
--
-- /See:/ 'newCancelCertificateTransfer' smart constructor.
data CancelCertificateTransfer = CancelCertificateTransfer'
  { -- | The ID of the certificate. (The last part of the certificate ARN
    -- contains the certificate ID.)
    CancelCertificateTransfer -> Text
certificateId :: Prelude.Text
  }
  deriving (CancelCertificateTransfer -> CancelCertificateTransfer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelCertificateTransfer -> CancelCertificateTransfer -> Bool
$c/= :: CancelCertificateTransfer -> CancelCertificateTransfer -> Bool
== :: CancelCertificateTransfer -> CancelCertificateTransfer -> Bool
$c== :: CancelCertificateTransfer -> CancelCertificateTransfer -> Bool
Prelude.Eq, ReadPrec [CancelCertificateTransfer]
ReadPrec CancelCertificateTransfer
Int -> ReadS CancelCertificateTransfer
ReadS [CancelCertificateTransfer]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CancelCertificateTransfer]
$creadListPrec :: ReadPrec [CancelCertificateTransfer]
readPrec :: ReadPrec CancelCertificateTransfer
$creadPrec :: ReadPrec CancelCertificateTransfer
readList :: ReadS [CancelCertificateTransfer]
$creadList :: ReadS [CancelCertificateTransfer]
readsPrec :: Int -> ReadS CancelCertificateTransfer
$creadsPrec :: Int -> ReadS CancelCertificateTransfer
Prelude.Read, Int -> CancelCertificateTransfer -> ShowS
[CancelCertificateTransfer] -> ShowS
CancelCertificateTransfer -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelCertificateTransfer] -> ShowS
$cshowList :: [CancelCertificateTransfer] -> ShowS
show :: CancelCertificateTransfer -> String
$cshow :: CancelCertificateTransfer -> String
showsPrec :: Int -> CancelCertificateTransfer -> ShowS
$cshowsPrec :: Int -> CancelCertificateTransfer -> ShowS
Prelude.Show, forall x.
Rep CancelCertificateTransfer x -> CancelCertificateTransfer
forall x.
CancelCertificateTransfer -> Rep CancelCertificateTransfer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CancelCertificateTransfer x -> CancelCertificateTransfer
$cfrom :: forall x.
CancelCertificateTransfer -> Rep CancelCertificateTransfer x
Prelude.Generic)

-- |
-- Create a value of 'CancelCertificateTransfer' 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:
--
-- 'certificateId', 'cancelCertificateTransfer_certificateId' - The ID of the certificate. (The last part of the certificate ARN
-- contains the certificate ID.)
newCancelCertificateTransfer ::
  -- | 'certificateId'
  Prelude.Text ->
  CancelCertificateTransfer
newCancelCertificateTransfer :: Text -> CancelCertificateTransfer
newCancelCertificateTransfer Text
pCertificateId_ =
  CancelCertificateTransfer'
    { $sel:certificateId:CancelCertificateTransfer' :: Text
certificateId =
        Text
pCertificateId_
    }

-- | The ID of the certificate. (The last part of the certificate ARN
-- contains the certificate ID.)
cancelCertificateTransfer_certificateId :: Lens.Lens' CancelCertificateTransfer Prelude.Text
cancelCertificateTransfer_certificateId :: Lens' CancelCertificateTransfer Text
cancelCertificateTransfer_certificateId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelCertificateTransfer' {Text
certificateId :: Text
$sel:certificateId:CancelCertificateTransfer' :: CancelCertificateTransfer -> Text
certificateId} -> Text
certificateId) (\s :: CancelCertificateTransfer
s@CancelCertificateTransfer' {} Text
a -> CancelCertificateTransfer
s {$sel:certificateId:CancelCertificateTransfer' :: Text
certificateId = Text
a} :: CancelCertificateTransfer)

instance Core.AWSRequest CancelCertificateTransfer where
  type
    AWSResponse CancelCertificateTransfer =
      CancelCertificateTransferResponse
  request :: (Service -> Service)
-> CancelCertificateTransfer -> Request CancelCertificateTransfer
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.patchJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CancelCertificateTransfer
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CancelCertificateTransfer)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      CancelCertificateTransferResponse
CancelCertificateTransferResponse'

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

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

instance Data.ToHeaders CancelCertificateTransfer where
  toHeaders :: CancelCertificateTransfer -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON CancelCertificateTransfer where
  toJSON :: CancelCertificateTransfer -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

instance Data.ToPath CancelCertificateTransfer where
  toPath :: CancelCertificateTransfer -> ByteString
toPath CancelCertificateTransfer' {Text
certificateId :: Text
$sel:certificateId:CancelCertificateTransfer' :: CancelCertificateTransfer -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/cancel-certificate-transfer/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
certificateId
      ]

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

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

-- |
-- Create a value of 'CancelCertificateTransferResponse' 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.
newCancelCertificateTransferResponse ::
  CancelCertificateTransferResponse
newCancelCertificateTransferResponse :: CancelCertificateTransferResponse
newCancelCertificateTransferResponse =
  CancelCertificateTransferResponse
CancelCertificateTransferResponse'

instance
  Prelude.NFData
    CancelCertificateTransferResponse
  where
  rnf :: CancelCertificateTransferResponse -> ()
rnf CancelCertificateTransferResponse
_ = ()