{-# 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.UpdateContactFlowName
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- The name of the flow.
--
-- You can also create and update flows using the
-- <https://docs.aws.amazon.com/connect/latest/APIReference/flow-language.html Amazon Connect Flow language>.
module Amazonka.Connect.UpdateContactFlowName
  ( -- * Creating a Request
    UpdateContactFlowName (..),
    newUpdateContactFlowName,

    -- * Request Lenses
    updateContactFlowName_description,
    updateContactFlowName_name,
    updateContactFlowName_instanceId,
    updateContactFlowName_contactFlowId,

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

-- |
-- Create a value of 'UpdateContactFlowName' 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:
--
-- 'description', 'updateContactFlowName_description' - The description of the flow.
--
-- 'name', 'updateContactFlowName_name' - The name of the flow.
--
-- 'instanceId', 'updateContactFlowName_instanceId' - The identifier of the Amazon Connect instance.
--
-- 'contactFlowId', 'updateContactFlowName_contactFlowId' - The identifier of the flow.
newUpdateContactFlowName ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'contactFlowId'
  Prelude.Text ->
  UpdateContactFlowName
newUpdateContactFlowName :: Text -> Text -> UpdateContactFlowName
newUpdateContactFlowName Text
pInstanceId_ Text
pContactFlowId_ =
  UpdateContactFlowName'
    { $sel:description:UpdateContactFlowName' :: Maybe Text
description =
        forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateContactFlowName' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:UpdateContactFlowName' :: Text
instanceId = Text
pInstanceId_,
      $sel:contactFlowId:UpdateContactFlowName' :: Text
contactFlowId = Text
pContactFlowId_
    }

-- | The description of the flow.
updateContactFlowName_description :: Lens.Lens' UpdateContactFlowName (Prelude.Maybe Prelude.Text)
updateContactFlowName_description :: Lens' UpdateContactFlowName (Maybe Text)
updateContactFlowName_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateContactFlowName' {Maybe Text
description :: Maybe Text
$sel:description:UpdateContactFlowName' :: UpdateContactFlowName -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateContactFlowName
s@UpdateContactFlowName' {} Maybe Text
a -> UpdateContactFlowName
s {$sel:description:UpdateContactFlowName' :: Maybe Text
description = Maybe Text
a} :: UpdateContactFlowName)

-- | The name of the flow.
updateContactFlowName_name :: Lens.Lens' UpdateContactFlowName (Prelude.Maybe Prelude.Text)
updateContactFlowName_name :: Lens' UpdateContactFlowName (Maybe Text)
updateContactFlowName_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateContactFlowName' {Maybe Text
name :: Maybe Text
$sel:name:UpdateContactFlowName' :: UpdateContactFlowName -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateContactFlowName
s@UpdateContactFlowName' {} Maybe Text
a -> UpdateContactFlowName
s {$sel:name:UpdateContactFlowName' :: Maybe Text
name = Maybe Text
a} :: UpdateContactFlowName)

-- | The identifier of the Amazon Connect instance.
updateContactFlowName_instanceId :: Lens.Lens' UpdateContactFlowName Prelude.Text
updateContactFlowName_instanceId :: Lens' UpdateContactFlowName Text
updateContactFlowName_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateContactFlowName' {Text
instanceId :: Text
$sel:instanceId:UpdateContactFlowName' :: UpdateContactFlowName -> Text
instanceId} -> Text
instanceId) (\s :: UpdateContactFlowName
s@UpdateContactFlowName' {} Text
a -> UpdateContactFlowName
s {$sel:instanceId:UpdateContactFlowName' :: Text
instanceId = Text
a} :: UpdateContactFlowName)

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

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

instance Prelude.Hashable UpdateContactFlowName where
  hashWithSalt :: Int -> UpdateContactFlowName -> Int
hashWithSalt Int
_salt UpdateContactFlowName' {Maybe Text
Text
contactFlowId :: Text
instanceId :: Text
name :: Maybe Text
description :: Maybe Text
$sel:contactFlowId:UpdateContactFlowName' :: UpdateContactFlowName -> Text
$sel:instanceId:UpdateContactFlowName' :: UpdateContactFlowName -> Text
$sel:name:UpdateContactFlowName' :: UpdateContactFlowName -> Maybe Text
$sel:description:UpdateContactFlowName' :: UpdateContactFlowName -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      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 UpdateContactFlowName where
  rnf :: UpdateContactFlowName -> ()
rnf UpdateContactFlowName' {Maybe Text
Text
contactFlowId :: Text
instanceId :: Text
name :: Maybe Text
description :: Maybe Text
$sel:contactFlowId:UpdateContactFlowName' :: UpdateContactFlowName -> Text
$sel:instanceId:UpdateContactFlowName' :: UpdateContactFlowName -> Text
$sel:name:UpdateContactFlowName' :: UpdateContactFlowName -> Maybe Text
$sel:description:UpdateContactFlowName' :: UpdateContactFlowName -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 UpdateContactFlowName where
  toHeaders :: UpdateContactFlowName -> [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.ToJSON UpdateContactFlowName where
  toJSON :: UpdateContactFlowName -> Value
toJSON UpdateContactFlowName' {Maybe Text
Text
contactFlowId :: Text
instanceId :: Text
name :: Maybe Text
description :: Maybe Text
$sel:contactFlowId:UpdateContactFlowName' :: UpdateContactFlowName -> Text
$sel:instanceId:UpdateContactFlowName' :: UpdateContactFlowName -> Text
$sel:name:UpdateContactFlowName' :: UpdateContactFlowName -> Maybe Text
$sel:description:UpdateContactFlowName' :: UpdateContactFlowName -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
description,
            (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
name
          ]
      )

instance Data.ToPath UpdateContactFlowName where
  toPath :: UpdateContactFlowName -> ByteString
toPath UpdateContactFlowName' {Maybe Text
Text
contactFlowId :: Text
instanceId :: Text
name :: Maybe Text
description :: Maybe Text
$sel:contactFlowId:UpdateContactFlowName' :: UpdateContactFlowName -> Text
$sel:instanceId:UpdateContactFlowName' :: UpdateContactFlowName -> Text
$sel:name:UpdateContactFlowName' :: UpdateContactFlowName -> Maybe Text
$sel:description:UpdateContactFlowName' :: UpdateContactFlowName -> Maybe 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,
        ByteString
"/name"
      ]

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

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

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

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