{-# 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.ListPermissionVersions
-- 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 available versions of the specified RAM permission.
module Amazonka.RAM.ListPermissionVersions
  ( -- * Creating a Request
    ListPermissionVersions (..),
    newListPermissionVersions,

    -- * Request Lenses
    listPermissionVersions_maxResults,
    listPermissionVersions_nextToken,
    listPermissionVersions_permissionArn,

    -- * Destructuring the Response
    ListPermissionVersionsResponse (..),
    newListPermissionVersionsResponse,

    -- * Response Lenses
    listPermissionVersionsResponse_nextToken,
    listPermissionVersionsResponse_permissions,
    listPermissionVersionsResponse_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:/ 'newListPermissionVersions' smart constructor.
data ListPermissionVersions = ListPermissionVersions'
  { -- | 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.
    ListPermissionVersions -> 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.
    ListPermissionVersions -> 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 RAM permission whose versions you want to list. You can use the
    -- @permissionVersion@ parameter on the AssociateResourceSharePermission
    -- operation to specify a non-default version to attach.
    ListPermissionVersions -> Text
permissionArn :: Prelude.Text
  }
  deriving (ListPermissionVersions -> ListPermissionVersions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPermissionVersions -> ListPermissionVersions -> Bool
$c/= :: ListPermissionVersions -> ListPermissionVersions -> Bool
== :: ListPermissionVersions -> ListPermissionVersions -> Bool
$c== :: ListPermissionVersions -> ListPermissionVersions -> Bool
Prelude.Eq, ReadPrec [ListPermissionVersions]
ReadPrec ListPermissionVersions
Int -> ReadS ListPermissionVersions
ReadS [ListPermissionVersions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPermissionVersions]
$creadListPrec :: ReadPrec [ListPermissionVersions]
readPrec :: ReadPrec ListPermissionVersions
$creadPrec :: ReadPrec ListPermissionVersions
readList :: ReadS [ListPermissionVersions]
$creadList :: ReadS [ListPermissionVersions]
readsPrec :: Int -> ReadS ListPermissionVersions
$creadsPrec :: Int -> ReadS ListPermissionVersions
Prelude.Read, Int -> ListPermissionVersions -> ShowS
[ListPermissionVersions] -> ShowS
ListPermissionVersions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPermissionVersions] -> ShowS
$cshowList :: [ListPermissionVersions] -> ShowS
show :: ListPermissionVersions -> String
$cshow :: ListPermissionVersions -> String
showsPrec :: Int -> ListPermissionVersions -> ShowS
$cshowsPrec :: Int -> ListPermissionVersions -> ShowS
Prelude.Show, forall x. Rep ListPermissionVersions x -> ListPermissionVersions
forall x. ListPermissionVersions -> Rep ListPermissionVersions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListPermissionVersions x -> ListPermissionVersions
$cfrom :: forall x. ListPermissionVersions -> Rep ListPermissionVersions x
Prelude.Generic)

-- |
-- Create a value of 'ListPermissionVersions' 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', 'listPermissionVersions_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', 'listPermissionVersions_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.
--
-- 'permissionArn', 'listPermissionVersions_permissionArn' - Specifies the
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
-- of the RAM permission whose versions you want to list. You can use the
-- @permissionVersion@ parameter on the AssociateResourceSharePermission
-- operation to specify a non-default version to attach.
newListPermissionVersions ::
  -- | 'permissionArn'
  Prelude.Text ->
  ListPermissionVersions
newListPermissionVersions :: Text -> ListPermissionVersions
newListPermissionVersions Text
pPermissionArn_ =
  ListPermissionVersions'
    { $sel:maxResults:ListPermissionVersions' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListPermissionVersions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:permissionArn:ListPermissionVersions' :: Text
permissionArn = Text
pPermissionArn_
    }

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

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

-- | Specifies the
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
-- of the RAM permission whose versions you want to list. You can use the
-- @permissionVersion@ parameter on the AssociateResourceSharePermission
-- operation to specify a non-default version to attach.
listPermissionVersions_permissionArn :: Lens.Lens' ListPermissionVersions Prelude.Text
listPermissionVersions_permissionArn :: Lens' ListPermissionVersions Text
listPermissionVersions_permissionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPermissionVersions' {Text
permissionArn :: Text
$sel:permissionArn:ListPermissionVersions' :: ListPermissionVersions -> Text
permissionArn} -> Text
permissionArn) (\s :: ListPermissionVersions
s@ListPermissionVersions' {} Text
a -> ListPermissionVersions
s {$sel:permissionArn:ListPermissionVersions' :: Text
permissionArn = Text
a} :: ListPermissionVersions)

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

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

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

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

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

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

-- |
-- Create a value of 'ListPermissionVersionsResponse' 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', 'listPermissionVersionsResponse_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', 'listPermissionVersionsResponse_permissions' - An array of objects that contain details for each of the available
-- versions.
--
-- 'httpStatus', 'listPermissionVersionsResponse_httpStatus' - The response's http status code.
newListPermissionVersionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListPermissionVersionsResponse
newListPermissionVersionsResponse :: Int -> ListPermissionVersionsResponse
newListPermissionVersionsResponse Int
pHttpStatus_ =
  ListPermissionVersionsResponse'
    { $sel:nextToken:ListPermissionVersionsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:permissions:ListPermissionVersionsResponse' :: Maybe [ResourceSharePermissionSummary]
permissions = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListPermissionVersionsResponse' :: 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.
listPermissionVersionsResponse_nextToken :: Lens.Lens' ListPermissionVersionsResponse (Prelude.Maybe Prelude.Text)
listPermissionVersionsResponse_nextToken :: Lens' ListPermissionVersionsResponse (Maybe Text)
listPermissionVersionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPermissionVersionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListPermissionVersionsResponse' :: ListPermissionVersionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListPermissionVersionsResponse
s@ListPermissionVersionsResponse' {} Maybe Text
a -> ListPermissionVersionsResponse
s {$sel:nextToken:ListPermissionVersionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListPermissionVersionsResponse)

-- | An array of objects that contain details for each of the available
-- versions.
listPermissionVersionsResponse_permissions :: Lens.Lens' ListPermissionVersionsResponse (Prelude.Maybe [ResourceSharePermissionSummary])
listPermissionVersionsResponse_permissions :: Lens'
  ListPermissionVersionsResponse
  (Maybe [ResourceSharePermissionSummary])
listPermissionVersionsResponse_permissions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPermissionVersionsResponse' {Maybe [ResourceSharePermissionSummary]
permissions :: Maybe [ResourceSharePermissionSummary]
$sel:permissions:ListPermissionVersionsResponse' :: ListPermissionVersionsResponse
-> Maybe [ResourceSharePermissionSummary]
permissions} -> Maybe [ResourceSharePermissionSummary]
permissions) (\s :: ListPermissionVersionsResponse
s@ListPermissionVersionsResponse' {} Maybe [ResourceSharePermissionSummary]
a -> ListPermissionVersionsResponse
s {$sel:permissions:ListPermissionVersionsResponse' :: Maybe [ResourceSharePermissionSummary]
permissions = Maybe [ResourceSharePermissionSummary]
a} :: ListPermissionVersionsResponse) 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.
listPermissionVersionsResponse_httpStatus :: Lens.Lens' ListPermissionVersionsResponse Prelude.Int
listPermissionVersionsResponse_httpStatus :: Lens' ListPermissionVersionsResponse Int
listPermissionVersionsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPermissionVersionsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListPermissionVersionsResponse' :: ListPermissionVersionsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListPermissionVersionsResponse
s@ListPermissionVersionsResponse' {} Int
a -> ListPermissionVersionsResponse
s {$sel:httpStatus:ListPermissionVersionsResponse' :: Int
httpStatus = Int
a} :: ListPermissionVersionsResponse)

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