{-# 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.SearchRoutingProfiles
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This API is in preview release for Amazon Connect and is subject to
-- change.
--
-- Searches routing profiles in an Amazon Connect instance, with optional
-- filtering.
--
-- This operation returns paginated results.
module Amazonka.Connect.SearchRoutingProfiles
  ( -- * Creating a Request
    SearchRoutingProfiles (..),
    newSearchRoutingProfiles,

    -- * Request Lenses
    searchRoutingProfiles_maxResults,
    searchRoutingProfiles_nextToken,
    searchRoutingProfiles_searchCriteria,
    searchRoutingProfiles_searchFilter,
    searchRoutingProfiles_instanceId,

    -- * Destructuring the Response
    SearchRoutingProfilesResponse (..),
    newSearchRoutingProfilesResponse,

    -- * Response Lenses
    searchRoutingProfilesResponse_approximateTotalCount,
    searchRoutingProfilesResponse_nextToken,
    searchRoutingProfilesResponse_routingProfiles,
    searchRoutingProfilesResponse_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:/ 'newSearchRoutingProfiles' smart constructor.
data SearchRoutingProfiles = SearchRoutingProfiles'
  { -- | The maximum number of results to return per page.
    SearchRoutingProfiles -> 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.
    SearchRoutingProfiles -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The search criteria to be used to return routing profiles.
    --
    -- The @name@ and @description@ fields support \"contains\" queries with a
    -- minimum of 2 characters and a maximum of 25 characters. Any queries with
    -- character lengths outside of this range will throw invalid results.
    SearchRoutingProfiles -> Maybe RoutingProfileSearchCriteria
searchCriteria :: Prelude.Maybe RoutingProfileSearchCriteria,
    -- | Filters to be applied to search results.
    SearchRoutingProfiles -> Maybe RoutingProfileSearchFilter
searchFilter :: Prelude.Maybe RoutingProfileSearchFilter,
    -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    SearchRoutingProfiles -> Text
instanceId :: Prelude.Text
  }
  deriving (SearchRoutingProfiles -> SearchRoutingProfiles -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchRoutingProfiles -> SearchRoutingProfiles -> Bool
$c/= :: SearchRoutingProfiles -> SearchRoutingProfiles -> Bool
== :: SearchRoutingProfiles -> SearchRoutingProfiles -> Bool
$c== :: SearchRoutingProfiles -> SearchRoutingProfiles -> Bool
Prelude.Eq, ReadPrec [SearchRoutingProfiles]
ReadPrec SearchRoutingProfiles
Int -> ReadS SearchRoutingProfiles
ReadS [SearchRoutingProfiles]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SearchRoutingProfiles]
$creadListPrec :: ReadPrec [SearchRoutingProfiles]
readPrec :: ReadPrec SearchRoutingProfiles
$creadPrec :: ReadPrec SearchRoutingProfiles
readList :: ReadS [SearchRoutingProfiles]
$creadList :: ReadS [SearchRoutingProfiles]
readsPrec :: Int -> ReadS SearchRoutingProfiles
$creadsPrec :: Int -> ReadS SearchRoutingProfiles
Prelude.Read, Int -> SearchRoutingProfiles -> ShowS
[SearchRoutingProfiles] -> ShowS
SearchRoutingProfiles -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchRoutingProfiles] -> ShowS
$cshowList :: [SearchRoutingProfiles] -> ShowS
show :: SearchRoutingProfiles -> String
$cshow :: SearchRoutingProfiles -> String
showsPrec :: Int -> SearchRoutingProfiles -> ShowS
$cshowsPrec :: Int -> SearchRoutingProfiles -> ShowS
Prelude.Show, forall x. Rep SearchRoutingProfiles x -> SearchRoutingProfiles
forall x. SearchRoutingProfiles -> Rep SearchRoutingProfiles x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchRoutingProfiles x -> SearchRoutingProfiles
$cfrom :: forall x. SearchRoutingProfiles -> Rep SearchRoutingProfiles x
Prelude.Generic)

-- |
-- Create a value of 'SearchRoutingProfiles' 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:
--
-- 'maxResults', 'searchRoutingProfiles_maxResults' - The maximum number of results to return per page.
--
-- 'nextToken', 'searchRoutingProfiles_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.
--
-- 'searchCriteria', 'searchRoutingProfiles_searchCriteria' - The search criteria to be used to return routing profiles.
--
-- The @name@ and @description@ fields support \"contains\" queries with a
-- minimum of 2 characters and a maximum of 25 characters. Any queries with
-- character lengths outside of this range will throw invalid results.
--
-- 'searchFilter', 'searchRoutingProfiles_searchFilter' - Filters to be applied to search results.
--
-- 'instanceId', 'searchRoutingProfiles_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
newSearchRoutingProfiles ::
  -- | 'instanceId'
  Prelude.Text ->
  SearchRoutingProfiles
newSearchRoutingProfiles :: Text -> SearchRoutingProfiles
newSearchRoutingProfiles Text
pInstanceId_ =
  SearchRoutingProfiles'
    { $sel:maxResults:SearchRoutingProfiles' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:SearchRoutingProfiles' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:searchCriteria:SearchRoutingProfiles' :: Maybe RoutingProfileSearchCriteria
searchCriteria = forall a. Maybe a
Prelude.Nothing,
      $sel:searchFilter:SearchRoutingProfiles' :: Maybe RoutingProfileSearchFilter
searchFilter = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:SearchRoutingProfiles' :: Text
instanceId = Text
pInstanceId_
    }

-- | The maximum number of results to return per page.
searchRoutingProfiles_maxResults :: Lens.Lens' SearchRoutingProfiles (Prelude.Maybe Prelude.Natural)
searchRoutingProfiles_maxResults :: Lens' SearchRoutingProfiles (Maybe Natural)
searchRoutingProfiles_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchRoutingProfiles' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:SearchRoutingProfiles' :: SearchRoutingProfiles -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: SearchRoutingProfiles
s@SearchRoutingProfiles' {} Maybe Natural
a -> SearchRoutingProfiles
s {$sel:maxResults:SearchRoutingProfiles' :: Maybe Natural
maxResults = Maybe Natural
a} :: SearchRoutingProfiles)

-- | 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.
searchRoutingProfiles_nextToken :: Lens.Lens' SearchRoutingProfiles (Prelude.Maybe Prelude.Text)
searchRoutingProfiles_nextToken :: Lens' SearchRoutingProfiles (Maybe Text)
searchRoutingProfiles_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchRoutingProfiles' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:SearchRoutingProfiles' :: SearchRoutingProfiles -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: SearchRoutingProfiles
s@SearchRoutingProfiles' {} Maybe Text
a -> SearchRoutingProfiles
s {$sel:nextToken:SearchRoutingProfiles' :: Maybe Text
nextToken = Maybe Text
a} :: SearchRoutingProfiles)

-- | The search criteria to be used to return routing profiles.
--
-- The @name@ and @description@ fields support \"contains\" queries with a
-- minimum of 2 characters and a maximum of 25 characters. Any queries with
-- character lengths outside of this range will throw invalid results.
searchRoutingProfiles_searchCriteria :: Lens.Lens' SearchRoutingProfiles (Prelude.Maybe RoutingProfileSearchCriteria)
searchRoutingProfiles_searchCriteria :: Lens' SearchRoutingProfiles (Maybe RoutingProfileSearchCriteria)
searchRoutingProfiles_searchCriteria = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchRoutingProfiles' {Maybe RoutingProfileSearchCriteria
searchCriteria :: Maybe RoutingProfileSearchCriteria
$sel:searchCriteria:SearchRoutingProfiles' :: SearchRoutingProfiles -> Maybe RoutingProfileSearchCriteria
searchCriteria} -> Maybe RoutingProfileSearchCriteria
searchCriteria) (\s :: SearchRoutingProfiles
s@SearchRoutingProfiles' {} Maybe RoutingProfileSearchCriteria
a -> SearchRoutingProfiles
s {$sel:searchCriteria:SearchRoutingProfiles' :: Maybe RoutingProfileSearchCriteria
searchCriteria = Maybe RoutingProfileSearchCriteria
a} :: SearchRoutingProfiles)

-- | Filters to be applied to search results.
searchRoutingProfiles_searchFilter :: Lens.Lens' SearchRoutingProfiles (Prelude.Maybe RoutingProfileSearchFilter)
searchRoutingProfiles_searchFilter :: Lens' SearchRoutingProfiles (Maybe RoutingProfileSearchFilter)
searchRoutingProfiles_searchFilter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchRoutingProfiles' {Maybe RoutingProfileSearchFilter
searchFilter :: Maybe RoutingProfileSearchFilter
$sel:searchFilter:SearchRoutingProfiles' :: SearchRoutingProfiles -> Maybe RoutingProfileSearchFilter
searchFilter} -> Maybe RoutingProfileSearchFilter
searchFilter) (\s :: SearchRoutingProfiles
s@SearchRoutingProfiles' {} Maybe RoutingProfileSearchFilter
a -> SearchRoutingProfiles
s {$sel:searchFilter:SearchRoutingProfiles' :: Maybe RoutingProfileSearchFilter
searchFilter = Maybe RoutingProfileSearchFilter
a} :: SearchRoutingProfiles)

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

instance Core.AWSPager SearchRoutingProfiles where
  page :: SearchRoutingProfiles
-> AWSResponse SearchRoutingProfiles -> Maybe SearchRoutingProfiles
page SearchRoutingProfiles
rq AWSResponse SearchRoutingProfiles
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse SearchRoutingProfiles
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SearchRoutingProfilesResponse (Maybe Text)
searchRoutingProfilesResponse_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 SearchRoutingProfiles
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SearchRoutingProfilesResponse (Maybe [RoutingProfile])
searchRoutingProfilesResponse_routingProfiles
            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.$ SearchRoutingProfiles
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' SearchRoutingProfiles (Maybe Text)
searchRoutingProfiles_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse SearchRoutingProfiles
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SearchRoutingProfilesResponse (Maybe Text)
searchRoutingProfilesResponse_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 SearchRoutingProfiles where
  type
    AWSResponse SearchRoutingProfiles =
      SearchRoutingProfilesResponse
  request :: (Service -> Service)
-> SearchRoutingProfiles -> Request SearchRoutingProfiles
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 SearchRoutingProfiles
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse SearchRoutingProfiles)))
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 Integer
-> Maybe Text
-> Maybe [RoutingProfile]
-> Int
-> SearchRoutingProfilesResponse
SearchRoutingProfilesResponse'
            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
"ApproximateTotalCount")
            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.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RoutingProfiles"
                            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable SearchRoutingProfiles where
  hashWithSalt :: Int -> SearchRoutingProfiles -> Int
hashWithSalt Int
_salt SearchRoutingProfiles' {Maybe Natural
Maybe Text
Maybe RoutingProfileSearchCriteria
Maybe RoutingProfileSearchFilter
Text
instanceId :: Text
searchFilter :: Maybe RoutingProfileSearchFilter
searchCriteria :: Maybe RoutingProfileSearchCriteria
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:instanceId:SearchRoutingProfiles' :: SearchRoutingProfiles -> Text
$sel:searchFilter:SearchRoutingProfiles' :: SearchRoutingProfiles -> Maybe RoutingProfileSearchFilter
$sel:searchCriteria:SearchRoutingProfiles' :: SearchRoutingProfiles -> Maybe RoutingProfileSearchCriteria
$sel:nextToken:SearchRoutingProfiles' :: SearchRoutingProfiles -> Maybe Text
$sel:maxResults:SearchRoutingProfiles' :: SearchRoutingProfiles -> Maybe Natural
..} =
    Int
_salt
      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` Maybe RoutingProfileSearchCriteria
searchCriteria
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RoutingProfileSearchFilter
searchFilter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId

instance Prelude.NFData SearchRoutingProfiles where
  rnf :: SearchRoutingProfiles -> ()
rnf SearchRoutingProfiles' {Maybe Natural
Maybe Text
Maybe RoutingProfileSearchCriteria
Maybe RoutingProfileSearchFilter
Text
instanceId :: Text
searchFilter :: Maybe RoutingProfileSearchFilter
searchCriteria :: Maybe RoutingProfileSearchCriteria
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:instanceId:SearchRoutingProfiles' :: SearchRoutingProfiles -> Text
$sel:searchFilter:SearchRoutingProfiles' :: SearchRoutingProfiles -> Maybe RoutingProfileSearchFilter
$sel:searchCriteria:SearchRoutingProfiles' :: SearchRoutingProfiles -> Maybe RoutingProfileSearchCriteria
$sel:nextToken:SearchRoutingProfiles' :: SearchRoutingProfiles -> Maybe Text
$sel:maxResults:SearchRoutingProfiles' :: SearchRoutingProfiles -> Maybe Natural
..} =
    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 Maybe RoutingProfileSearchCriteria
searchCriteria
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RoutingProfileSearchFilter
searchFilter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId

instance Data.ToHeaders SearchRoutingProfiles where
  toHeaders :: SearchRoutingProfiles -> 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 SearchRoutingProfiles where
  toJSON :: SearchRoutingProfiles -> Value
toJSON SearchRoutingProfiles' {Maybe Natural
Maybe Text
Maybe RoutingProfileSearchCriteria
Maybe RoutingProfileSearchFilter
Text
instanceId :: Text
searchFilter :: Maybe RoutingProfileSearchFilter
searchCriteria :: Maybe RoutingProfileSearchCriteria
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:instanceId:SearchRoutingProfiles' :: SearchRoutingProfiles -> Text
$sel:searchFilter:SearchRoutingProfiles' :: SearchRoutingProfiles -> Maybe RoutingProfileSearchFilter
$sel:searchCriteria:SearchRoutingProfiles' :: SearchRoutingProfiles -> Maybe RoutingProfileSearchCriteria
$sel:nextToken:SearchRoutingProfiles' :: SearchRoutingProfiles -> Maybe Text
$sel:maxResults:SearchRoutingProfiles' :: SearchRoutingProfiles -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"MaxResults" 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 Natural
maxResults,
            (Key
"NextToken" 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
nextToken,
            (Key
"SearchCriteria" 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 RoutingProfileSearchCriteria
searchCriteria,
            (Key
"SearchFilter" 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 RoutingProfileSearchFilter
searchFilter,
            forall a. a -> Maybe a
Prelude.Just (Key
"InstanceId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
instanceId)
          ]
      )

instance Data.ToPath SearchRoutingProfiles where
  toPath :: SearchRoutingProfiles -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/search-routing-profiles"

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

-- | /See:/ 'newSearchRoutingProfilesResponse' smart constructor.
data SearchRoutingProfilesResponse = SearchRoutingProfilesResponse'
  { -- | The total number of routing profiles which matched your search query.
    SearchRoutingProfilesResponse -> Maybe Integer
approximateTotalCount :: Prelude.Maybe Prelude.Integer,
    -- | If there are additional results, this is the token for the next set of
    -- results.
    SearchRoutingProfilesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Information about the routing profiles.
    SearchRoutingProfilesResponse -> Maybe [RoutingProfile]
routingProfiles :: Prelude.Maybe [RoutingProfile],
    -- | The response's http status code.
    SearchRoutingProfilesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (SearchRoutingProfilesResponse
-> SearchRoutingProfilesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchRoutingProfilesResponse
-> SearchRoutingProfilesResponse -> Bool
$c/= :: SearchRoutingProfilesResponse
-> SearchRoutingProfilesResponse -> Bool
== :: SearchRoutingProfilesResponse
-> SearchRoutingProfilesResponse -> Bool
$c== :: SearchRoutingProfilesResponse
-> SearchRoutingProfilesResponse -> Bool
Prelude.Eq, ReadPrec [SearchRoutingProfilesResponse]
ReadPrec SearchRoutingProfilesResponse
Int -> ReadS SearchRoutingProfilesResponse
ReadS [SearchRoutingProfilesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SearchRoutingProfilesResponse]
$creadListPrec :: ReadPrec [SearchRoutingProfilesResponse]
readPrec :: ReadPrec SearchRoutingProfilesResponse
$creadPrec :: ReadPrec SearchRoutingProfilesResponse
readList :: ReadS [SearchRoutingProfilesResponse]
$creadList :: ReadS [SearchRoutingProfilesResponse]
readsPrec :: Int -> ReadS SearchRoutingProfilesResponse
$creadsPrec :: Int -> ReadS SearchRoutingProfilesResponse
Prelude.Read, Int -> SearchRoutingProfilesResponse -> ShowS
[SearchRoutingProfilesResponse] -> ShowS
SearchRoutingProfilesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchRoutingProfilesResponse] -> ShowS
$cshowList :: [SearchRoutingProfilesResponse] -> ShowS
show :: SearchRoutingProfilesResponse -> String
$cshow :: SearchRoutingProfilesResponse -> String
showsPrec :: Int -> SearchRoutingProfilesResponse -> ShowS
$cshowsPrec :: Int -> SearchRoutingProfilesResponse -> ShowS
Prelude.Show, forall x.
Rep SearchRoutingProfilesResponse x
-> SearchRoutingProfilesResponse
forall x.
SearchRoutingProfilesResponse
-> Rep SearchRoutingProfilesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SearchRoutingProfilesResponse x
-> SearchRoutingProfilesResponse
$cfrom :: forall x.
SearchRoutingProfilesResponse
-> Rep SearchRoutingProfilesResponse x
Prelude.Generic)

-- |
-- Create a value of 'SearchRoutingProfilesResponse' 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:
--
-- 'approximateTotalCount', 'searchRoutingProfilesResponse_approximateTotalCount' - The total number of routing profiles which matched your search query.
--
-- 'nextToken', 'searchRoutingProfilesResponse_nextToken' - If there are additional results, this is the token for the next set of
-- results.
--
-- 'routingProfiles', 'searchRoutingProfilesResponse_routingProfiles' - Information about the routing profiles.
--
-- 'httpStatus', 'searchRoutingProfilesResponse_httpStatus' - The response's http status code.
newSearchRoutingProfilesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  SearchRoutingProfilesResponse
newSearchRoutingProfilesResponse :: Int -> SearchRoutingProfilesResponse
newSearchRoutingProfilesResponse Int
pHttpStatus_ =
  SearchRoutingProfilesResponse'
    { $sel:approximateTotalCount:SearchRoutingProfilesResponse' :: Maybe Integer
approximateTotalCount =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:SearchRoutingProfilesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:routingProfiles:SearchRoutingProfilesResponse' :: Maybe [RoutingProfile]
routingProfiles = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:SearchRoutingProfilesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The total number of routing profiles which matched your search query.
searchRoutingProfilesResponse_approximateTotalCount :: Lens.Lens' SearchRoutingProfilesResponse (Prelude.Maybe Prelude.Integer)
searchRoutingProfilesResponse_approximateTotalCount :: Lens' SearchRoutingProfilesResponse (Maybe Integer)
searchRoutingProfilesResponse_approximateTotalCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchRoutingProfilesResponse' {Maybe Integer
approximateTotalCount :: Maybe Integer
$sel:approximateTotalCount:SearchRoutingProfilesResponse' :: SearchRoutingProfilesResponse -> Maybe Integer
approximateTotalCount} -> Maybe Integer
approximateTotalCount) (\s :: SearchRoutingProfilesResponse
s@SearchRoutingProfilesResponse' {} Maybe Integer
a -> SearchRoutingProfilesResponse
s {$sel:approximateTotalCount:SearchRoutingProfilesResponse' :: Maybe Integer
approximateTotalCount = Maybe Integer
a} :: SearchRoutingProfilesResponse)

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

-- | Information about the routing profiles.
searchRoutingProfilesResponse_routingProfiles :: Lens.Lens' SearchRoutingProfilesResponse (Prelude.Maybe [RoutingProfile])
searchRoutingProfilesResponse_routingProfiles :: Lens' SearchRoutingProfilesResponse (Maybe [RoutingProfile])
searchRoutingProfilesResponse_routingProfiles = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchRoutingProfilesResponse' {Maybe [RoutingProfile]
routingProfiles :: Maybe [RoutingProfile]
$sel:routingProfiles:SearchRoutingProfilesResponse' :: SearchRoutingProfilesResponse -> Maybe [RoutingProfile]
routingProfiles} -> Maybe [RoutingProfile]
routingProfiles) (\s :: SearchRoutingProfilesResponse
s@SearchRoutingProfilesResponse' {} Maybe [RoutingProfile]
a -> SearchRoutingProfilesResponse
s {$sel:routingProfiles:SearchRoutingProfilesResponse' :: Maybe [RoutingProfile]
routingProfiles = Maybe [RoutingProfile]
a} :: SearchRoutingProfilesResponse) 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 response's http status code.
searchRoutingProfilesResponse_httpStatus :: Lens.Lens' SearchRoutingProfilesResponse Prelude.Int
searchRoutingProfilesResponse_httpStatus :: Lens' SearchRoutingProfilesResponse Int
searchRoutingProfilesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchRoutingProfilesResponse' {Int
httpStatus :: Int
$sel:httpStatus:SearchRoutingProfilesResponse' :: SearchRoutingProfilesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: SearchRoutingProfilesResponse
s@SearchRoutingProfilesResponse' {} Int
a -> SearchRoutingProfilesResponse
s {$sel:httpStatus:SearchRoutingProfilesResponse' :: Int
httpStatus = Int
a} :: SearchRoutingProfilesResponse)

instance Prelude.NFData SearchRoutingProfilesResponse where
  rnf :: SearchRoutingProfilesResponse -> ()
rnf SearchRoutingProfilesResponse' {Int
Maybe Integer
Maybe [RoutingProfile]
Maybe Text
httpStatus :: Int
routingProfiles :: Maybe [RoutingProfile]
nextToken :: Maybe Text
approximateTotalCount :: Maybe Integer
$sel:httpStatus:SearchRoutingProfilesResponse' :: SearchRoutingProfilesResponse -> Int
$sel:routingProfiles:SearchRoutingProfilesResponse' :: SearchRoutingProfilesResponse -> Maybe [RoutingProfile]
$sel:nextToken:SearchRoutingProfilesResponse' :: SearchRoutingProfilesResponse -> Maybe Text
$sel:approximateTotalCount:SearchRoutingProfilesResponse' :: SearchRoutingProfilesResponse -> Maybe Integer
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
approximateTotalCount
      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 Maybe [RoutingProfile]
routingProfiles
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus