{-# 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.CreateContactFlow
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a flow for the specified Amazon Connect instance.
--
-- 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.CreateContactFlow
  ( -- * Creating a Request
    CreateContactFlow (..),
    newCreateContactFlow,

    -- * Request Lenses
    createContactFlow_description,
    createContactFlow_tags,
    createContactFlow_instanceId,
    createContactFlow_name,
    createContactFlow_type,
    createContactFlow_content,

    -- * Destructuring the Response
    CreateContactFlowResponse (..),
    newCreateContactFlowResponse,

    -- * Response Lenses
    createContactFlowResponse_contactFlowArn,
    createContactFlowResponse_contactFlowId,
    createContactFlowResponse_httpStatus,
  )
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:/ 'newCreateContactFlow' smart constructor.
data CreateContactFlow = CreateContactFlow'
  { -- | The description of the flow.
    CreateContactFlow -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The tags used to organize, track, or control access for this resource.
    -- For example, { \"tags\": {\"key1\":\"value1\", \"key2\":\"value2\"} }.
    CreateContactFlow -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The identifier of the Amazon Connect instance.
    CreateContactFlow -> Text
instanceId :: Prelude.Text,
    -- | The name of the flow.
    CreateContactFlow -> Text
name :: Prelude.Text,
    -- | The type of the flow. For descriptions of the available types, see
    -- <https://docs.aws.amazon.com/connect/latest/adminguide/create-contact-flow.html#contact-flow-types Choose a flow type>
    -- in the /Amazon Connect Administrator Guide/.
    CreateContactFlow -> ContactFlowType
type' :: ContactFlowType,
    -- | The content of the flow.
    CreateContactFlow -> Text
content :: Prelude.Text
  }
  deriving (CreateContactFlow -> CreateContactFlow -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateContactFlow -> CreateContactFlow -> Bool
$c/= :: CreateContactFlow -> CreateContactFlow -> Bool
== :: CreateContactFlow -> CreateContactFlow -> Bool
$c== :: CreateContactFlow -> CreateContactFlow -> Bool
Prelude.Eq, ReadPrec [CreateContactFlow]
ReadPrec CreateContactFlow
Int -> ReadS CreateContactFlow
ReadS [CreateContactFlow]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateContactFlow]
$creadListPrec :: ReadPrec [CreateContactFlow]
readPrec :: ReadPrec CreateContactFlow
$creadPrec :: ReadPrec CreateContactFlow
readList :: ReadS [CreateContactFlow]
$creadList :: ReadS [CreateContactFlow]
readsPrec :: Int -> ReadS CreateContactFlow
$creadsPrec :: Int -> ReadS CreateContactFlow
Prelude.Read, Int -> CreateContactFlow -> ShowS
[CreateContactFlow] -> ShowS
CreateContactFlow -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateContactFlow] -> ShowS
$cshowList :: [CreateContactFlow] -> ShowS
show :: CreateContactFlow -> String
$cshow :: CreateContactFlow -> String
showsPrec :: Int -> CreateContactFlow -> ShowS
$cshowsPrec :: Int -> CreateContactFlow -> ShowS
Prelude.Show, forall x. Rep CreateContactFlow x -> CreateContactFlow
forall x. CreateContactFlow -> Rep CreateContactFlow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateContactFlow x -> CreateContactFlow
$cfrom :: forall x. CreateContactFlow -> Rep CreateContactFlow x
Prelude.Generic)

-- |
-- Create a value of 'CreateContactFlow' 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', 'createContactFlow_description' - The description of the flow.
--
-- 'tags', 'createContactFlow_tags' - The tags used to organize, track, or control access for this resource.
-- For example, { \"tags\": {\"key1\":\"value1\", \"key2\":\"value2\"} }.
--
-- 'instanceId', 'createContactFlow_instanceId' - The identifier of the Amazon Connect instance.
--
-- 'name', 'createContactFlow_name' - The name of the flow.
--
-- 'type'', 'createContactFlow_type' - The type of the flow. For descriptions of the available types, see
-- <https://docs.aws.amazon.com/connect/latest/adminguide/create-contact-flow.html#contact-flow-types Choose a flow type>
-- in the /Amazon Connect Administrator Guide/.
--
-- 'content', 'createContactFlow_content' - The content of the flow.
newCreateContactFlow ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  -- | 'type''
  ContactFlowType ->
  -- | 'content'
  Prelude.Text ->
  CreateContactFlow
newCreateContactFlow :: Text -> Text -> ContactFlowType -> Text -> CreateContactFlow
newCreateContactFlow
  Text
pInstanceId_
  Text
pName_
  ContactFlowType
pType_
  Text
pContent_ =
    CreateContactFlow'
      { $sel:description:CreateContactFlow' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateContactFlow' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:instanceId:CreateContactFlow' :: Text
instanceId = Text
pInstanceId_,
        $sel:name:CreateContactFlow' :: Text
name = Text
pName_,
        $sel:type':CreateContactFlow' :: ContactFlowType
type' = ContactFlowType
pType_,
        $sel:content:CreateContactFlow' :: Text
content = Text
pContent_
      }

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

-- | The tags used to organize, track, or control access for this resource.
-- For example, { \"tags\": {\"key1\":\"value1\", \"key2\":\"value2\"} }.
createContactFlow_tags :: Lens.Lens' CreateContactFlow (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createContactFlow_tags :: Lens' CreateContactFlow (Maybe (HashMap Text Text))
createContactFlow_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateContactFlow' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateContactFlow' :: CreateContactFlow -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateContactFlow
s@CreateContactFlow' {} Maybe (HashMap Text Text)
a -> CreateContactFlow
s {$sel:tags:CreateContactFlow' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateContactFlow) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

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

-- | The type of the flow. For descriptions of the available types, see
-- <https://docs.aws.amazon.com/connect/latest/adminguide/create-contact-flow.html#contact-flow-types Choose a flow type>
-- in the /Amazon Connect Administrator Guide/.
createContactFlow_type :: Lens.Lens' CreateContactFlow ContactFlowType
createContactFlow_type :: Lens' CreateContactFlow ContactFlowType
createContactFlow_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateContactFlow' {ContactFlowType
type' :: ContactFlowType
$sel:type':CreateContactFlow' :: CreateContactFlow -> ContactFlowType
type'} -> ContactFlowType
type') (\s :: CreateContactFlow
s@CreateContactFlow' {} ContactFlowType
a -> CreateContactFlow
s {$sel:type':CreateContactFlow' :: ContactFlowType
type' = ContactFlowType
a} :: CreateContactFlow)

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

instance Core.AWSRequest CreateContactFlow where
  type
    AWSResponse CreateContactFlow =
      CreateContactFlowResponse
  request :: (Service -> Service)
-> CreateContactFlow -> Request CreateContactFlow
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateContactFlow
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateContactFlow)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Maybe Text -> Int -> CreateContactFlowResponse
CreateContactFlowResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ContactFlowArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ContactFlowId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable CreateContactFlow where
  hashWithSalt :: Int -> CreateContactFlow -> Int
hashWithSalt Int
_salt CreateContactFlow' {Maybe Text
Maybe (HashMap Text Text)
Text
ContactFlowType
content :: Text
type' :: ContactFlowType
name :: Text
instanceId :: Text
tags :: Maybe (HashMap Text Text)
description :: Maybe Text
$sel:content:CreateContactFlow' :: CreateContactFlow -> Text
$sel:type':CreateContactFlow' :: CreateContactFlow -> ContactFlowType
$sel:name:CreateContactFlow' :: CreateContactFlow -> Text
$sel:instanceId:CreateContactFlow' :: CreateContactFlow -> Text
$sel:tags:CreateContactFlow' :: CreateContactFlow -> Maybe (HashMap Text Text)
$sel:description:CreateContactFlow' :: CreateContactFlow -> 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 (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ContactFlowType
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
content

instance Prelude.NFData CreateContactFlow where
  rnf :: CreateContactFlow -> ()
rnf CreateContactFlow' {Maybe Text
Maybe (HashMap Text Text)
Text
ContactFlowType
content :: Text
type' :: ContactFlowType
name :: Text
instanceId :: Text
tags :: Maybe (HashMap Text Text)
description :: Maybe Text
$sel:content:CreateContactFlow' :: CreateContactFlow -> Text
$sel:type':CreateContactFlow' :: CreateContactFlow -> ContactFlowType
$sel:name:CreateContactFlow' :: CreateContactFlow -> Text
$sel:instanceId:CreateContactFlow' :: CreateContactFlow -> Text
$sel:tags:CreateContactFlow' :: CreateContactFlow -> Maybe (HashMap Text Text)
$sel:description:CreateContactFlow' :: CreateContactFlow -> 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 (HashMap Text Text)
tags
      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
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ContactFlowType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
content

instance Data.ToHeaders CreateContactFlow where
  toHeaders :: CreateContactFlow -> ResponseHeaders
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 -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CreateContactFlow where
  toJSON :: CreateContactFlow -> Value
toJSON CreateContactFlow' {Maybe Text
Maybe (HashMap Text Text)
Text
ContactFlowType
content :: Text
type' :: ContactFlowType
name :: Text
instanceId :: Text
tags :: Maybe (HashMap Text Text)
description :: Maybe Text
$sel:content:CreateContactFlow' :: CreateContactFlow -> Text
$sel:type':CreateContactFlow' :: CreateContactFlow -> ContactFlowType
$sel:name:CreateContactFlow' :: CreateContactFlow -> Text
$sel:instanceId:CreateContactFlow' :: CreateContactFlow -> Text
$sel:tags:CreateContactFlow' :: CreateContactFlow -> Maybe (HashMap Text Text)
$sel:description:CreateContactFlow' :: CreateContactFlow -> 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
"Tags" 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 (HashMap Text Text)
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name),
            forall a. a -> Maybe a
Prelude.Just (Key
"Type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ContactFlowType
type'),
            forall a. a -> Maybe a
Prelude.Just (Key
"Content" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
content)
          ]
      )

instance Data.ToPath CreateContactFlow where
  toPath :: CreateContactFlow -> ByteString
toPath CreateContactFlow' {Maybe Text
Maybe (HashMap Text Text)
Text
ContactFlowType
content :: Text
type' :: ContactFlowType
name :: Text
instanceId :: Text
tags :: Maybe (HashMap Text Text)
description :: Maybe Text
$sel:content:CreateContactFlow' :: CreateContactFlow -> Text
$sel:type':CreateContactFlow' :: CreateContactFlow -> ContactFlowType
$sel:name:CreateContactFlow' :: CreateContactFlow -> Text
$sel:instanceId:CreateContactFlow' :: CreateContactFlow -> Text
$sel:tags:CreateContactFlow' :: CreateContactFlow -> Maybe (HashMap Text Text)
$sel:description:CreateContactFlow' :: CreateContactFlow -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/contact-flows/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId]

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

-- | /See:/ 'newCreateContactFlowResponse' smart constructor.
data CreateContactFlowResponse = CreateContactFlowResponse'
  { -- | The Amazon Resource Name (ARN) of the flow.
    CreateContactFlowResponse -> Maybe Text
contactFlowArn :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the flow.
    CreateContactFlowResponse -> Maybe Text
contactFlowId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateContactFlowResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateContactFlowResponse -> CreateContactFlowResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateContactFlowResponse -> CreateContactFlowResponse -> Bool
$c/= :: CreateContactFlowResponse -> CreateContactFlowResponse -> Bool
== :: CreateContactFlowResponse -> CreateContactFlowResponse -> Bool
$c== :: CreateContactFlowResponse -> CreateContactFlowResponse -> Bool
Prelude.Eq, ReadPrec [CreateContactFlowResponse]
ReadPrec CreateContactFlowResponse
Int -> ReadS CreateContactFlowResponse
ReadS [CreateContactFlowResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateContactFlowResponse]
$creadListPrec :: ReadPrec [CreateContactFlowResponse]
readPrec :: ReadPrec CreateContactFlowResponse
$creadPrec :: ReadPrec CreateContactFlowResponse
readList :: ReadS [CreateContactFlowResponse]
$creadList :: ReadS [CreateContactFlowResponse]
readsPrec :: Int -> ReadS CreateContactFlowResponse
$creadsPrec :: Int -> ReadS CreateContactFlowResponse
Prelude.Read, Int -> CreateContactFlowResponse -> ShowS
[CreateContactFlowResponse] -> ShowS
CreateContactFlowResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateContactFlowResponse] -> ShowS
$cshowList :: [CreateContactFlowResponse] -> ShowS
show :: CreateContactFlowResponse -> String
$cshow :: CreateContactFlowResponse -> String
showsPrec :: Int -> CreateContactFlowResponse -> ShowS
$cshowsPrec :: Int -> CreateContactFlowResponse -> ShowS
Prelude.Show, forall x.
Rep CreateContactFlowResponse x -> CreateContactFlowResponse
forall x.
CreateContactFlowResponse -> Rep CreateContactFlowResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateContactFlowResponse x -> CreateContactFlowResponse
$cfrom :: forall x.
CreateContactFlowResponse -> Rep CreateContactFlowResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateContactFlowResponse' 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:
--
-- 'contactFlowArn', 'createContactFlowResponse_contactFlowArn' - The Amazon Resource Name (ARN) of the flow.
--
-- 'contactFlowId', 'createContactFlowResponse_contactFlowId' - The identifier of the flow.
--
-- 'httpStatus', 'createContactFlowResponse_httpStatus' - The response's http status code.
newCreateContactFlowResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateContactFlowResponse
newCreateContactFlowResponse :: Int -> CreateContactFlowResponse
newCreateContactFlowResponse Int
pHttpStatus_ =
  CreateContactFlowResponse'
    { $sel:contactFlowArn:CreateContactFlowResponse' :: Maybe Text
contactFlowArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:contactFlowId:CreateContactFlowResponse' :: Maybe Text
contactFlowId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateContactFlowResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the flow.
createContactFlowResponse_contactFlowArn :: Lens.Lens' CreateContactFlowResponse (Prelude.Maybe Prelude.Text)
createContactFlowResponse_contactFlowArn :: Lens' CreateContactFlowResponse (Maybe Text)
createContactFlowResponse_contactFlowArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateContactFlowResponse' {Maybe Text
contactFlowArn :: Maybe Text
$sel:contactFlowArn:CreateContactFlowResponse' :: CreateContactFlowResponse -> Maybe Text
contactFlowArn} -> Maybe Text
contactFlowArn) (\s :: CreateContactFlowResponse
s@CreateContactFlowResponse' {} Maybe Text
a -> CreateContactFlowResponse
s {$sel:contactFlowArn:CreateContactFlowResponse' :: Maybe Text
contactFlowArn = Maybe Text
a} :: CreateContactFlowResponse)

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

-- | The response's http status code.
createContactFlowResponse_httpStatus :: Lens.Lens' CreateContactFlowResponse Prelude.Int
createContactFlowResponse_httpStatus :: Lens' CreateContactFlowResponse Int
createContactFlowResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateContactFlowResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateContactFlowResponse' :: CreateContactFlowResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateContactFlowResponse
s@CreateContactFlowResponse' {} Int
a -> CreateContactFlowResponse
s {$sel:httpStatus:CreateContactFlowResponse' :: Int
httpStatus = Int
a} :: CreateContactFlowResponse)

instance Prelude.NFData CreateContactFlowResponse where
  rnf :: CreateContactFlowResponse -> ()
rnf CreateContactFlowResponse' {Int
Maybe Text
httpStatus :: Int
contactFlowId :: Maybe Text
contactFlowArn :: Maybe Text
$sel:httpStatus:CreateContactFlowResponse' :: CreateContactFlowResponse -> Int
$sel:contactFlowId:CreateContactFlowResponse' :: CreateContactFlowResponse -> Maybe Text
$sel:contactFlowArn:CreateContactFlowResponse' :: CreateContactFlowResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
contactFlowArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
contactFlowId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus