{-# 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.GetResourcePolicies
-- 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 the resource policies for the specified resources that you own
-- and have shared.
--
-- This operation returns paginated results.
module Amazonka.RAM.GetResourcePolicies
  ( -- * Creating a Request
    GetResourcePolicies (..),
    newGetResourcePolicies,

    -- * Request Lenses
    getResourcePolicies_maxResults,
    getResourcePolicies_nextToken,
    getResourcePolicies_principal,
    getResourcePolicies_resourceArns,

    -- * Destructuring the Response
    GetResourcePoliciesResponse (..),
    newGetResourcePoliciesResponse,

    -- * Response Lenses
    getResourcePoliciesResponse_nextToken,
    getResourcePoliciesResponse_policies,
    getResourcePoliciesResponse_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:/ 'newGetResourcePolicies' smart constructor.
data GetResourcePolicies = GetResourcePolicies'
  { -- | 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.
    GetResourcePolicies -> 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.
    GetResourcePolicies -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Specifies the principal.
    GetResourcePolicies -> Maybe Text
principal :: Prelude.Maybe Prelude.Text,
    -- | Specifies the
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
    -- of the resources whose policies you want to retrieve.
    GetResourcePolicies -> [Text]
resourceArns :: [Prelude.Text]
  }
  deriving (GetResourcePolicies -> GetResourcePolicies -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetResourcePolicies -> GetResourcePolicies -> Bool
$c/= :: GetResourcePolicies -> GetResourcePolicies -> Bool
== :: GetResourcePolicies -> GetResourcePolicies -> Bool
$c== :: GetResourcePolicies -> GetResourcePolicies -> Bool
Prelude.Eq, ReadPrec [GetResourcePolicies]
ReadPrec GetResourcePolicies
Int -> ReadS GetResourcePolicies
ReadS [GetResourcePolicies]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetResourcePolicies]
$creadListPrec :: ReadPrec [GetResourcePolicies]
readPrec :: ReadPrec GetResourcePolicies
$creadPrec :: ReadPrec GetResourcePolicies
readList :: ReadS [GetResourcePolicies]
$creadList :: ReadS [GetResourcePolicies]
readsPrec :: Int -> ReadS GetResourcePolicies
$creadsPrec :: Int -> ReadS GetResourcePolicies
Prelude.Read, Int -> GetResourcePolicies -> ShowS
[GetResourcePolicies] -> ShowS
GetResourcePolicies -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetResourcePolicies] -> ShowS
$cshowList :: [GetResourcePolicies] -> ShowS
show :: GetResourcePolicies -> String
$cshow :: GetResourcePolicies -> String
showsPrec :: Int -> GetResourcePolicies -> ShowS
$cshowsPrec :: Int -> GetResourcePolicies -> ShowS
Prelude.Show, forall x. Rep GetResourcePolicies x -> GetResourcePolicies
forall x. GetResourcePolicies -> Rep GetResourcePolicies x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetResourcePolicies x -> GetResourcePolicies
$cfrom :: forall x. GetResourcePolicies -> Rep GetResourcePolicies x
Prelude.Generic)

-- |
-- Create a value of 'GetResourcePolicies' 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', 'getResourcePolicies_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', 'getResourcePolicies_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.
--
-- 'principal', 'getResourcePolicies_principal' - Specifies the principal.
--
-- 'resourceArns', 'getResourcePolicies_resourceArns' - Specifies the
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- of the resources whose policies you want to retrieve.
newGetResourcePolicies ::
  GetResourcePolicies
newGetResourcePolicies :: GetResourcePolicies
newGetResourcePolicies =
  GetResourcePolicies'
    { $sel:maxResults:GetResourcePolicies' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetResourcePolicies' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:principal:GetResourcePolicies' :: Maybe Text
principal = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceArns:GetResourcePolicies' :: [Text]
resourceArns = forall a. Monoid a => a
Prelude.mempty
    }

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

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

-- | Specifies the principal.
getResourcePolicies_principal :: Lens.Lens' GetResourcePolicies (Prelude.Maybe Prelude.Text)
getResourcePolicies_principal :: Lens' GetResourcePolicies (Maybe Text)
getResourcePolicies_principal = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetResourcePolicies' {Maybe Text
principal :: Maybe Text
$sel:principal:GetResourcePolicies' :: GetResourcePolicies -> Maybe Text
principal} -> Maybe Text
principal) (\s :: GetResourcePolicies
s@GetResourcePolicies' {} Maybe Text
a -> GetResourcePolicies
s {$sel:principal:GetResourcePolicies' :: Maybe Text
principal = Maybe Text
a} :: GetResourcePolicies)

-- | Specifies the
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- of the resources whose policies you want to retrieve.
getResourcePolicies_resourceArns :: Lens.Lens' GetResourcePolicies [Prelude.Text]
getResourcePolicies_resourceArns :: Lens' GetResourcePolicies [Text]
getResourcePolicies_resourceArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetResourcePolicies' {[Text]
resourceArns :: [Text]
$sel:resourceArns:GetResourcePolicies' :: GetResourcePolicies -> [Text]
resourceArns} -> [Text]
resourceArns) (\s :: GetResourcePolicies
s@GetResourcePolicies' {} [Text]
a -> GetResourcePolicies
s {$sel:resourceArns:GetResourcePolicies' :: [Text]
resourceArns = [Text]
a} :: GetResourcePolicies) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSPager GetResourcePolicies where
  page :: GetResourcePolicies
-> AWSResponse GetResourcePolicies -> Maybe GetResourcePolicies
page GetResourcePolicies
rq AWSResponse GetResourcePolicies
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse GetResourcePolicies
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetResourcePoliciesResponse (Maybe Text)
getResourcePoliciesResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse GetResourcePolicies
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetResourcePoliciesResponse (Maybe [Text])
getResourcePoliciesResponse_policies
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ GetResourcePolicies
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' GetResourcePolicies (Maybe Text)
getResourcePolicies_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse GetResourcePolicies
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetResourcePoliciesResponse (Maybe Text)
getResourcePoliciesResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest GetResourcePolicies where
  type
    AWSResponse GetResourcePolicies =
      GetResourcePoliciesResponse
  request :: (Service -> Service)
-> GetResourcePolicies -> Request GetResourcePolicies
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 GetResourcePolicies
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetResourcePolicies)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Maybe [Text] -> Int -> GetResourcePoliciesResponse
GetResourcePoliciesResponse'
            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
"policies" 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 GetResourcePolicies where
  hashWithSalt :: Int -> GetResourcePolicies -> Int
hashWithSalt Int
_salt GetResourcePolicies' {[Text]
Maybe Natural
Maybe Text
resourceArns :: [Text]
principal :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:resourceArns:GetResourcePolicies' :: GetResourcePolicies -> [Text]
$sel:principal:GetResourcePolicies' :: GetResourcePolicies -> Maybe Text
$sel:nextToken:GetResourcePolicies' :: GetResourcePolicies -> Maybe Text
$sel:maxResults:GetResourcePolicies' :: GetResourcePolicies -> 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
principal
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
resourceArns

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

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

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

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

-- | /See:/ 'newGetResourcePoliciesResponse' smart constructor.
data GetResourcePoliciesResponse = GetResourcePoliciesResponse'
  { -- | 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.
    GetResourcePoliciesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An array of resource policy documents in JSON format.
    GetResourcePoliciesResponse -> Maybe [Text]
policies :: Prelude.Maybe [Prelude.Text],
    -- | The response's http status code.
    GetResourcePoliciesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetResourcePoliciesResponse -> GetResourcePoliciesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetResourcePoliciesResponse -> GetResourcePoliciesResponse -> Bool
$c/= :: GetResourcePoliciesResponse -> GetResourcePoliciesResponse -> Bool
== :: GetResourcePoliciesResponse -> GetResourcePoliciesResponse -> Bool
$c== :: GetResourcePoliciesResponse -> GetResourcePoliciesResponse -> Bool
Prelude.Eq, ReadPrec [GetResourcePoliciesResponse]
ReadPrec GetResourcePoliciesResponse
Int -> ReadS GetResourcePoliciesResponse
ReadS [GetResourcePoliciesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetResourcePoliciesResponse]
$creadListPrec :: ReadPrec [GetResourcePoliciesResponse]
readPrec :: ReadPrec GetResourcePoliciesResponse
$creadPrec :: ReadPrec GetResourcePoliciesResponse
readList :: ReadS [GetResourcePoliciesResponse]
$creadList :: ReadS [GetResourcePoliciesResponse]
readsPrec :: Int -> ReadS GetResourcePoliciesResponse
$creadsPrec :: Int -> ReadS GetResourcePoliciesResponse
Prelude.Read, Int -> GetResourcePoliciesResponse -> ShowS
[GetResourcePoliciesResponse] -> ShowS
GetResourcePoliciesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetResourcePoliciesResponse] -> ShowS
$cshowList :: [GetResourcePoliciesResponse] -> ShowS
show :: GetResourcePoliciesResponse -> String
$cshow :: GetResourcePoliciesResponse -> String
showsPrec :: Int -> GetResourcePoliciesResponse -> ShowS
$cshowsPrec :: Int -> GetResourcePoliciesResponse -> ShowS
Prelude.Show, forall x.
Rep GetResourcePoliciesResponse x -> GetResourcePoliciesResponse
forall x.
GetResourcePoliciesResponse -> Rep GetResourcePoliciesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetResourcePoliciesResponse x -> GetResourcePoliciesResponse
$cfrom :: forall x.
GetResourcePoliciesResponse -> Rep GetResourcePoliciesResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetResourcePoliciesResponse' 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', 'getResourcePoliciesResponse_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.
--
-- 'policies', 'getResourcePoliciesResponse_policies' - An array of resource policy documents in JSON format.
--
-- 'httpStatus', 'getResourcePoliciesResponse_httpStatus' - The response's http status code.
newGetResourcePoliciesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetResourcePoliciesResponse
newGetResourcePoliciesResponse :: Int -> GetResourcePoliciesResponse
newGetResourcePoliciesResponse Int
pHttpStatus_ =
  GetResourcePoliciesResponse'
    { $sel:nextToken:GetResourcePoliciesResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:policies:GetResourcePoliciesResponse' :: Maybe [Text]
policies = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetResourcePoliciesResponse' :: 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.
getResourcePoliciesResponse_nextToken :: Lens.Lens' GetResourcePoliciesResponse (Prelude.Maybe Prelude.Text)
getResourcePoliciesResponse_nextToken :: Lens' GetResourcePoliciesResponse (Maybe Text)
getResourcePoliciesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetResourcePoliciesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetResourcePoliciesResponse' :: GetResourcePoliciesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetResourcePoliciesResponse
s@GetResourcePoliciesResponse' {} Maybe Text
a -> GetResourcePoliciesResponse
s {$sel:nextToken:GetResourcePoliciesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetResourcePoliciesResponse)

-- | An array of resource policy documents in JSON format.
getResourcePoliciesResponse_policies :: Lens.Lens' GetResourcePoliciesResponse (Prelude.Maybe [Prelude.Text])
getResourcePoliciesResponse_policies :: Lens' GetResourcePoliciesResponse (Maybe [Text])
getResourcePoliciesResponse_policies = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetResourcePoliciesResponse' {Maybe [Text]
policies :: Maybe [Text]
$sel:policies:GetResourcePoliciesResponse' :: GetResourcePoliciesResponse -> Maybe [Text]
policies} -> Maybe [Text]
policies) (\s :: GetResourcePoliciesResponse
s@GetResourcePoliciesResponse' {} Maybe [Text]
a -> GetResourcePoliciesResponse
s {$sel:policies:GetResourcePoliciesResponse' :: Maybe [Text]
policies = Maybe [Text]
a} :: GetResourcePoliciesResponse) 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.
getResourcePoliciesResponse_httpStatus :: Lens.Lens' GetResourcePoliciesResponse Prelude.Int
getResourcePoliciesResponse_httpStatus :: Lens' GetResourcePoliciesResponse Int
getResourcePoliciesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetResourcePoliciesResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetResourcePoliciesResponse' :: GetResourcePoliciesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetResourcePoliciesResponse
s@GetResourcePoliciesResponse' {} Int
a -> GetResourcePoliciesResponse
s {$sel:httpStatus:GetResourcePoliciesResponse' :: Int
httpStatus = Int
a} :: GetResourcePoliciesResponse)

instance Prelude.NFData GetResourcePoliciesResponse where
  rnf :: GetResourcePoliciesResponse -> ()
rnf GetResourcePoliciesResponse' {Int
Maybe [Text]
Maybe Text
httpStatus :: Int
policies :: Maybe [Text]
nextToken :: Maybe Text
$sel:httpStatus:GetResourcePoliciesResponse' :: GetResourcePoliciesResponse -> Int
$sel:policies:GetResourcePoliciesResponse' :: GetResourcePoliciesResponse -> Maybe [Text]
$sel:nextToken:GetResourcePoliciesResponse' :: GetResourcePoliciesResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
policies
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus