{-# 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.SearchSecurityProfiles
-- 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 security profiles in an Amazon Connect instance, with optional
-- filtering.
--
-- This operation returns paginated results.
module Amazonka.Connect.SearchSecurityProfiles
  ( -- * Creating a Request
    SearchSecurityProfiles (..),
    newSearchSecurityProfiles,

    -- * Request Lenses
    searchSecurityProfiles_maxResults,
    searchSecurityProfiles_nextToken,
    searchSecurityProfiles_searchCriteria,
    searchSecurityProfiles_searchFilter,
    searchSecurityProfiles_instanceId,

    -- * Destructuring the Response
    SearchSecurityProfilesResponse (..),
    newSearchSecurityProfilesResponse,

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

-- |
-- Create a value of 'SearchSecurityProfiles' 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', 'searchSecurityProfiles_maxResults' - The maximum number of results to return per page.
--
-- 'nextToken', 'searchSecurityProfiles_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', 'searchSecurityProfiles_searchCriteria' - The search criteria to be used to return security profiles.
--
-- The @name@ field support \"contains\" queries with a minimum of 2
-- characters and maximum of 25 characters. Any queries with character
-- lengths outside of this range will throw invalid results.
--
-- The currently supported value for @FieldName@: @name@
--
-- 'searchFilter', 'searchSecurityProfiles_searchFilter' - Filters to be applied to search results.
--
-- 'instanceId', 'searchSecurityProfiles_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
newSearchSecurityProfiles ::
  -- | 'instanceId'
  Prelude.Text ->
  SearchSecurityProfiles
newSearchSecurityProfiles :: Text -> SearchSecurityProfiles
newSearchSecurityProfiles Text
pInstanceId_ =
  SearchSecurityProfiles'
    { $sel:maxResults:SearchSecurityProfiles' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:SearchSecurityProfiles' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:searchCriteria:SearchSecurityProfiles' :: Maybe SecurityProfileSearchCriteria
searchCriteria = forall a. Maybe a
Prelude.Nothing,
      $sel:searchFilter:SearchSecurityProfiles' :: Maybe SecurityProfilesSearchFilter
searchFilter = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:SearchSecurityProfiles' :: Text
instanceId = Text
pInstanceId_
    }

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

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

-- | The search criteria to be used to return security profiles.
--
-- The @name@ field support \"contains\" queries with a minimum of 2
-- characters and maximum of 25 characters. Any queries with character
-- lengths outside of this range will throw invalid results.
--
-- The currently supported value for @FieldName@: @name@
searchSecurityProfiles_searchCriteria :: Lens.Lens' SearchSecurityProfiles (Prelude.Maybe SecurityProfileSearchCriteria)
searchSecurityProfiles_searchCriteria :: Lens' SearchSecurityProfiles (Maybe SecurityProfileSearchCriteria)
searchSecurityProfiles_searchCriteria = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchSecurityProfiles' {Maybe SecurityProfileSearchCriteria
searchCriteria :: Maybe SecurityProfileSearchCriteria
$sel:searchCriteria:SearchSecurityProfiles' :: SearchSecurityProfiles -> Maybe SecurityProfileSearchCriteria
searchCriteria} -> Maybe SecurityProfileSearchCriteria
searchCriteria) (\s :: SearchSecurityProfiles
s@SearchSecurityProfiles' {} Maybe SecurityProfileSearchCriteria
a -> SearchSecurityProfiles
s {$sel:searchCriteria:SearchSecurityProfiles' :: Maybe SecurityProfileSearchCriteria
searchCriteria = Maybe SecurityProfileSearchCriteria
a} :: SearchSecurityProfiles)

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

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

instance Core.AWSPager SearchSecurityProfiles where
  page :: SearchSecurityProfiles
-> AWSResponse SearchSecurityProfiles
-> Maybe SearchSecurityProfiles
page SearchSecurityProfiles
rq AWSResponse SearchSecurityProfiles
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse SearchSecurityProfiles
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SearchSecurityProfilesResponse (Maybe Text)
searchSecurityProfilesResponse_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 SearchSecurityProfiles
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  SearchSecurityProfilesResponse
  (Maybe [SecurityProfileSearchSummary])
searchSecurityProfilesResponse_securityProfiles
            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.$ SearchSecurityProfiles
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' SearchSecurityProfiles (Maybe Text)
searchSecurityProfiles_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse SearchSecurityProfiles
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SearchSecurityProfilesResponse (Maybe Text)
searchSecurityProfilesResponse_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 SearchSecurityProfiles where
  type
    AWSResponse SearchSecurityProfiles =
      SearchSecurityProfilesResponse
  request :: (Service -> Service)
-> SearchSecurityProfiles -> Request SearchSecurityProfiles
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 SearchSecurityProfiles
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse SearchSecurityProfiles)))
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 [SecurityProfileSearchSummary]
-> Int
-> SearchSecurityProfilesResponse
SearchSecurityProfilesResponse'
            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
"SecurityProfiles"
                            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 SearchSecurityProfiles where
  hashWithSalt :: Int -> SearchSecurityProfiles -> Int
hashWithSalt Int
_salt SearchSecurityProfiles' {Maybe Natural
Maybe Text
Maybe SecurityProfileSearchCriteria
Maybe SecurityProfilesSearchFilter
Text
instanceId :: Text
searchFilter :: Maybe SecurityProfilesSearchFilter
searchCriteria :: Maybe SecurityProfileSearchCriteria
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:instanceId:SearchSecurityProfiles' :: SearchSecurityProfiles -> Text
$sel:searchFilter:SearchSecurityProfiles' :: SearchSecurityProfiles -> Maybe SecurityProfilesSearchFilter
$sel:searchCriteria:SearchSecurityProfiles' :: SearchSecurityProfiles -> Maybe SecurityProfileSearchCriteria
$sel:nextToken:SearchSecurityProfiles' :: SearchSecurityProfiles -> Maybe Text
$sel:maxResults:SearchSecurityProfiles' :: SearchSecurityProfiles -> 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 SecurityProfileSearchCriteria
searchCriteria
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SecurityProfilesSearchFilter
searchFilter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId

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

instance Data.ToHeaders SearchSecurityProfiles where
  toHeaders :: SearchSecurityProfiles -> 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 SearchSecurityProfiles where
  toJSON :: SearchSecurityProfiles -> Value
toJSON SearchSecurityProfiles' {Maybe Natural
Maybe Text
Maybe SecurityProfileSearchCriteria
Maybe SecurityProfilesSearchFilter
Text
instanceId :: Text
searchFilter :: Maybe SecurityProfilesSearchFilter
searchCriteria :: Maybe SecurityProfileSearchCriteria
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:instanceId:SearchSecurityProfiles' :: SearchSecurityProfiles -> Text
$sel:searchFilter:SearchSecurityProfiles' :: SearchSecurityProfiles -> Maybe SecurityProfilesSearchFilter
$sel:searchCriteria:SearchSecurityProfiles' :: SearchSecurityProfiles -> Maybe SecurityProfileSearchCriteria
$sel:nextToken:SearchSecurityProfiles' :: SearchSecurityProfiles -> Maybe Text
$sel:maxResults:SearchSecurityProfiles' :: SearchSecurityProfiles -> 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 SecurityProfileSearchCriteria
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 SecurityProfilesSearchFilter
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 SearchSecurityProfiles where
  toPath :: SearchSecurityProfiles -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/search-security-profiles"

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

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

-- |
-- Create a value of 'SearchSecurityProfilesResponse' 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', 'searchSecurityProfilesResponse_approximateTotalCount' - The total number of security profiles which matched your search query.
--
-- 'nextToken', 'searchSecurityProfilesResponse_nextToken' - If there are additional results, this is the token for the next set of
-- results.
--
-- 'securityProfiles', 'searchSecurityProfilesResponse_securityProfiles' - Information about the security profiles.
--
-- 'httpStatus', 'searchSecurityProfilesResponse_httpStatus' - The response's http status code.
newSearchSecurityProfilesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  SearchSecurityProfilesResponse
newSearchSecurityProfilesResponse :: Int -> SearchSecurityProfilesResponse
newSearchSecurityProfilesResponse Int
pHttpStatus_ =
  SearchSecurityProfilesResponse'
    { $sel:approximateTotalCount:SearchSecurityProfilesResponse' :: Maybe Integer
approximateTotalCount =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:SearchSecurityProfilesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:securityProfiles:SearchSecurityProfilesResponse' :: Maybe [SecurityProfileSearchSummary]
securityProfiles = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:SearchSecurityProfilesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

-- | Information about the security profiles.
searchSecurityProfilesResponse_securityProfiles :: Lens.Lens' SearchSecurityProfilesResponse (Prelude.Maybe [SecurityProfileSearchSummary])
searchSecurityProfilesResponse_securityProfiles :: Lens'
  SearchSecurityProfilesResponse
  (Maybe [SecurityProfileSearchSummary])
searchSecurityProfilesResponse_securityProfiles = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchSecurityProfilesResponse' {Maybe [SecurityProfileSearchSummary]
securityProfiles :: Maybe [SecurityProfileSearchSummary]
$sel:securityProfiles:SearchSecurityProfilesResponse' :: SearchSecurityProfilesResponse
-> Maybe [SecurityProfileSearchSummary]
securityProfiles} -> Maybe [SecurityProfileSearchSummary]
securityProfiles) (\s :: SearchSecurityProfilesResponse
s@SearchSecurityProfilesResponse' {} Maybe [SecurityProfileSearchSummary]
a -> SearchSecurityProfilesResponse
s {$sel:securityProfiles:SearchSecurityProfilesResponse' :: Maybe [SecurityProfileSearchSummary]
securityProfiles = Maybe [SecurityProfileSearchSummary]
a} :: SearchSecurityProfilesResponse) 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.
searchSecurityProfilesResponse_httpStatus :: Lens.Lens' SearchSecurityProfilesResponse Prelude.Int
searchSecurityProfilesResponse_httpStatus :: Lens' SearchSecurityProfilesResponse Int
searchSecurityProfilesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchSecurityProfilesResponse' {Int
httpStatus :: Int
$sel:httpStatus:SearchSecurityProfilesResponse' :: SearchSecurityProfilesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: SearchSecurityProfilesResponse
s@SearchSecurityProfilesResponse' {} Int
a -> SearchSecurityProfilesResponse
s {$sel:httpStatus:SearchSecurityProfilesResponse' :: Int
httpStatus = Int
a} :: SearchSecurityProfilesResponse)

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