{-# 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.DeleteUseCase
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes a use case from an integration association.
module Amazonka.Connect.DeleteUseCase
  ( -- * Creating a Request
    DeleteUseCase (..),
    newDeleteUseCase,

    -- * Request Lenses
    deleteUseCase_instanceId,
    deleteUseCase_integrationAssociationId,
    deleteUseCase_useCaseId,

    -- * Destructuring the Response
    DeleteUseCaseResponse (..),
    newDeleteUseCaseResponse,
  )
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:/ 'newDeleteUseCase' smart constructor.
data DeleteUseCase = DeleteUseCase'
  { -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    DeleteUseCase -> Text
instanceId :: Prelude.Text,
    -- | The identifier for the integration association.
    DeleteUseCase -> Text
integrationAssociationId :: Prelude.Text,
    -- | The identifier for the use case.
    DeleteUseCase -> Text
useCaseId :: Prelude.Text
  }
  deriving (DeleteUseCase -> DeleteUseCase -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteUseCase -> DeleteUseCase -> Bool
$c/= :: DeleteUseCase -> DeleteUseCase -> Bool
== :: DeleteUseCase -> DeleteUseCase -> Bool
$c== :: DeleteUseCase -> DeleteUseCase -> Bool
Prelude.Eq, ReadPrec [DeleteUseCase]
ReadPrec DeleteUseCase
Int -> ReadS DeleteUseCase
ReadS [DeleteUseCase]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteUseCase]
$creadListPrec :: ReadPrec [DeleteUseCase]
readPrec :: ReadPrec DeleteUseCase
$creadPrec :: ReadPrec DeleteUseCase
readList :: ReadS [DeleteUseCase]
$creadList :: ReadS [DeleteUseCase]
readsPrec :: Int -> ReadS DeleteUseCase
$creadsPrec :: Int -> ReadS DeleteUseCase
Prelude.Read, Int -> DeleteUseCase -> ShowS
[DeleteUseCase] -> ShowS
DeleteUseCase -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteUseCase] -> ShowS
$cshowList :: [DeleteUseCase] -> ShowS
show :: DeleteUseCase -> String
$cshow :: DeleteUseCase -> String
showsPrec :: Int -> DeleteUseCase -> ShowS
$cshowsPrec :: Int -> DeleteUseCase -> ShowS
Prelude.Show, forall x. Rep DeleteUseCase x -> DeleteUseCase
forall x. DeleteUseCase -> Rep DeleteUseCase x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteUseCase x -> DeleteUseCase
$cfrom :: forall x. DeleteUseCase -> Rep DeleteUseCase x
Prelude.Generic)

-- |
-- Create a value of 'DeleteUseCase' 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', 'deleteUseCase_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
--
-- 'integrationAssociationId', 'deleteUseCase_integrationAssociationId' - The identifier for the integration association.
--
-- 'useCaseId', 'deleteUseCase_useCaseId' - The identifier for the use case.
newDeleteUseCase ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'integrationAssociationId'
  Prelude.Text ->
  -- | 'useCaseId'
  Prelude.Text ->
  DeleteUseCase
newDeleteUseCase :: Text -> Text -> Text -> DeleteUseCase
newDeleteUseCase
  Text
pInstanceId_
  Text
pIntegrationAssociationId_
  Text
pUseCaseId_ =
    DeleteUseCase'
      { $sel:instanceId:DeleteUseCase' :: Text
instanceId = Text
pInstanceId_,
        $sel:integrationAssociationId:DeleteUseCase' :: Text
integrationAssociationId =
          Text
pIntegrationAssociationId_,
        $sel:useCaseId:DeleteUseCase' :: Text
useCaseId = Text
pUseCaseId_
      }

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

-- | The identifier for the integration association.
deleteUseCase_integrationAssociationId :: Lens.Lens' DeleteUseCase Prelude.Text
deleteUseCase_integrationAssociationId :: Lens' DeleteUseCase Text
deleteUseCase_integrationAssociationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteUseCase' {Text
integrationAssociationId :: Text
$sel:integrationAssociationId:DeleteUseCase' :: DeleteUseCase -> Text
integrationAssociationId} -> Text
integrationAssociationId) (\s :: DeleteUseCase
s@DeleteUseCase' {} Text
a -> DeleteUseCase
s {$sel:integrationAssociationId:DeleteUseCase' :: Text
integrationAssociationId = Text
a} :: DeleteUseCase)

-- | The identifier for the use case.
deleteUseCase_useCaseId :: Lens.Lens' DeleteUseCase Prelude.Text
deleteUseCase_useCaseId :: Lens' DeleteUseCase Text
deleteUseCase_useCaseId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteUseCase' {Text
useCaseId :: Text
$sel:useCaseId:DeleteUseCase' :: DeleteUseCase -> Text
useCaseId} -> Text
useCaseId) (\s :: DeleteUseCase
s@DeleteUseCase' {} Text
a -> DeleteUseCase
s {$sel:useCaseId:DeleteUseCase' :: Text
useCaseId = Text
a} :: DeleteUseCase)

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

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

instance Prelude.NFData DeleteUseCase where
  rnf :: DeleteUseCase -> ()
rnf DeleteUseCase' {Text
useCaseId :: Text
integrationAssociationId :: Text
instanceId :: Text
$sel:useCaseId:DeleteUseCase' :: DeleteUseCase -> Text
$sel:integrationAssociationId:DeleteUseCase' :: DeleteUseCase -> Text
$sel:instanceId:DeleteUseCase' :: DeleteUseCase -> 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
integrationAssociationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
useCaseId

instance Data.ToHeaders DeleteUseCase where
  toHeaders :: DeleteUseCase -> [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 DeleteUseCase where
  toPath :: DeleteUseCase -> ByteString
toPath DeleteUseCase' {Text
useCaseId :: Text
integrationAssociationId :: Text
instanceId :: Text
$sel:useCaseId:DeleteUseCase' :: DeleteUseCase -> Text
$sel:integrationAssociationId:DeleteUseCase' :: DeleteUseCase -> Text
$sel:instanceId:DeleteUseCase' :: DeleteUseCase -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/instance/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId,
        ByteString
"/integration-associations/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
integrationAssociationId,
        ByteString
"/use-cases/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
useCaseId
      ]

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

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

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

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