{-# 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.Signer.CancelSigningProfile
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Changes the state of an @ACTIVE@ signing profile to @CANCELED@. A
-- canceled profile is still viewable with the @ListSigningProfiles@
-- operation, but it cannot perform new signing jobs, and is deleted two
-- years after cancelation.
module Amazonka.Signer.CancelSigningProfile
  ( -- * Creating a Request
    CancelSigningProfile (..),
    newCancelSigningProfile,

    -- * Request Lenses
    cancelSigningProfile_profileName,

    -- * Destructuring the Response
    CancelSigningProfileResponse (..),
    newCancelSigningProfileResponse,
  )
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.Signer.Types

-- | /See:/ 'newCancelSigningProfile' smart constructor.
data CancelSigningProfile = CancelSigningProfile'
  { -- | The name of the signing profile to be canceled.
    CancelSigningProfile -> Text
profileName :: Prelude.Text
  }
  deriving (CancelSigningProfile -> CancelSigningProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelSigningProfile -> CancelSigningProfile -> Bool
$c/= :: CancelSigningProfile -> CancelSigningProfile -> Bool
== :: CancelSigningProfile -> CancelSigningProfile -> Bool
$c== :: CancelSigningProfile -> CancelSigningProfile -> Bool
Prelude.Eq, ReadPrec [CancelSigningProfile]
ReadPrec CancelSigningProfile
Int -> ReadS CancelSigningProfile
ReadS [CancelSigningProfile]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CancelSigningProfile]
$creadListPrec :: ReadPrec [CancelSigningProfile]
readPrec :: ReadPrec CancelSigningProfile
$creadPrec :: ReadPrec CancelSigningProfile
readList :: ReadS [CancelSigningProfile]
$creadList :: ReadS [CancelSigningProfile]
readsPrec :: Int -> ReadS CancelSigningProfile
$creadsPrec :: Int -> ReadS CancelSigningProfile
Prelude.Read, Int -> CancelSigningProfile -> ShowS
[CancelSigningProfile] -> ShowS
CancelSigningProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelSigningProfile] -> ShowS
$cshowList :: [CancelSigningProfile] -> ShowS
show :: CancelSigningProfile -> String
$cshow :: CancelSigningProfile -> String
showsPrec :: Int -> CancelSigningProfile -> ShowS
$cshowsPrec :: Int -> CancelSigningProfile -> ShowS
Prelude.Show, forall x. Rep CancelSigningProfile x -> CancelSigningProfile
forall x. CancelSigningProfile -> Rep CancelSigningProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CancelSigningProfile x -> CancelSigningProfile
$cfrom :: forall x. CancelSigningProfile -> Rep CancelSigningProfile x
Prelude.Generic)

-- |
-- Create a value of 'CancelSigningProfile' 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:
--
-- 'profileName', 'cancelSigningProfile_profileName' - The name of the signing profile to be canceled.
newCancelSigningProfile ::
  -- | 'profileName'
  Prelude.Text ->
  CancelSigningProfile
newCancelSigningProfile :: Text -> CancelSigningProfile
newCancelSigningProfile Text
pProfileName_ =
  CancelSigningProfile' {$sel:profileName:CancelSigningProfile' :: Text
profileName = Text
pProfileName_}

-- | The name of the signing profile to be canceled.
cancelSigningProfile_profileName :: Lens.Lens' CancelSigningProfile Prelude.Text
cancelSigningProfile_profileName :: Lens' CancelSigningProfile Text
cancelSigningProfile_profileName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelSigningProfile' {Text
profileName :: Text
$sel:profileName:CancelSigningProfile' :: CancelSigningProfile -> Text
profileName} -> Text
profileName) (\s :: CancelSigningProfile
s@CancelSigningProfile' {} Text
a -> CancelSigningProfile
s {$sel:profileName:CancelSigningProfile' :: Text
profileName = Text
a} :: CancelSigningProfile)

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

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

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

instance Data.ToHeaders CancelSigningProfile where
  toHeaders :: CancelSigningProfile -> [Header]
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath CancelSigningProfile where
  toPath :: CancelSigningProfile -> ByteString
toPath CancelSigningProfile' {Text
profileName :: Text
$sel:profileName:CancelSigningProfile' :: CancelSigningProfile -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/signing-profiles/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
profileName]

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

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

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

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