{-# 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.ListSecurityProfilePermissions
-- 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.
--
-- Lists the permissions granted to a security profile.
--
-- This operation returns paginated results.
module Amazonka.Connect.ListSecurityProfilePermissions
  ( -- * Creating a Request
    ListSecurityProfilePermissions (..),
    newListSecurityProfilePermissions,

    -- * Request Lenses
    listSecurityProfilePermissions_maxResults,
    listSecurityProfilePermissions_nextToken,
    listSecurityProfilePermissions_securityProfileId,
    listSecurityProfilePermissions_instanceId,

    -- * Destructuring the Response
    ListSecurityProfilePermissionsResponse (..),
    newListSecurityProfilePermissionsResponse,

    -- * Response Lenses
    listSecurityProfilePermissionsResponse_nextToken,
    listSecurityProfilePermissionsResponse_permissions,
    listSecurityProfilePermissionsResponse_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:/ 'newListSecurityProfilePermissions' smart constructor.
data ListSecurityProfilePermissions = ListSecurityProfilePermissions'
  { -- | The maximum number of results to return per page.
    ListSecurityProfilePermissions -> 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.
    ListSecurityProfilePermissions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The identifier for the security profle.
    ListSecurityProfilePermissions -> Text
securityProfileId :: Prelude.Text,
    -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    ListSecurityProfilePermissions -> Text
instanceId :: Prelude.Text
  }
  deriving (ListSecurityProfilePermissions
-> ListSecurityProfilePermissions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListSecurityProfilePermissions
-> ListSecurityProfilePermissions -> Bool
$c/= :: ListSecurityProfilePermissions
-> ListSecurityProfilePermissions -> Bool
== :: ListSecurityProfilePermissions
-> ListSecurityProfilePermissions -> Bool
$c== :: ListSecurityProfilePermissions
-> ListSecurityProfilePermissions -> Bool
Prelude.Eq, ReadPrec [ListSecurityProfilePermissions]
ReadPrec ListSecurityProfilePermissions
Int -> ReadS ListSecurityProfilePermissions
ReadS [ListSecurityProfilePermissions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListSecurityProfilePermissions]
$creadListPrec :: ReadPrec [ListSecurityProfilePermissions]
readPrec :: ReadPrec ListSecurityProfilePermissions
$creadPrec :: ReadPrec ListSecurityProfilePermissions
readList :: ReadS [ListSecurityProfilePermissions]
$creadList :: ReadS [ListSecurityProfilePermissions]
readsPrec :: Int -> ReadS ListSecurityProfilePermissions
$creadsPrec :: Int -> ReadS ListSecurityProfilePermissions
Prelude.Read, Int -> ListSecurityProfilePermissions -> ShowS
[ListSecurityProfilePermissions] -> ShowS
ListSecurityProfilePermissions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListSecurityProfilePermissions] -> ShowS
$cshowList :: [ListSecurityProfilePermissions] -> ShowS
show :: ListSecurityProfilePermissions -> String
$cshow :: ListSecurityProfilePermissions -> String
showsPrec :: Int -> ListSecurityProfilePermissions -> ShowS
$cshowsPrec :: Int -> ListSecurityProfilePermissions -> ShowS
Prelude.Show, forall x.
Rep ListSecurityProfilePermissions x
-> ListSecurityProfilePermissions
forall x.
ListSecurityProfilePermissions
-> Rep ListSecurityProfilePermissions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListSecurityProfilePermissions x
-> ListSecurityProfilePermissions
$cfrom :: forall x.
ListSecurityProfilePermissions
-> Rep ListSecurityProfilePermissions x
Prelude.Generic)

-- |
-- Create a value of 'ListSecurityProfilePermissions' 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', 'listSecurityProfilePermissions_maxResults' - The maximum number of results to return per page.
--
-- 'nextToken', 'listSecurityProfilePermissions_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.
--
-- 'securityProfileId', 'listSecurityProfilePermissions_securityProfileId' - The identifier for the security profle.
--
-- 'instanceId', 'listSecurityProfilePermissions_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
newListSecurityProfilePermissions ::
  -- | 'securityProfileId'
  Prelude.Text ->
  -- | 'instanceId'
  Prelude.Text ->
  ListSecurityProfilePermissions
newListSecurityProfilePermissions :: Text -> Text -> ListSecurityProfilePermissions
newListSecurityProfilePermissions
  Text
pSecurityProfileId_
  Text
pInstanceId_ =
    ListSecurityProfilePermissions'
      { $sel:maxResults:ListSecurityProfilePermissions' :: Maybe Natural
maxResults =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:ListSecurityProfilePermissions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:securityProfileId:ListSecurityProfilePermissions' :: Text
securityProfileId = Text
pSecurityProfileId_,
        $sel:instanceId:ListSecurityProfilePermissions' :: Text
instanceId = Text
pInstanceId_
      }

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

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

-- | The identifier for the security profle.
listSecurityProfilePermissions_securityProfileId :: Lens.Lens' ListSecurityProfilePermissions Prelude.Text
listSecurityProfilePermissions_securityProfileId :: Lens' ListSecurityProfilePermissions Text
listSecurityProfilePermissions_securityProfileId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSecurityProfilePermissions' {Text
securityProfileId :: Text
$sel:securityProfileId:ListSecurityProfilePermissions' :: ListSecurityProfilePermissions -> Text
securityProfileId} -> Text
securityProfileId) (\s :: ListSecurityProfilePermissions
s@ListSecurityProfilePermissions' {} Text
a -> ListSecurityProfilePermissions
s {$sel:securityProfileId:ListSecurityProfilePermissions' :: Text
securityProfileId = Text
a} :: ListSecurityProfilePermissions)

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

instance Core.AWSPager ListSecurityProfilePermissions where
  page :: ListSecurityProfilePermissions
-> AWSResponse ListSecurityProfilePermissions
-> Maybe ListSecurityProfilePermissions
page ListSecurityProfilePermissions
rq AWSResponse ListSecurityProfilePermissions
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListSecurityProfilePermissions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListSecurityProfilePermissionsResponse (Maybe Text)
listSecurityProfilePermissionsResponse_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 ListSecurityProfilePermissions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListSecurityProfilePermissionsResponse (Maybe [Text])
listSecurityProfilePermissionsResponse_permissions
            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.$ ListSecurityProfilePermissions
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListSecurityProfilePermissions (Maybe Text)
listSecurityProfilePermissions_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListSecurityProfilePermissions
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListSecurityProfilePermissionsResponse (Maybe Text)
listSecurityProfilePermissionsResponse_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
    ListSecurityProfilePermissions
  where
  type
    AWSResponse ListSecurityProfilePermissions =
      ListSecurityProfilePermissionsResponse
  request :: (Service -> Service)
-> ListSecurityProfilePermissions
-> Request ListSecurityProfilePermissions
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 ListSecurityProfilePermissions
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse ListSecurityProfilePermissions)))
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 -> ListSecurityProfilePermissionsResponse
ListSecurityProfilePermissionsResponse'
            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
"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
"Permissions" 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
    ListSecurityProfilePermissions
  where
  hashWithSalt :: Int -> ListSecurityProfilePermissions -> Int
hashWithSalt
    Int
_salt
    ListSecurityProfilePermissions' {Maybe Natural
Maybe Text
Text
instanceId :: Text
securityProfileId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:instanceId:ListSecurityProfilePermissions' :: ListSecurityProfilePermissions -> Text
$sel:securityProfileId:ListSecurityProfilePermissions' :: ListSecurityProfilePermissions -> Text
$sel:nextToken:ListSecurityProfilePermissions' :: ListSecurityProfilePermissions -> Maybe Text
$sel:maxResults:ListSecurityProfilePermissions' :: ListSecurityProfilePermissions -> 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` Text
securityProfileId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId

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

instance
  Data.ToHeaders
    ListSecurityProfilePermissions
  where
  toHeaders :: ListSecurityProfilePermissions -> 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 ListSecurityProfilePermissions where
  toPath :: ListSecurityProfilePermissions -> ByteString
toPath ListSecurityProfilePermissions' {Maybe Natural
Maybe Text
Text
instanceId :: Text
securityProfileId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:instanceId:ListSecurityProfilePermissions' :: ListSecurityProfilePermissions -> Text
$sel:securityProfileId:ListSecurityProfilePermissions' :: ListSecurityProfilePermissions -> Text
$sel:nextToken:ListSecurityProfilePermissions' :: ListSecurityProfilePermissions -> Maybe Text
$sel:maxResults:ListSecurityProfilePermissions' :: ListSecurityProfilePermissions -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/security-profiles-permissions/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId,
        ByteString
"/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
securityProfileId
      ]

instance Data.ToQuery ListSecurityProfilePermissions where
  toQuery :: ListSecurityProfilePermissions -> QueryString
toQuery ListSecurityProfilePermissions' {Maybe Natural
Maybe Text
Text
instanceId :: Text
securityProfileId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:instanceId:ListSecurityProfilePermissions' :: ListSecurityProfilePermissions -> Text
$sel:securityProfileId:ListSecurityProfilePermissions' :: ListSecurityProfilePermissions -> Text
$sel:nextToken:ListSecurityProfilePermissions' :: ListSecurityProfilePermissions -> Maybe Text
$sel:maxResults:ListSecurityProfilePermissions' :: ListSecurityProfilePermissions -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ 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:/ 'newListSecurityProfilePermissionsResponse' smart constructor.
data ListSecurityProfilePermissionsResponse = ListSecurityProfilePermissionsResponse'
  { -- | If there are additional results, this is the token for the next set of
    -- results.
    ListSecurityProfilePermissionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The permissions granted to the security profile. For a complete list of
    -- valid permissions, see
    -- <https://docs.aws.amazon.com/connect/latest/adminguide/security-profile-list.html List of security profile permissions>.
    ListSecurityProfilePermissionsResponse -> Maybe [Text]
permissions :: Prelude.Maybe [Prelude.Text],
    -- | The response's http status code.
    ListSecurityProfilePermissionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListSecurityProfilePermissionsResponse
-> ListSecurityProfilePermissionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListSecurityProfilePermissionsResponse
-> ListSecurityProfilePermissionsResponse -> Bool
$c/= :: ListSecurityProfilePermissionsResponse
-> ListSecurityProfilePermissionsResponse -> Bool
== :: ListSecurityProfilePermissionsResponse
-> ListSecurityProfilePermissionsResponse -> Bool
$c== :: ListSecurityProfilePermissionsResponse
-> ListSecurityProfilePermissionsResponse -> Bool
Prelude.Eq, ReadPrec [ListSecurityProfilePermissionsResponse]
ReadPrec ListSecurityProfilePermissionsResponse
Int -> ReadS ListSecurityProfilePermissionsResponse
ReadS [ListSecurityProfilePermissionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListSecurityProfilePermissionsResponse]
$creadListPrec :: ReadPrec [ListSecurityProfilePermissionsResponse]
readPrec :: ReadPrec ListSecurityProfilePermissionsResponse
$creadPrec :: ReadPrec ListSecurityProfilePermissionsResponse
readList :: ReadS [ListSecurityProfilePermissionsResponse]
$creadList :: ReadS [ListSecurityProfilePermissionsResponse]
readsPrec :: Int -> ReadS ListSecurityProfilePermissionsResponse
$creadsPrec :: Int -> ReadS ListSecurityProfilePermissionsResponse
Prelude.Read, Int -> ListSecurityProfilePermissionsResponse -> ShowS
[ListSecurityProfilePermissionsResponse] -> ShowS
ListSecurityProfilePermissionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListSecurityProfilePermissionsResponse] -> ShowS
$cshowList :: [ListSecurityProfilePermissionsResponse] -> ShowS
show :: ListSecurityProfilePermissionsResponse -> String
$cshow :: ListSecurityProfilePermissionsResponse -> String
showsPrec :: Int -> ListSecurityProfilePermissionsResponse -> ShowS
$cshowsPrec :: Int -> ListSecurityProfilePermissionsResponse -> ShowS
Prelude.Show, forall x.
Rep ListSecurityProfilePermissionsResponse x
-> ListSecurityProfilePermissionsResponse
forall x.
ListSecurityProfilePermissionsResponse
-> Rep ListSecurityProfilePermissionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListSecurityProfilePermissionsResponse x
-> ListSecurityProfilePermissionsResponse
$cfrom :: forall x.
ListSecurityProfilePermissionsResponse
-> Rep ListSecurityProfilePermissionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListSecurityProfilePermissionsResponse' 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:
--
-- 'nextToken', 'listSecurityProfilePermissionsResponse_nextToken' - If there are additional results, this is the token for the next set of
-- results.
--
-- 'permissions', 'listSecurityProfilePermissionsResponse_permissions' - The permissions granted to the security profile. For a complete list of
-- valid permissions, see
-- <https://docs.aws.amazon.com/connect/latest/adminguide/security-profile-list.html List of security profile permissions>.
--
-- 'httpStatus', 'listSecurityProfilePermissionsResponse_httpStatus' - The response's http status code.
newListSecurityProfilePermissionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListSecurityProfilePermissionsResponse
newListSecurityProfilePermissionsResponse :: Int -> ListSecurityProfilePermissionsResponse
newListSecurityProfilePermissionsResponse
  Int
pHttpStatus_ =
    ListSecurityProfilePermissionsResponse'
      { $sel:nextToken:ListSecurityProfilePermissionsResponse' :: Maybe Text
nextToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:permissions:ListSecurityProfilePermissionsResponse' :: Maybe [Text]
permissions = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:ListSecurityProfilePermissionsResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

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

-- | The permissions granted to the security profile. For a complete list of
-- valid permissions, see
-- <https://docs.aws.amazon.com/connect/latest/adminguide/security-profile-list.html List of security profile permissions>.
listSecurityProfilePermissionsResponse_permissions :: Lens.Lens' ListSecurityProfilePermissionsResponse (Prelude.Maybe [Prelude.Text])
listSecurityProfilePermissionsResponse_permissions :: Lens' ListSecurityProfilePermissionsResponse (Maybe [Text])
listSecurityProfilePermissionsResponse_permissions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSecurityProfilePermissionsResponse' {Maybe [Text]
permissions :: Maybe [Text]
$sel:permissions:ListSecurityProfilePermissionsResponse' :: ListSecurityProfilePermissionsResponse -> Maybe [Text]
permissions} -> Maybe [Text]
permissions) (\s :: ListSecurityProfilePermissionsResponse
s@ListSecurityProfilePermissionsResponse' {} Maybe [Text]
a -> ListSecurityProfilePermissionsResponse
s {$sel:permissions:ListSecurityProfilePermissionsResponse' :: Maybe [Text]
permissions = Maybe [Text]
a} :: ListSecurityProfilePermissionsResponse) 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.
listSecurityProfilePermissionsResponse_httpStatus :: Lens.Lens' ListSecurityProfilePermissionsResponse Prelude.Int
listSecurityProfilePermissionsResponse_httpStatus :: Lens' ListSecurityProfilePermissionsResponse Int
listSecurityProfilePermissionsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSecurityProfilePermissionsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListSecurityProfilePermissionsResponse' :: ListSecurityProfilePermissionsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListSecurityProfilePermissionsResponse
s@ListSecurityProfilePermissionsResponse' {} Int
a -> ListSecurityProfilePermissionsResponse
s {$sel:httpStatus:ListSecurityProfilePermissionsResponse' :: Int
httpStatus = Int
a} :: ListSecurityProfilePermissionsResponse)

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