{-# 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.ListContactFlows
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Provides information about the flows 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>.
--
-- For more information about flows, see
-- <https://docs.aws.amazon.com/connect/latest/adminguide/concepts-contact-flows.html Flows>
-- in the /Amazon Connect Administrator Guide/.
--
-- This operation returns paginated results.
module Amazonka.Connect.ListContactFlows
  ( -- * Creating a Request
    ListContactFlows (..),
    newListContactFlows,

    -- * Request Lenses
    listContactFlows_contactFlowTypes,
    listContactFlows_maxResults,
    listContactFlows_nextToken,
    listContactFlows_instanceId,

    -- * Destructuring the Response
    ListContactFlowsResponse (..),
    newListContactFlowsResponse,

    -- * Response Lenses
    listContactFlowsResponse_contactFlowSummaryList,
    listContactFlowsResponse_nextToken,
    listContactFlowsResponse_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:/ 'newListContactFlows' smart constructor.
data ListContactFlows = ListContactFlows'
  { -- | The type of flow.
    ListContactFlows -> Maybe [ContactFlowType]
contactFlowTypes :: Prelude.Maybe [ContactFlowType],
    -- | The maximum number of results to return per page. The default MaxResult
    -- size is 100.
    ListContactFlows -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token for the next set of results. Use the value returned in the
    -- previous response in the next request to retrieve the next set of
    -- results.
    ListContactFlows -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    ListContactFlows -> Text
instanceId :: Prelude.Text
  }
  deriving (ListContactFlows -> ListContactFlows -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListContactFlows -> ListContactFlows -> Bool
$c/= :: ListContactFlows -> ListContactFlows -> Bool
== :: ListContactFlows -> ListContactFlows -> Bool
$c== :: ListContactFlows -> ListContactFlows -> Bool
Prelude.Eq, ReadPrec [ListContactFlows]
ReadPrec ListContactFlows
Int -> ReadS ListContactFlows
ReadS [ListContactFlows]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListContactFlows]
$creadListPrec :: ReadPrec [ListContactFlows]
readPrec :: ReadPrec ListContactFlows
$creadPrec :: ReadPrec ListContactFlows
readList :: ReadS [ListContactFlows]
$creadList :: ReadS [ListContactFlows]
readsPrec :: Int -> ReadS ListContactFlows
$creadsPrec :: Int -> ReadS ListContactFlows
Prelude.Read, Int -> ListContactFlows -> ShowS
[ListContactFlows] -> ShowS
ListContactFlows -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListContactFlows] -> ShowS
$cshowList :: [ListContactFlows] -> ShowS
show :: ListContactFlows -> String
$cshow :: ListContactFlows -> String
showsPrec :: Int -> ListContactFlows -> ShowS
$cshowsPrec :: Int -> ListContactFlows -> ShowS
Prelude.Show, forall x. Rep ListContactFlows x -> ListContactFlows
forall x. ListContactFlows -> Rep ListContactFlows x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListContactFlows x -> ListContactFlows
$cfrom :: forall x. ListContactFlows -> Rep ListContactFlows x
Prelude.Generic)

-- |
-- Create a value of 'ListContactFlows' 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:
--
-- 'contactFlowTypes', 'listContactFlows_contactFlowTypes' - The type of flow.
--
-- 'maxResults', 'listContactFlows_maxResults' - The maximum number of results to return per page. The default MaxResult
-- size is 100.
--
-- 'nextToken', 'listContactFlows_nextToken' - The token for the next set of results. Use the value returned in the
-- previous response in the next request to retrieve the next set of
-- results.
--
-- 'instanceId', 'listContactFlows_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
newListContactFlows ::
  -- | 'instanceId'
  Prelude.Text ->
  ListContactFlows
newListContactFlows :: Text -> ListContactFlows
newListContactFlows Text
pInstanceId_ =
  ListContactFlows'
    { $sel:contactFlowTypes:ListContactFlows' :: Maybe [ContactFlowType]
contactFlowTypes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListContactFlows' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListContactFlows' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:ListContactFlows' :: Text
instanceId = Text
pInstanceId_
    }

-- | The type of flow.
listContactFlows_contactFlowTypes :: Lens.Lens' ListContactFlows (Prelude.Maybe [ContactFlowType])
listContactFlows_contactFlowTypes :: Lens' ListContactFlows (Maybe [ContactFlowType])
listContactFlows_contactFlowTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListContactFlows' {Maybe [ContactFlowType]
contactFlowTypes :: Maybe [ContactFlowType]
$sel:contactFlowTypes:ListContactFlows' :: ListContactFlows -> Maybe [ContactFlowType]
contactFlowTypes} -> Maybe [ContactFlowType]
contactFlowTypes) (\s :: ListContactFlows
s@ListContactFlows' {} Maybe [ContactFlowType]
a -> ListContactFlows
s {$sel:contactFlowTypes:ListContactFlows' :: Maybe [ContactFlowType]
contactFlowTypes = Maybe [ContactFlowType]
a} :: ListContactFlows) 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 maximum number of results to return per page. The default MaxResult
-- size is 100.
listContactFlows_maxResults :: Lens.Lens' ListContactFlows (Prelude.Maybe Prelude.Natural)
listContactFlows_maxResults :: Lens' ListContactFlows (Maybe Natural)
listContactFlows_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListContactFlows' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListContactFlows' :: ListContactFlows -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListContactFlows
s@ListContactFlows' {} Maybe Natural
a -> ListContactFlows
s {$sel:maxResults:ListContactFlows' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListContactFlows)

-- | The token for the next set of results. Use the value returned in the
-- previous response in the next request to retrieve the next set of
-- results.
listContactFlows_nextToken :: Lens.Lens' ListContactFlows (Prelude.Maybe Prelude.Text)
listContactFlows_nextToken :: Lens' ListContactFlows (Maybe Text)
listContactFlows_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListContactFlows' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListContactFlows' :: ListContactFlows -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListContactFlows
s@ListContactFlows' {} Maybe Text
a -> ListContactFlows
s {$sel:nextToken:ListContactFlows' :: Maybe Text
nextToken = Maybe Text
a} :: ListContactFlows)

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

instance Core.AWSPager ListContactFlows where
  page :: ListContactFlows
-> AWSResponse ListContactFlows -> Maybe ListContactFlows
page ListContactFlows
rq AWSResponse ListContactFlows
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListContactFlows
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListContactFlowsResponse (Maybe Text)
listContactFlowsResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListContactFlows
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListContactFlowsResponse (Maybe [ContactFlowSummary])
listContactFlowsResponse_contactFlowSummaryList
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListContactFlows
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListContactFlows (Maybe Text)
listContactFlows_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListContactFlows
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListContactFlowsResponse (Maybe Text)
listContactFlowsResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest ListContactFlows where
  type
    AWSResponse ListContactFlows =
      ListContactFlowsResponse
  request :: (Service -> Service)
-> ListContactFlows -> Request ListContactFlows
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListContactFlows
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListContactFlows)))
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 [ContactFlowSummary]
-> Maybe Text -> Int -> ListContactFlowsResponse
ListContactFlowsResponse'
            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
"ContactFlowSummaryList"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            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
"NextToken")
            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 ListContactFlows where
  hashWithSalt :: Int -> ListContactFlows -> Int
hashWithSalt Int
_salt ListContactFlows' {Maybe Natural
Maybe [ContactFlowType]
Maybe Text
Text
instanceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
contactFlowTypes :: Maybe [ContactFlowType]
$sel:instanceId:ListContactFlows' :: ListContactFlows -> Text
$sel:nextToken:ListContactFlows' :: ListContactFlows -> Maybe Text
$sel:maxResults:ListContactFlows' :: ListContactFlows -> Maybe Natural
$sel:contactFlowTypes:ListContactFlows' :: ListContactFlows -> Maybe [ContactFlowType]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ContactFlowType]
contactFlowTypes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId

instance Prelude.NFData ListContactFlows where
  rnf :: ListContactFlows -> ()
rnf ListContactFlows' {Maybe Natural
Maybe [ContactFlowType]
Maybe Text
Text
instanceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
contactFlowTypes :: Maybe [ContactFlowType]
$sel:instanceId:ListContactFlows' :: ListContactFlows -> Text
$sel:nextToken:ListContactFlows' :: ListContactFlows -> Maybe Text
$sel:maxResults:ListContactFlows' :: ListContactFlows -> Maybe Natural
$sel:contactFlowTypes:ListContactFlows' :: ListContactFlows -> Maybe [ContactFlowType]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [ContactFlowType]
contactFlowTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId

instance Data.ToHeaders ListContactFlows where
  toHeaders :: ListContactFlows -> 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.ToPath ListContactFlows where
  toPath :: ListContactFlows -> ByteString
toPath ListContactFlows' {Maybe Natural
Maybe [ContactFlowType]
Maybe Text
Text
instanceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
contactFlowTypes :: Maybe [ContactFlowType]
$sel:instanceId:ListContactFlows' :: ListContactFlows -> Text
$sel:nextToken:ListContactFlows' :: ListContactFlows -> Maybe Text
$sel:maxResults:ListContactFlows' :: ListContactFlows -> Maybe Natural
$sel:contactFlowTypes:ListContactFlows' :: ListContactFlows -> Maybe [ContactFlowType]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/contact-flows-summary/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId]

instance Data.ToQuery ListContactFlows where
  toQuery :: ListContactFlows -> QueryString
toQuery ListContactFlows' {Maybe Natural
Maybe [ContactFlowType]
Maybe Text
Text
instanceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
contactFlowTypes :: Maybe [ContactFlowType]
$sel:instanceId:ListContactFlows' :: ListContactFlows -> Text
$sel:nextToken:ListContactFlows' :: ListContactFlows -> Maybe Text
$sel:maxResults:ListContactFlows' :: ListContactFlows -> Maybe Natural
$sel:contactFlowTypes:ListContactFlows' :: ListContactFlows -> Maybe [ContactFlowType]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"contactFlowTypes"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ContactFlowType]
contactFlowTypes
            ),
        ByteString
"maxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
      ]

-- | /See:/ 'newListContactFlowsResponse' smart constructor.
data ListContactFlowsResponse = ListContactFlowsResponse'
  { -- | Information about the flows.
    ListContactFlowsResponse -> Maybe [ContactFlowSummary]
contactFlowSummaryList :: Prelude.Maybe [ContactFlowSummary],
    -- | If there are additional results, this is the token for the next set of
    -- results.
    ListContactFlowsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListContactFlowsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListContactFlowsResponse -> ListContactFlowsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListContactFlowsResponse -> ListContactFlowsResponse -> Bool
$c/= :: ListContactFlowsResponse -> ListContactFlowsResponse -> Bool
== :: ListContactFlowsResponse -> ListContactFlowsResponse -> Bool
$c== :: ListContactFlowsResponse -> ListContactFlowsResponse -> Bool
Prelude.Eq, ReadPrec [ListContactFlowsResponse]
ReadPrec ListContactFlowsResponse
Int -> ReadS ListContactFlowsResponse
ReadS [ListContactFlowsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListContactFlowsResponse]
$creadListPrec :: ReadPrec [ListContactFlowsResponse]
readPrec :: ReadPrec ListContactFlowsResponse
$creadPrec :: ReadPrec ListContactFlowsResponse
readList :: ReadS [ListContactFlowsResponse]
$creadList :: ReadS [ListContactFlowsResponse]
readsPrec :: Int -> ReadS ListContactFlowsResponse
$creadsPrec :: Int -> ReadS ListContactFlowsResponse
Prelude.Read, Int -> ListContactFlowsResponse -> ShowS
[ListContactFlowsResponse] -> ShowS
ListContactFlowsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListContactFlowsResponse] -> ShowS
$cshowList :: [ListContactFlowsResponse] -> ShowS
show :: ListContactFlowsResponse -> String
$cshow :: ListContactFlowsResponse -> String
showsPrec :: Int -> ListContactFlowsResponse -> ShowS
$cshowsPrec :: Int -> ListContactFlowsResponse -> ShowS
Prelude.Show, forall x.
Rep ListContactFlowsResponse x -> ListContactFlowsResponse
forall x.
ListContactFlowsResponse -> Rep ListContactFlowsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListContactFlowsResponse x -> ListContactFlowsResponse
$cfrom :: forall x.
ListContactFlowsResponse -> Rep ListContactFlowsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListContactFlowsResponse' 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:
--
-- 'contactFlowSummaryList', 'listContactFlowsResponse_contactFlowSummaryList' - Information about the flows.
--
-- 'nextToken', 'listContactFlowsResponse_nextToken' - If there are additional results, this is the token for the next set of
-- results.
--
-- 'httpStatus', 'listContactFlowsResponse_httpStatus' - The response's http status code.
newListContactFlowsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListContactFlowsResponse
newListContactFlowsResponse :: Int -> ListContactFlowsResponse
newListContactFlowsResponse Int
pHttpStatus_ =
  ListContactFlowsResponse'
    { $sel:contactFlowSummaryList:ListContactFlowsResponse' :: Maybe [ContactFlowSummary]
contactFlowSummaryList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListContactFlowsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListContactFlowsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the flows.
listContactFlowsResponse_contactFlowSummaryList :: Lens.Lens' ListContactFlowsResponse (Prelude.Maybe [ContactFlowSummary])
listContactFlowsResponse_contactFlowSummaryList :: Lens' ListContactFlowsResponse (Maybe [ContactFlowSummary])
listContactFlowsResponse_contactFlowSummaryList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListContactFlowsResponse' {Maybe [ContactFlowSummary]
contactFlowSummaryList :: Maybe [ContactFlowSummary]
$sel:contactFlowSummaryList:ListContactFlowsResponse' :: ListContactFlowsResponse -> Maybe [ContactFlowSummary]
contactFlowSummaryList} -> Maybe [ContactFlowSummary]
contactFlowSummaryList) (\s :: ListContactFlowsResponse
s@ListContactFlowsResponse' {} Maybe [ContactFlowSummary]
a -> ListContactFlowsResponse
s {$sel:contactFlowSummaryList:ListContactFlowsResponse' :: Maybe [ContactFlowSummary]
contactFlowSummaryList = Maybe [ContactFlowSummary]
a} :: ListContactFlowsResponse) 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

-- | If there are additional results, this is the token for the next set of
-- results.
listContactFlowsResponse_nextToken :: Lens.Lens' ListContactFlowsResponse (Prelude.Maybe Prelude.Text)
listContactFlowsResponse_nextToken :: Lens' ListContactFlowsResponse (Maybe Text)
listContactFlowsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListContactFlowsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListContactFlowsResponse' :: ListContactFlowsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListContactFlowsResponse
s@ListContactFlowsResponse' {} Maybe Text
a -> ListContactFlowsResponse
s {$sel:nextToken:ListContactFlowsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListContactFlowsResponse)

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

instance Prelude.NFData ListContactFlowsResponse where
  rnf :: ListContactFlowsResponse -> ()
rnf ListContactFlowsResponse' {Int
Maybe [ContactFlowSummary]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
contactFlowSummaryList :: Maybe [ContactFlowSummary]
$sel:httpStatus:ListContactFlowsResponse' :: ListContactFlowsResponse -> Int
$sel:nextToken:ListContactFlowsResponse' :: ListContactFlowsResponse -> Maybe Text
$sel:contactFlowSummaryList:ListContactFlowsResponse' :: ListContactFlowsResponse -> Maybe [ContactFlowSummary]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [ContactFlowSummary]
contactFlowSummaryList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus