{-# 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.LicenseManager.ListDistributedGrants
-- 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 grants distributed for the specified license.
module Amazonka.LicenseManager.ListDistributedGrants
  ( -- * Creating a Request
    ListDistributedGrants (..),
    newListDistributedGrants,

    -- * Request Lenses
    listDistributedGrants_filters,
    listDistributedGrants_grantArns,
    listDistributedGrants_maxResults,
    listDistributedGrants_nextToken,

    -- * Destructuring the Response
    ListDistributedGrantsResponse (..),
    newListDistributedGrantsResponse,

    -- * Response Lenses
    listDistributedGrantsResponse_grants,
    listDistributedGrantsResponse_nextToken,
    listDistributedGrantsResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.LicenseManager.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListDistributedGrants' smart constructor.
data ListDistributedGrants = ListDistributedGrants'
  { -- | Filters to scope the results. The following filters are supported:
    --
    -- -   @LicenseArn@
    --
    -- -   @GrantStatus@
    --
    -- -   @GranteePrincipalARN@
    --
    -- -   @ProductSKU@
    --
    -- -   @LicenseIssuerName@
    ListDistributedGrants -> Maybe [Filter]
filters :: Prelude.Maybe [Filter],
    -- | Amazon Resource Names (ARNs) of the grants.
    ListDistributedGrants -> Maybe [Text]
grantArns :: Prelude.Maybe [Prelude.Text],
    -- | Maximum number of results to return in a single call.
    ListDistributedGrants -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | Token for the next set of results.
    ListDistributedGrants -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListDistributedGrants -> ListDistributedGrants -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListDistributedGrants -> ListDistributedGrants -> Bool
$c/= :: ListDistributedGrants -> ListDistributedGrants -> Bool
== :: ListDistributedGrants -> ListDistributedGrants -> Bool
$c== :: ListDistributedGrants -> ListDistributedGrants -> Bool
Prelude.Eq, ReadPrec [ListDistributedGrants]
ReadPrec ListDistributedGrants
Int -> ReadS ListDistributedGrants
ReadS [ListDistributedGrants]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListDistributedGrants]
$creadListPrec :: ReadPrec [ListDistributedGrants]
readPrec :: ReadPrec ListDistributedGrants
$creadPrec :: ReadPrec ListDistributedGrants
readList :: ReadS [ListDistributedGrants]
$creadList :: ReadS [ListDistributedGrants]
readsPrec :: Int -> ReadS ListDistributedGrants
$creadsPrec :: Int -> ReadS ListDistributedGrants
Prelude.Read, Int -> ListDistributedGrants -> ShowS
[ListDistributedGrants] -> ShowS
ListDistributedGrants -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListDistributedGrants] -> ShowS
$cshowList :: [ListDistributedGrants] -> ShowS
show :: ListDistributedGrants -> String
$cshow :: ListDistributedGrants -> String
showsPrec :: Int -> ListDistributedGrants -> ShowS
$cshowsPrec :: Int -> ListDistributedGrants -> ShowS
Prelude.Show, forall x. Rep ListDistributedGrants x -> ListDistributedGrants
forall x. ListDistributedGrants -> Rep ListDistributedGrants x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListDistributedGrants x -> ListDistributedGrants
$cfrom :: forall x. ListDistributedGrants -> Rep ListDistributedGrants x
Prelude.Generic)

-- |
-- Create a value of 'ListDistributedGrants' 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:
--
-- 'filters', 'listDistributedGrants_filters' - Filters to scope the results. The following filters are supported:
--
-- -   @LicenseArn@
--
-- -   @GrantStatus@
--
-- -   @GranteePrincipalARN@
--
-- -   @ProductSKU@
--
-- -   @LicenseIssuerName@
--
-- 'grantArns', 'listDistributedGrants_grantArns' - Amazon Resource Names (ARNs) of the grants.
--
-- 'maxResults', 'listDistributedGrants_maxResults' - Maximum number of results to return in a single call.
--
-- 'nextToken', 'listDistributedGrants_nextToken' - Token for the next set of results.
newListDistributedGrants ::
  ListDistributedGrants
newListDistributedGrants :: ListDistributedGrants
newListDistributedGrants =
  ListDistributedGrants'
    { $sel:filters:ListDistributedGrants' :: Maybe [Filter]
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:grantArns:ListDistributedGrants' :: Maybe [Text]
grantArns = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListDistributedGrants' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListDistributedGrants' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | Filters to scope the results. The following filters are supported:
--
-- -   @LicenseArn@
--
-- -   @GrantStatus@
--
-- -   @GranteePrincipalARN@
--
-- -   @ProductSKU@
--
-- -   @LicenseIssuerName@
listDistributedGrants_filters :: Lens.Lens' ListDistributedGrants (Prelude.Maybe [Filter])
listDistributedGrants_filters :: Lens' ListDistributedGrants (Maybe [Filter])
listDistributedGrants_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDistributedGrants' {Maybe [Filter]
filters :: Maybe [Filter]
$sel:filters:ListDistributedGrants' :: ListDistributedGrants -> Maybe [Filter]
filters} -> Maybe [Filter]
filters) (\s :: ListDistributedGrants
s@ListDistributedGrants' {} Maybe [Filter]
a -> ListDistributedGrants
s {$sel:filters:ListDistributedGrants' :: Maybe [Filter]
filters = Maybe [Filter]
a} :: ListDistributedGrants) 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

-- | Amazon Resource Names (ARNs) of the grants.
listDistributedGrants_grantArns :: Lens.Lens' ListDistributedGrants (Prelude.Maybe [Prelude.Text])
listDistributedGrants_grantArns :: Lens' ListDistributedGrants (Maybe [Text])
listDistributedGrants_grantArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDistributedGrants' {Maybe [Text]
grantArns :: Maybe [Text]
$sel:grantArns:ListDistributedGrants' :: ListDistributedGrants -> Maybe [Text]
grantArns} -> Maybe [Text]
grantArns) (\s :: ListDistributedGrants
s@ListDistributedGrants' {} Maybe [Text]
a -> ListDistributedGrants
s {$sel:grantArns:ListDistributedGrants' :: Maybe [Text]
grantArns = Maybe [Text]
a} :: ListDistributedGrants) 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

-- | Maximum number of results to return in a single call.
listDistributedGrants_maxResults :: Lens.Lens' ListDistributedGrants (Prelude.Maybe Prelude.Natural)
listDistributedGrants_maxResults :: Lens' ListDistributedGrants (Maybe Natural)
listDistributedGrants_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDistributedGrants' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListDistributedGrants' :: ListDistributedGrants -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListDistributedGrants
s@ListDistributedGrants' {} Maybe Natural
a -> ListDistributedGrants
s {$sel:maxResults:ListDistributedGrants' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListDistributedGrants)

-- | Token for the next set of results.
listDistributedGrants_nextToken :: Lens.Lens' ListDistributedGrants (Prelude.Maybe Prelude.Text)
listDistributedGrants_nextToken :: Lens' ListDistributedGrants (Maybe Text)
listDistributedGrants_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDistributedGrants' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListDistributedGrants' :: ListDistributedGrants -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListDistributedGrants
s@ListDistributedGrants' {} Maybe Text
a -> ListDistributedGrants
s {$sel:nextToken:ListDistributedGrants' :: Maybe Text
nextToken = Maybe Text
a} :: ListDistributedGrants)

instance Core.AWSRequest ListDistributedGrants where
  type
    AWSResponse ListDistributedGrants =
      ListDistributedGrantsResponse
  request :: (Service -> Service)
-> ListDistributedGrants -> Request ListDistributedGrants
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 ListDistributedGrants
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListDistributedGrants)))
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 [Grant] -> Maybe Text -> Int -> ListDistributedGrantsResponse
ListDistributedGrantsResponse'
            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
"Grants" 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.<*> (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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable ListDistributedGrants where
  hashWithSalt :: Int -> ListDistributedGrants -> Int
hashWithSalt Int
_salt ListDistributedGrants' {Maybe Natural
Maybe [Text]
Maybe [Filter]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
grantArns :: Maybe [Text]
filters :: Maybe [Filter]
$sel:nextToken:ListDistributedGrants' :: ListDistributedGrants -> Maybe Text
$sel:maxResults:ListDistributedGrants' :: ListDistributedGrants -> Maybe Natural
$sel:grantArns:ListDistributedGrants' :: ListDistributedGrants -> Maybe [Text]
$sel:filters:ListDistributedGrants' :: ListDistributedGrants -> Maybe [Filter]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Filter]
filters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
grantArns
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData ListDistributedGrants where
  rnf :: ListDistributedGrants -> ()
rnf ListDistributedGrants' {Maybe Natural
Maybe [Text]
Maybe [Filter]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
grantArns :: Maybe [Text]
filters :: Maybe [Filter]
$sel:nextToken:ListDistributedGrants' :: ListDistributedGrants -> Maybe Text
$sel:maxResults:ListDistributedGrants' :: ListDistributedGrants -> Maybe Natural
$sel:grantArns:ListDistributedGrants' :: ListDistributedGrants -> Maybe [Text]
$sel:filters:ListDistributedGrants' :: ListDistributedGrants -> Maybe [Filter]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Filter]
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
grantArns
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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

instance Data.ToHeaders ListDistributedGrants where
  toHeaders :: ListDistributedGrants -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSLicenseManager.ListDistributedGrants" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON ListDistributedGrants where
  toJSON :: ListDistributedGrants -> Value
toJSON ListDistributedGrants' {Maybe Natural
Maybe [Text]
Maybe [Filter]
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
grantArns :: Maybe [Text]
filters :: Maybe [Filter]
$sel:nextToken:ListDistributedGrants' :: ListDistributedGrants -> Maybe Text
$sel:maxResults:ListDistributedGrants' :: ListDistributedGrants -> Maybe Natural
$sel:grantArns:ListDistributedGrants' :: ListDistributedGrants -> Maybe [Text]
$sel:filters:ListDistributedGrants' :: ListDistributedGrants -> Maybe [Filter]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Filters" 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 [Filter]
filters,
            (Key
"GrantArns" 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]
grantArns,
            (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
          ]
      )

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

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

-- | /See:/ 'newListDistributedGrantsResponse' smart constructor.
data ListDistributedGrantsResponse = ListDistributedGrantsResponse'
  { -- | Distributed grant details.
    ListDistributedGrantsResponse -> Maybe [Grant]
grants :: Prelude.Maybe [Grant],
    -- | Token for the next set of results.
    ListDistributedGrantsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListDistributedGrantsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListDistributedGrantsResponse
-> ListDistributedGrantsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListDistributedGrantsResponse
-> ListDistributedGrantsResponse -> Bool
$c/= :: ListDistributedGrantsResponse
-> ListDistributedGrantsResponse -> Bool
== :: ListDistributedGrantsResponse
-> ListDistributedGrantsResponse -> Bool
$c== :: ListDistributedGrantsResponse
-> ListDistributedGrantsResponse -> Bool
Prelude.Eq, ReadPrec [ListDistributedGrantsResponse]
ReadPrec ListDistributedGrantsResponse
Int -> ReadS ListDistributedGrantsResponse
ReadS [ListDistributedGrantsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListDistributedGrantsResponse]
$creadListPrec :: ReadPrec [ListDistributedGrantsResponse]
readPrec :: ReadPrec ListDistributedGrantsResponse
$creadPrec :: ReadPrec ListDistributedGrantsResponse
readList :: ReadS [ListDistributedGrantsResponse]
$creadList :: ReadS [ListDistributedGrantsResponse]
readsPrec :: Int -> ReadS ListDistributedGrantsResponse
$creadsPrec :: Int -> ReadS ListDistributedGrantsResponse
Prelude.Read, Int -> ListDistributedGrantsResponse -> ShowS
[ListDistributedGrantsResponse] -> ShowS
ListDistributedGrantsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListDistributedGrantsResponse] -> ShowS
$cshowList :: [ListDistributedGrantsResponse] -> ShowS
show :: ListDistributedGrantsResponse -> String
$cshow :: ListDistributedGrantsResponse -> String
showsPrec :: Int -> ListDistributedGrantsResponse -> ShowS
$cshowsPrec :: Int -> ListDistributedGrantsResponse -> ShowS
Prelude.Show, forall x.
Rep ListDistributedGrantsResponse x
-> ListDistributedGrantsResponse
forall x.
ListDistributedGrantsResponse
-> Rep ListDistributedGrantsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListDistributedGrantsResponse x
-> ListDistributedGrantsResponse
$cfrom :: forall x.
ListDistributedGrantsResponse
-> Rep ListDistributedGrantsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListDistributedGrantsResponse' 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:
--
-- 'grants', 'listDistributedGrantsResponse_grants' - Distributed grant details.
--
-- 'nextToken', 'listDistributedGrantsResponse_nextToken' - Token for the next set of results.
--
-- 'httpStatus', 'listDistributedGrantsResponse_httpStatus' - The response's http status code.
newListDistributedGrantsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListDistributedGrantsResponse
newListDistributedGrantsResponse :: Int -> ListDistributedGrantsResponse
newListDistributedGrantsResponse Int
pHttpStatus_ =
  ListDistributedGrantsResponse'
    { $sel:grants:ListDistributedGrantsResponse' :: Maybe [Grant]
grants =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListDistributedGrantsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListDistributedGrantsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Distributed grant details.
listDistributedGrantsResponse_grants :: Lens.Lens' ListDistributedGrantsResponse (Prelude.Maybe [Grant])
listDistributedGrantsResponse_grants :: Lens' ListDistributedGrantsResponse (Maybe [Grant])
listDistributedGrantsResponse_grants = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDistributedGrantsResponse' {Maybe [Grant]
grants :: Maybe [Grant]
$sel:grants:ListDistributedGrantsResponse' :: ListDistributedGrantsResponse -> Maybe [Grant]
grants} -> Maybe [Grant]
grants) (\s :: ListDistributedGrantsResponse
s@ListDistributedGrantsResponse' {} Maybe [Grant]
a -> ListDistributedGrantsResponse
s {$sel:grants:ListDistributedGrantsResponse' :: Maybe [Grant]
grants = Maybe [Grant]
a} :: ListDistributedGrantsResponse) 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

-- | Token for the next set of results.
listDistributedGrantsResponse_nextToken :: Lens.Lens' ListDistributedGrantsResponse (Prelude.Maybe Prelude.Text)
listDistributedGrantsResponse_nextToken :: Lens' ListDistributedGrantsResponse (Maybe Text)
listDistributedGrantsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDistributedGrantsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListDistributedGrantsResponse' :: ListDistributedGrantsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListDistributedGrantsResponse
s@ListDistributedGrantsResponse' {} Maybe Text
a -> ListDistributedGrantsResponse
s {$sel:nextToken:ListDistributedGrantsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListDistributedGrantsResponse)

-- | The response's http status code.
listDistributedGrantsResponse_httpStatus :: Lens.Lens' ListDistributedGrantsResponse Prelude.Int
listDistributedGrantsResponse_httpStatus :: Lens' ListDistributedGrantsResponse Int
listDistributedGrantsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDistributedGrantsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListDistributedGrantsResponse' :: ListDistributedGrantsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListDistributedGrantsResponse
s@ListDistributedGrantsResponse' {} Int
a -> ListDistributedGrantsResponse
s {$sel:httpStatus:ListDistributedGrantsResponse' :: Int
httpStatus = Int
a} :: ListDistributedGrantsResponse)

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