{-# 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.DeleteContactFlow
-- 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 flow for the specified Amazon Connect instance.
module Amazonka.Connect.DeleteContactFlow
  ( -- * Creating a Request
    DeleteContactFlow (..),
    newDeleteContactFlow,

    -- * Request Lenses
    deleteContactFlow_instanceId,
    deleteContactFlow_contactFlowId,

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

-- |
-- Create a value of 'DeleteContactFlow' 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', 'deleteContactFlow_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
--
-- 'contactFlowId', 'deleteContactFlow_contactFlowId' - The identifier of the flow.
newDeleteContactFlow ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'contactFlowId'
  Prelude.Text ->
  DeleteContactFlow
newDeleteContactFlow :: Text -> Text -> DeleteContactFlow
newDeleteContactFlow Text
pInstanceId_ Text
pContactFlowId_ =
  DeleteContactFlow'
    { $sel:instanceId:DeleteContactFlow' :: Text
instanceId = Text
pInstanceId_,
      $sel:contactFlowId:DeleteContactFlow' :: Text
contactFlowId = Text
pContactFlowId_
    }

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

-- | The identifier of the flow.
deleteContactFlow_contactFlowId :: Lens.Lens' DeleteContactFlow Prelude.Text
deleteContactFlow_contactFlowId :: Lens' DeleteContactFlow Text
deleteContactFlow_contactFlowId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteContactFlow' {Text
contactFlowId :: Text
$sel:contactFlowId:DeleteContactFlow' :: DeleteContactFlow -> Text
contactFlowId} -> Text
contactFlowId) (\s :: DeleteContactFlow
s@DeleteContactFlow' {} Text
a -> DeleteContactFlow
s {$sel:contactFlowId:DeleteContactFlow' :: Text
contactFlowId = Text
a} :: DeleteContactFlow)

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

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

instance Prelude.NFData DeleteContactFlow where
  rnf :: DeleteContactFlow -> ()
rnf DeleteContactFlow' {Text
contactFlowId :: Text
instanceId :: Text
$sel:contactFlowId:DeleteContactFlow' :: DeleteContactFlow -> Text
$sel:instanceId:DeleteContactFlow' :: DeleteContactFlow -> 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
contactFlowId

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

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

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

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

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