{-# 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.Connect.DisassociateSecurityKey
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This API is in preview release for Amazon Connect and is subject to
-- change.
--
-- Deletes the specified security key.
module Amazonka.Connect.DisassociateSecurityKey
  ( -- * Creating a Request
    DisassociateSecurityKey (..),
    newDisassociateSecurityKey,

    -- * Request Lenses
    disassociateSecurityKey_instanceId,
    disassociateSecurityKey_associationId,

    -- * Destructuring the Response
    DisassociateSecurityKeyResponse (..),
    newDisassociateSecurityKeyResponse,
  )
where

import Amazonka.Connect.Types
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

-- | /See:/ 'newDisassociateSecurityKey' smart constructor.
data DisassociateSecurityKey = DisassociateSecurityKey'
  { -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    DisassociateSecurityKey -> Text
instanceId :: Prelude.Text,
    -- | The existing association identifier that uniquely identifies the
    -- resource type and storage config for the given instance ID.
    DisassociateSecurityKey -> Text
associationId :: Prelude.Text
  }
  deriving (DisassociateSecurityKey -> DisassociateSecurityKey -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateSecurityKey -> DisassociateSecurityKey -> Bool
$c/= :: DisassociateSecurityKey -> DisassociateSecurityKey -> Bool
== :: DisassociateSecurityKey -> DisassociateSecurityKey -> Bool
$c== :: DisassociateSecurityKey -> DisassociateSecurityKey -> Bool
Prelude.Eq, ReadPrec [DisassociateSecurityKey]
ReadPrec DisassociateSecurityKey
Int -> ReadS DisassociateSecurityKey
ReadS [DisassociateSecurityKey]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateSecurityKey]
$creadListPrec :: ReadPrec [DisassociateSecurityKey]
readPrec :: ReadPrec DisassociateSecurityKey
$creadPrec :: ReadPrec DisassociateSecurityKey
readList :: ReadS [DisassociateSecurityKey]
$creadList :: ReadS [DisassociateSecurityKey]
readsPrec :: Int -> ReadS DisassociateSecurityKey
$creadsPrec :: Int -> ReadS DisassociateSecurityKey
Prelude.Read, Int -> DisassociateSecurityKey -> ShowS
[DisassociateSecurityKey] -> ShowS
DisassociateSecurityKey -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateSecurityKey] -> ShowS
$cshowList :: [DisassociateSecurityKey] -> ShowS
show :: DisassociateSecurityKey -> String
$cshow :: DisassociateSecurityKey -> String
showsPrec :: Int -> DisassociateSecurityKey -> ShowS
$cshowsPrec :: Int -> DisassociateSecurityKey -> ShowS
Prelude.Show, forall x. Rep DisassociateSecurityKey x -> DisassociateSecurityKey
forall x. DisassociateSecurityKey -> Rep DisassociateSecurityKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DisassociateSecurityKey x -> DisassociateSecurityKey
$cfrom :: forall x. DisassociateSecurityKey -> Rep DisassociateSecurityKey x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateSecurityKey' 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:
--
-- 'instanceId', 'disassociateSecurityKey_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
--
-- 'associationId', 'disassociateSecurityKey_associationId' - The existing association identifier that uniquely identifies the
-- resource type and storage config for the given instance ID.
newDisassociateSecurityKey ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'associationId'
  Prelude.Text ->
  DisassociateSecurityKey
newDisassociateSecurityKey :: Text -> Text -> DisassociateSecurityKey
newDisassociateSecurityKey
  Text
pInstanceId_
  Text
pAssociationId_ =
    DisassociateSecurityKey'
      { $sel:instanceId:DisassociateSecurityKey' :: Text
instanceId = Text
pInstanceId_,
        $sel:associationId:DisassociateSecurityKey' :: Text
associationId = Text
pAssociationId_
      }

-- | The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
disassociateSecurityKey_instanceId :: Lens.Lens' DisassociateSecurityKey Prelude.Text
disassociateSecurityKey_instanceId :: Lens' DisassociateSecurityKey Text
disassociateSecurityKey_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateSecurityKey' {Text
instanceId :: Text
$sel:instanceId:DisassociateSecurityKey' :: DisassociateSecurityKey -> Text
instanceId} -> Text
instanceId) (\s :: DisassociateSecurityKey
s@DisassociateSecurityKey' {} Text
a -> DisassociateSecurityKey
s {$sel:instanceId:DisassociateSecurityKey' :: Text
instanceId = Text
a} :: DisassociateSecurityKey)

-- | The existing association identifier that uniquely identifies the
-- resource type and storage config for the given instance ID.
disassociateSecurityKey_associationId :: Lens.Lens' DisassociateSecurityKey Prelude.Text
disassociateSecurityKey_associationId :: Lens' DisassociateSecurityKey Text
disassociateSecurityKey_associationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateSecurityKey' {Text
associationId :: Text
$sel:associationId:DisassociateSecurityKey' :: DisassociateSecurityKey -> Text
associationId} -> Text
associationId) (\s :: DisassociateSecurityKey
s@DisassociateSecurityKey' {} Text
a -> DisassociateSecurityKey
s {$sel:associationId:DisassociateSecurityKey' :: Text
associationId = Text
a} :: DisassociateSecurityKey)

instance Core.AWSRequest DisassociateSecurityKey where
  type
    AWSResponse DisassociateSecurityKey =
      DisassociateSecurityKeyResponse
  request :: (Service -> Service)
-> DisassociateSecurityKey -> Request DisassociateSecurityKey
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 DisassociateSecurityKey
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DisassociateSecurityKey)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      DisassociateSecurityKeyResponse
DisassociateSecurityKeyResponse'

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

instance Prelude.NFData DisassociateSecurityKey where
  rnf :: DisassociateSecurityKey -> ()
rnf DisassociateSecurityKey' {Text
associationId :: Text
instanceId :: Text
$sel:associationId:DisassociateSecurityKey' :: DisassociateSecurityKey -> Text
$sel:instanceId:DisassociateSecurityKey' :: DisassociateSecurityKey -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
associationId

instance Data.ToHeaders DisassociateSecurityKey where
  toHeaders :: DisassociateSecurityKey -> [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 DisassociateSecurityKey where
  toPath :: DisassociateSecurityKey -> ByteString
toPath DisassociateSecurityKey' {Text
associationId :: Text
instanceId :: Text
$sel:associationId:DisassociateSecurityKey' :: DisassociateSecurityKey -> Text
$sel:instanceId:DisassociateSecurityKey' :: DisassociateSecurityKey -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/instance/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId,
        ByteString
"/security-key/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
associationId
      ]

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

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

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

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