{-# 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.RAM.ListResourceSharePermissions
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists the RAM permissions that are associated with a resource share.
module Amazonka.RAM.ListResourceSharePermissions
  ( -- * Creating a Request
    ListResourceSharePermissions (..),
    newListResourceSharePermissions,

    -- * Request Lenses
    listResourceSharePermissions_maxResults,
    listResourceSharePermissions_nextToken,
    listResourceSharePermissions_resourceShareArn,

    -- * Destructuring the Response
    ListResourceSharePermissionsResponse (..),
    newListResourceSharePermissionsResponse,

    -- * Response Lenses
    listResourceSharePermissionsResponse_nextToken,
    listResourceSharePermissionsResponse_permissions,
    listResourceSharePermissionsResponse_httpStatus,
  )
where

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 Amazonka.RAM.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListResourceSharePermissions' smart constructor.
data ListResourceSharePermissions = ListResourceSharePermissions'
  { -- | Specifies the total number of results that you want included on each
    -- page of the response. If you do not include this parameter, it defaults
    -- to a value that is specific to the operation. If additional items exist
    -- beyond the number you specify, the @NextToken@ response element is
    -- returned with a value (not null). Include the specified value as the
    -- @NextToken@ request parameter in the next call to the operation to get
    -- the next part of the results. Note that the service might return fewer
    -- results than the maximum even when there are more results available. You
    -- should check @NextToken@ after every operation to ensure that you
    -- receive all of the results.
    ListResourceSharePermissions -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | Specifies that you want to receive the next page of results. Valid only
    -- if you received a @NextToken@ response in the previous request. If you
    -- did, it indicates that more output is available. Set this parameter to
    -- the value provided by the previous call\'s @NextToken@ response to
    -- request the next page of results.
    ListResourceSharePermissions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Specifies the
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
    -- of the resource share for which you want to retrieve the associated
    -- permissions.
    ListResourceSharePermissions -> Text
resourceShareArn :: Prelude.Text
  }
  deriving (ListResourceSharePermissions
-> ListResourceSharePermissions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListResourceSharePermissions
-> ListResourceSharePermissions -> Bool
$c/= :: ListResourceSharePermissions
-> ListResourceSharePermissions -> Bool
== :: ListResourceSharePermissions
-> ListResourceSharePermissions -> Bool
$c== :: ListResourceSharePermissions
-> ListResourceSharePermissions -> Bool
Prelude.Eq, ReadPrec [ListResourceSharePermissions]
ReadPrec ListResourceSharePermissions
Int -> ReadS ListResourceSharePermissions
ReadS [ListResourceSharePermissions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListResourceSharePermissions]
$creadListPrec :: ReadPrec [ListResourceSharePermissions]
readPrec :: ReadPrec ListResourceSharePermissions
$creadPrec :: ReadPrec ListResourceSharePermissions
readList :: ReadS [ListResourceSharePermissions]
$creadList :: ReadS [ListResourceSharePermissions]
readsPrec :: Int -> ReadS ListResourceSharePermissions
$creadsPrec :: Int -> ReadS ListResourceSharePermissions
Prelude.Read, Int -> ListResourceSharePermissions -> ShowS
[ListResourceSharePermissions] -> ShowS
ListResourceSharePermissions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListResourceSharePermissions] -> ShowS
$cshowList :: [ListResourceSharePermissions] -> ShowS
show :: ListResourceSharePermissions -> String
$cshow :: ListResourceSharePermissions -> String
showsPrec :: Int -> ListResourceSharePermissions -> ShowS
$cshowsPrec :: Int -> ListResourceSharePermissions -> ShowS
Prelude.Show, forall x.
Rep ListResourceSharePermissions x -> ListResourceSharePermissions
forall x.
ListResourceSharePermissions -> Rep ListResourceSharePermissions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListResourceSharePermissions x -> ListResourceSharePermissions
$cfrom :: forall x.
ListResourceSharePermissions -> Rep ListResourceSharePermissions x
Prelude.Generic)

-- |
-- Create a value of 'ListResourceSharePermissions' 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', 'listResourceSharePermissions_maxResults' - Specifies the total number of results that you want included on each
-- page of the response. If you do not include this parameter, it defaults
-- to a value that is specific to the operation. If additional items exist
-- beyond the number you specify, the @NextToken@ response element is
-- returned with a value (not null). Include the specified value as the
-- @NextToken@ request parameter in the next call to the operation to get
-- the next part of the results. Note that the service might return fewer
-- results than the maximum even when there are more results available. You
-- should check @NextToken@ after every operation to ensure that you
-- receive all of the results.
--
-- 'nextToken', 'listResourceSharePermissions_nextToken' - Specifies that you want to receive the next page of results. Valid only
-- if you received a @NextToken@ response in the previous request. If you
-- did, it indicates that more output is available. Set this parameter to
-- the value provided by the previous call\'s @NextToken@ response to
-- request the next page of results.
--
-- 'resourceShareArn', 'listResourceSharePermissions_resourceShareArn' - Specifies the
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
-- of the resource share for which you want to retrieve the associated
-- permissions.
newListResourceSharePermissions ::
  -- | 'resourceShareArn'
  Prelude.Text ->
  ListResourceSharePermissions
newListResourceSharePermissions :: Text -> ListResourceSharePermissions
newListResourceSharePermissions Text
pResourceShareArn_ =
  ListResourceSharePermissions'
    { $sel:maxResults:ListResourceSharePermissions' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListResourceSharePermissions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceShareArn:ListResourceSharePermissions' :: Text
resourceShareArn = Text
pResourceShareArn_
    }

-- | Specifies the total number of results that you want included on each
-- page of the response. If you do not include this parameter, it defaults
-- to a value that is specific to the operation. If additional items exist
-- beyond the number you specify, the @NextToken@ response element is
-- returned with a value (not null). Include the specified value as the
-- @NextToken@ request parameter in the next call to the operation to get
-- the next part of the results. Note that the service might return fewer
-- results than the maximum even when there are more results available. You
-- should check @NextToken@ after every operation to ensure that you
-- receive all of the results.
listResourceSharePermissions_maxResults :: Lens.Lens' ListResourceSharePermissions (Prelude.Maybe Prelude.Natural)
listResourceSharePermissions_maxResults :: Lens' ListResourceSharePermissions (Maybe Natural)
listResourceSharePermissions_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceSharePermissions' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListResourceSharePermissions' :: ListResourceSharePermissions -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListResourceSharePermissions
s@ListResourceSharePermissions' {} Maybe Natural
a -> ListResourceSharePermissions
s {$sel:maxResults:ListResourceSharePermissions' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListResourceSharePermissions)

-- | Specifies that you want to receive the next page of results. Valid only
-- if you received a @NextToken@ response in the previous request. If you
-- did, it indicates that more output is available. Set this parameter to
-- the value provided by the previous call\'s @NextToken@ response to
-- request the next page of results.
listResourceSharePermissions_nextToken :: Lens.Lens' ListResourceSharePermissions (Prelude.Maybe Prelude.Text)
listResourceSharePermissions_nextToken :: Lens' ListResourceSharePermissions (Maybe Text)
listResourceSharePermissions_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceSharePermissions' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListResourceSharePermissions' :: ListResourceSharePermissions -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListResourceSharePermissions
s@ListResourceSharePermissions' {} Maybe Text
a -> ListResourceSharePermissions
s {$sel:nextToken:ListResourceSharePermissions' :: Maybe Text
nextToken = Maybe Text
a} :: ListResourceSharePermissions)

-- | Specifies the
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
-- of the resource share for which you want to retrieve the associated
-- permissions.
listResourceSharePermissions_resourceShareArn :: Lens.Lens' ListResourceSharePermissions Prelude.Text
listResourceSharePermissions_resourceShareArn :: Lens' ListResourceSharePermissions Text
listResourceSharePermissions_resourceShareArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceSharePermissions' {Text
resourceShareArn :: Text
$sel:resourceShareArn:ListResourceSharePermissions' :: ListResourceSharePermissions -> Text
resourceShareArn} -> Text
resourceShareArn) (\s :: ListResourceSharePermissions
s@ListResourceSharePermissions' {} Text
a -> ListResourceSharePermissions
s {$sel:resourceShareArn:ListResourceSharePermissions' :: Text
resourceShareArn = Text
a} :: ListResourceSharePermissions)

instance Core.AWSRequest ListResourceSharePermissions where
  type
    AWSResponse ListResourceSharePermissions =
      ListResourceSharePermissionsResponse
  request :: (Service -> Service)
-> ListResourceSharePermissions
-> Request ListResourceSharePermissions
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 ListResourceSharePermissions
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListResourceSharePermissions)))
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 [ResourceSharePermissionSummary]
-> Int
-> ListResourceSharePermissionsResponse
ListResourceSharePermissionsResponse'
            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
    ListResourceSharePermissions
  where
  hashWithSalt :: Int -> ListResourceSharePermissions -> Int
hashWithSalt Int
_salt ListResourceSharePermissions' {Maybe Natural
Maybe Text
Text
resourceShareArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceShareArn:ListResourceSharePermissions' :: ListResourceSharePermissions -> Text
$sel:nextToken:ListResourceSharePermissions' :: ListResourceSharePermissions -> Maybe Text
$sel:maxResults:ListResourceSharePermissions' :: ListResourceSharePermissions -> 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
resourceShareArn

instance Prelude.NFData ListResourceSharePermissions where
  rnf :: ListResourceSharePermissions -> ()
rnf ListResourceSharePermissions' {Maybe Natural
Maybe Text
Text
resourceShareArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceShareArn:ListResourceSharePermissions' :: ListResourceSharePermissions -> Text
$sel:nextToken:ListResourceSharePermissions' :: ListResourceSharePermissions -> Maybe Text
$sel:maxResults:ListResourceSharePermissions' :: ListResourceSharePermissions -> 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
resourceShareArn

instance Data.ToHeaders ListResourceSharePermissions where
  toHeaders :: ListResourceSharePermissions -> 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 ListResourceSharePermissions where
  toJSON :: ListResourceSharePermissions -> Value
toJSON ListResourceSharePermissions' {Maybe Natural
Maybe Text
Text
resourceShareArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceShareArn:ListResourceSharePermissions' :: ListResourceSharePermissions -> Text
$sel:nextToken:ListResourceSharePermissions' :: ListResourceSharePermissions -> Maybe Text
$sel:maxResults:ListResourceSharePermissions' :: ListResourceSharePermissions -> 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,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"resourceShareArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
resourceShareArn)
          ]
      )

instance Data.ToPath ListResourceSharePermissions where
  toPath :: ListResourceSharePermissions -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const ByteString
"/listresourcesharepermissions"

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

-- | /See:/ 'newListResourceSharePermissionsResponse' smart constructor.
data ListResourceSharePermissionsResponse = ListResourceSharePermissionsResponse'
  { -- | If present, this value indicates that more output is available than is
    -- included in the current response. Use this value in the @NextToken@
    -- request parameter in a subsequent call to the operation to get the next
    -- part of the output. You should repeat this until the @NextToken@
    -- response element comes back as @null@. This indicates that this is the
    -- last page of results.
    ListResourceSharePermissionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An array of objects that describe the permissions associated with the
    -- resource share.
    ListResourceSharePermissionsResponse
-> Maybe [ResourceSharePermissionSummary]
permissions :: Prelude.Maybe [ResourceSharePermissionSummary],
    -- | The response's http status code.
    ListResourceSharePermissionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListResourceSharePermissionsResponse
-> ListResourceSharePermissionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListResourceSharePermissionsResponse
-> ListResourceSharePermissionsResponse -> Bool
$c/= :: ListResourceSharePermissionsResponse
-> ListResourceSharePermissionsResponse -> Bool
== :: ListResourceSharePermissionsResponse
-> ListResourceSharePermissionsResponse -> Bool
$c== :: ListResourceSharePermissionsResponse
-> ListResourceSharePermissionsResponse -> Bool
Prelude.Eq, ReadPrec [ListResourceSharePermissionsResponse]
ReadPrec ListResourceSharePermissionsResponse
Int -> ReadS ListResourceSharePermissionsResponse
ReadS [ListResourceSharePermissionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListResourceSharePermissionsResponse]
$creadListPrec :: ReadPrec [ListResourceSharePermissionsResponse]
readPrec :: ReadPrec ListResourceSharePermissionsResponse
$creadPrec :: ReadPrec ListResourceSharePermissionsResponse
readList :: ReadS [ListResourceSharePermissionsResponse]
$creadList :: ReadS [ListResourceSharePermissionsResponse]
readsPrec :: Int -> ReadS ListResourceSharePermissionsResponse
$creadsPrec :: Int -> ReadS ListResourceSharePermissionsResponse
Prelude.Read, Int -> ListResourceSharePermissionsResponse -> ShowS
[ListResourceSharePermissionsResponse] -> ShowS
ListResourceSharePermissionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListResourceSharePermissionsResponse] -> ShowS
$cshowList :: [ListResourceSharePermissionsResponse] -> ShowS
show :: ListResourceSharePermissionsResponse -> String
$cshow :: ListResourceSharePermissionsResponse -> String
showsPrec :: Int -> ListResourceSharePermissionsResponse -> ShowS
$cshowsPrec :: Int -> ListResourceSharePermissionsResponse -> ShowS
Prelude.Show, forall x.
Rep ListResourceSharePermissionsResponse x
-> ListResourceSharePermissionsResponse
forall x.
ListResourceSharePermissionsResponse
-> Rep ListResourceSharePermissionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListResourceSharePermissionsResponse x
-> ListResourceSharePermissionsResponse
$cfrom :: forall x.
ListResourceSharePermissionsResponse
-> Rep ListResourceSharePermissionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListResourceSharePermissionsResponse' 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', 'listResourceSharePermissionsResponse_nextToken' - If present, this value indicates that more output is available than is
-- included in the current response. Use this value in the @NextToken@
-- request parameter in a subsequent call to the operation to get the next
-- part of the output. You should repeat this until the @NextToken@
-- response element comes back as @null@. This indicates that this is the
-- last page of results.
--
-- 'permissions', 'listResourceSharePermissionsResponse_permissions' - An array of objects that describe the permissions associated with the
-- resource share.
--
-- 'httpStatus', 'listResourceSharePermissionsResponse_httpStatus' - The response's http status code.
newListResourceSharePermissionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListResourceSharePermissionsResponse
newListResourceSharePermissionsResponse :: Int -> ListResourceSharePermissionsResponse
newListResourceSharePermissionsResponse Int
pHttpStatus_ =
  ListResourceSharePermissionsResponse'
    { $sel:nextToken:ListResourceSharePermissionsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:permissions:ListResourceSharePermissionsResponse' :: Maybe [ResourceSharePermissionSummary]
permissions = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListResourceSharePermissionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | If present, this value indicates that more output is available than is
-- included in the current response. Use this value in the @NextToken@
-- request parameter in a subsequent call to the operation to get the next
-- part of the output. You should repeat this until the @NextToken@
-- response element comes back as @null@. This indicates that this is the
-- last page of results.
listResourceSharePermissionsResponse_nextToken :: Lens.Lens' ListResourceSharePermissionsResponse (Prelude.Maybe Prelude.Text)
listResourceSharePermissionsResponse_nextToken :: Lens' ListResourceSharePermissionsResponse (Maybe Text)
listResourceSharePermissionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceSharePermissionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListResourceSharePermissionsResponse' :: ListResourceSharePermissionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListResourceSharePermissionsResponse
s@ListResourceSharePermissionsResponse' {} Maybe Text
a -> ListResourceSharePermissionsResponse
s {$sel:nextToken:ListResourceSharePermissionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListResourceSharePermissionsResponse)

-- | An array of objects that describe the permissions associated with the
-- resource share.
listResourceSharePermissionsResponse_permissions :: Lens.Lens' ListResourceSharePermissionsResponse (Prelude.Maybe [ResourceSharePermissionSummary])
listResourceSharePermissionsResponse_permissions :: Lens'
  ListResourceSharePermissionsResponse
  (Maybe [ResourceSharePermissionSummary])
listResourceSharePermissionsResponse_permissions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceSharePermissionsResponse' {Maybe [ResourceSharePermissionSummary]
permissions :: Maybe [ResourceSharePermissionSummary]
$sel:permissions:ListResourceSharePermissionsResponse' :: ListResourceSharePermissionsResponse
-> Maybe [ResourceSharePermissionSummary]
permissions} -> Maybe [ResourceSharePermissionSummary]
permissions) (\s :: ListResourceSharePermissionsResponse
s@ListResourceSharePermissionsResponse' {} Maybe [ResourceSharePermissionSummary]
a -> ListResourceSharePermissionsResponse
s {$sel:permissions:ListResourceSharePermissionsResponse' :: Maybe [ResourceSharePermissionSummary]
permissions = Maybe [ResourceSharePermissionSummary]
a} :: ListResourceSharePermissionsResponse) 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.
listResourceSharePermissionsResponse_httpStatus :: Lens.Lens' ListResourceSharePermissionsResponse Prelude.Int
listResourceSharePermissionsResponse_httpStatus :: Lens' ListResourceSharePermissionsResponse Int
listResourceSharePermissionsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListResourceSharePermissionsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListResourceSharePermissionsResponse' :: ListResourceSharePermissionsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListResourceSharePermissionsResponse
s@ListResourceSharePermissionsResponse' {} Int
a -> ListResourceSharePermissionsResponse
s {$sel:httpStatus:ListResourceSharePermissionsResponse' :: Int
httpStatus = Int
a} :: ListResourceSharePermissionsResponse)

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