{-# 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.ListPermissions
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves a list of available RAM permissions that you can use for the
-- supported resource types.
module Amazonka.RAM.ListPermissions
  ( -- * Creating a Request
    ListPermissions (..),
    newListPermissions,

    -- * Request Lenses
    listPermissions_maxResults,
    listPermissions_nextToken,
    listPermissions_resourceType,

    -- * Destructuring the Response
    ListPermissionsResponse (..),
    newListPermissionsResponse,

    -- * Response Lenses
    listPermissionsResponse_nextToken,
    listPermissionsResponse_permissions,
    listPermissionsResponse_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:/ 'newListPermissions' smart constructor.
data ListPermissions = ListPermissions'
  { -- | 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.
    ListPermissions -> 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.
    ListPermissions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Specifies that you want to list permissions for only the specified
    -- resource type. For example, to list only permissions that apply to EC2
    -- subnets, specify @ec2:Subnet@. You can use the ListResourceTypes
    -- operation to get the specific string required.
    ListPermissions -> Maybe Text
resourceType :: Prelude.Maybe Prelude.Text
  }
  deriving (ListPermissions -> ListPermissions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPermissions -> ListPermissions -> Bool
$c/= :: ListPermissions -> ListPermissions -> Bool
== :: ListPermissions -> ListPermissions -> Bool
$c== :: ListPermissions -> ListPermissions -> Bool
Prelude.Eq, ReadPrec [ListPermissions]
ReadPrec ListPermissions
Int -> ReadS ListPermissions
ReadS [ListPermissions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPermissions]
$creadListPrec :: ReadPrec [ListPermissions]
readPrec :: ReadPrec ListPermissions
$creadPrec :: ReadPrec ListPermissions
readList :: ReadS [ListPermissions]
$creadList :: ReadS [ListPermissions]
readsPrec :: Int -> ReadS ListPermissions
$creadsPrec :: Int -> ReadS ListPermissions
Prelude.Read, Int -> ListPermissions -> ShowS
[ListPermissions] -> ShowS
ListPermissions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPermissions] -> ShowS
$cshowList :: [ListPermissions] -> ShowS
show :: ListPermissions -> String
$cshow :: ListPermissions -> String
showsPrec :: Int -> ListPermissions -> ShowS
$cshowsPrec :: Int -> ListPermissions -> ShowS
Prelude.Show, forall x. Rep ListPermissions x -> ListPermissions
forall x. ListPermissions -> Rep ListPermissions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListPermissions x -> ListPermissions
$cfrom :: forall x. ListPermissions -> Rep ListPermissions x
Prelude.Generic)

-- |
-- Create a value of 'ListPermissions' 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', 'listPermissions_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', 'listPermissions_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.
--
-- 'resourceType', 'listPermissions_resourceType' - Specifies that you want to list permissions for only the specified
-- resource type. For example, to list only permissions that apply to EC2
-- subnets, specify @ec2:Subnet@. You can use the ListResourceTypes
-- operation to get the specific string required.
newListPermissions ::
  ListPermissions
newListPermissions :: ListPermissions
newListPermissions =
  ListPermissions'
    { $sel:maxResults:ListPermissions' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListPermissions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceType:ListPermissions' :: Maybe Text
resourceType = forall a. Maybe a
Prelude.Nothing
    }

-- | 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.
listPermissions_maxResults :: Lens.Lens' ListPermissions (Prelude.Maybe Prelude.Natural)
listPermissions_maxResults :: Lens' ListPermissions (Maybe Natural)
listPermissions_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPermissions' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListPermissions' :: ListPermissions -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListPermissions
s@ListPermissions' {} Maybe Natural
a -> ListPermissions
s {$sel:maxResults:ListPermissions' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListPermissions)

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

-- | Specifies that you want to list permissions for only the specified
-- resource type. For example, to list only permissions that apply to EC2
-- subnets, specify @ec2:Subnet@. You can use the ListResourceTypes
-- operation to get the specific string required.
listPermissions_resourceType :: Lens.Lens' ListPermissions (Prelude.Maybe Prelude.Text)
listPermissions_resourceType :: Lens' ListPermissions (Maybe Text)
listPermissions_resourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPermissions' {Maybe Text
resourceType :: Maybe Text
$sel:resourceType:ListPermissions' :: ListPermissions -> Maybe Text
resourceType} -> Maybe Text
resourceType) (\s :: ListPermissions
s@ListPermissions' {} Maybe Text
a -> ListPermissions
s {$sel:resourceType:ListPermissions' :: Maybe Text
resourceType = Maybe Text
a} :: ListPermissions)

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

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

instance Data.ToHeaders ListPermissions where
  toHeaders :: ListPermissions -> 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 ListPermissions where
  toJSON :: ListPermissions -> Value
toJSON ListPermissions' {Maybe Natural
Maybe Text
resourceType :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceType:ListPermissions' :: ListPermissions -> Maybe Text
$sel:nextToken:ListPermissions' :: ListPermissions -> Maybe Text
$sel:maxResults:ListPermissions' :: ListPermissions -> 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
"resourceType" 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
resourceType
          ]
      )

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

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

-- | /See:/ 'newListPermissionsResponse' smart constructor.
data ListPermissionsResponse = ListPermissionsResponse'
  { -- | 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.
    ListPermissionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An array of objects with information about the permissions.
    ListPermissionsResponse -> Maybe [ResourceSharePermissionSummary]
permissions :: Prelude.Maybe [ResourceSharePermissionSummary],
    -- | The response's http status code.
    ListPermissionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListPermissionsResponse -> ListPermissionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPermissionsResponse -> ListPermissionsResponse -> Bool
$c/= :: ListPermissionsResponse -> ListPermissionsResponse -> Bool
== :: ListPermissionsResponse -> ListPermissionsResponse -> Bool
$c== :: ListPermissionsResponse -> ListPermissionsResponse -> Bool
Prelude.Eq, ReadPrec [ListPermissionsResponse]
ReadPrec ListPermissionsResponse
Int -> ReadS ListPermissionsResponse
ReadS [ListPermissionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPermissionsResponse]
$creadListPrec :: ReadPrec [ListPermissionsResponse]
readPrec :: ReadPrec ListPermissionsResponse
$creadPrec :: ReadPrec ListPermissionsResponse
readList :: ReadS [ListPermissionsResponse]
$creadList :: ReadS [ListPermissionsResponse]
readsPrec :: Int -> ReadS ListPermissionsResponse
$creadsPrec :: Int -> ReadS ListPermissionsResponse
Prelude.Read, Int -> ListPermissionsResponse -> ShowS
[ListPermissionsResponse] -> ShowS
ListPermissionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPermissionsResponse] -> ShowS
$cshowList :: [ListPermissionsResponse] -> ShowS
show :: ListPermissionsResponse -> String
$cshow :: ListPermissionsResponse -> String
showsPrec :: Int -> ListPermissionsResponse -> ShowS
$cshowsPrec :: Int -> ListPermissionsResponse -> ShowS
Prelude.Show, forall x. Rep ListPermissionsResponse x -> ListPermissionsResponse
forall x. ListPermissionsResponse -> Rep ListPermissionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListPermissionsResponse x -> ListPermissionsResponse
$cfrom :: forall x. ListPermissionsResponse -> Rep ListPermissionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListPermissionsResponse' 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', 'listPermissionsResponse_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', 'listPermissionsResponse_permissions' - An array of objects with information about the permissions.
--
-- 'httpStatus', 'listPermissionsResponse_httpStatus' - The response's http status code.
newListPermissionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListPermissionsResponse
newListPermissionsResponse :: Int -> ListPermissionsResponse
newListPermissionsResponse Int
pHttpStatus_ =
  ListPermissionsResponse'
    { $sel:nextToken:ListPermissionsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:permissions:ListPermissionsResponse' :: Maybe [ResourceSharePermissionSummary]
permissions = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListPermissionsResponse' :: 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.
listPermissionsResponse_nextToken :: Lens.Lens' ListPermissionsResponse (Prelude.Maybe Prelude.Text)
listPermissionsResponse_nextToken :: Lens' ListPermissionsResponse (Maybe Text)
listPermissionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPermissionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListPermissionsResponse' :: ListPermissionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListPermissionsResponse
s@ListPermissionsResponse' {} Maybe Text
a -> ListPermissionsResponse
s {$sel:nextToken:ListPermissionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListPermissionsResponse)

-- | An array of objects with information about the permissions.
listPermissionsResponse_permissions :: Lens.Lens' ListPermissionsResponse (Prelude.Maybe [ResourceSharePermissionSummary])
listPermissionsResponse_permissions :: Lens'
  ListPermissionsResponse (Maybe [ResourceSharePermissionSummary])
listPermissionsResponse_permissions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPermissionsResponse' {Maybe [ResourceSharePermissionSummary]
permissions :: Maybe [ResourceSharePermissionSummary]
$sel:permissions:ListPermissionsResponse' :: ListPermissionsResponse -> Maybe [ResourceSharePermissionSummary]
permissions} -> Maybe [ResourceSharePermissionSummary]
permissions) (\s :: ListPermissionsResponse
s@ListPermissionsResponse' {} Maybe [ResourceSharePermissionSummary]
a -> ListPermissionsResponse
s {$sel:permissions:ListPermissionsResponse' :: Maybe [ResourceSharePermissionSummary]
permissions = Maybe [ResourceSharePermissionSummary]
a} :: ListPermissionsResponse) 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.
listPermissionsResponse_httpStatus :: Lens.Lens' ListPermissionsResponse Prelude.Int
listPermissionsResponse_httpStatus :: Lens' ListPermissionsResponse Int
listPermissionsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPermissionsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListPermissionsResponse' :: ListPermissionsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListPermissionsResponse
s@ListPermissionsResponse' {} Int
a -> ListPermissionsResponse
s {$sel:httpStatus:ListPermissionsResponse' :: Int
httpStatus = Int
a} :: ListPermissionsResponse)

instance Prelude.NFData ListPermissionsResponse where
  rnf :: ListPermissionsResponse -> ()
rnf ListPermissionsResponse' {Int
Maybe [ResourceSharePermissionSummary]
Maybe Text
httpStatus :: Int
permissions :: Maybe [ResourceSharePermissionSummary]
nextToken :: Maybe Text
$sel:httpStatus:ListPermissionsResponse' :: ListPermissionsResponse -> Int
$sel:permissions:ListPermissionsResponse' :: ListPermissionsResponse -> Maybe [ResourceSharePermissionSummary]
$sel:nextToken:ListPermissionsResponse' :: ListPermissionsResponse -> 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