{-# 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.Redshift.DescribeSnapshotCopyGrants
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a list of snapshot copy grants owned by the Amazon Web Services
-- account in the destination region.
--
-- For more information about managing snapshot copy grants, go to
-- <https://docs.aws.amazon.com/redshift/latest/mgmt/working-with-db-encryption.html Amazon Redshift Database Encryption>
-- in the /Amazon Redshift Cluster Management Guide/.
--
-- This operation returns paginated results.
module Amazonka.Redshift.DescribeSnapshotCopyGrants
  ( -- * Creating a Request
    DescribeSnapshotCopyGrants (..),
    newDescribeSnapshotCopyGrants,

    -- * Request Lenses
    describeSnapshotCopyGrants_marker,
    describeSnapshotCopyGrants_maxRecords,
    describeSnapshotCopyGrants_snapshotCopyGrantName,
    describeSnapshotCopyGrants_tagKeys,
    describeSnapshotCopyGrants_tagValues,

    -- * Destructuring the Response
    DescribeSnapshotCopyGrantsResponse (..),
    newDescribeSnapshotCopyGrantsResponse,

    -- * Response Lenses
    describeSnapshotCopyGrantsResponse_marker,
    describeSnapshotCopyGrantsResponse_snapshotCopyGrants,
    describeSnapshotCopyGrantsResponse_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.Redshift.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | The result of the @DescribeSnapshotCopyGrants@ action.
--
-- /See:/ 'newDescribeSnapshotCopyGrants' smart constructor.
data DescribeSnapshotCopyGrants = DescribeSnapshotCopyGrants'
  { -- | An optional parameter that specifies the starting point to return a set
    -- of response records. When the results of a @DescribeSnapshotCopyGrant@
    -- request exceed the value specified in @MaxRecords@, Amazon Web Services
    -- returns a value in the @Marker@ field of the response. You can retrieve
    -- the next set of response records by providing the returned marker value
    -- in the @Marker@ parameter and retrying the request.
    --
    -- Constraints: You can specify either the __SnapshotCopyGrantName__
    -- parameter or the __Marker__ parameter, but not both.
    DescribeSnapshotCopyGrants -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of response records to return in each call. If the
    -- number of remaining response records exceeds the specified @MaxRecords@
    -- value, a value is returned in a @marker@ field of the response. You can
    -- retrieve the next set of records by retrying the command with the
    -- returned marker value.
    --
    -- Default: @100@
    --
    -- Constraints: minimum 20, maximum 100.
    DescribeSnapshotCopyGrants -> Maybe Int
maxRecords :: Prelude.Maybe Prelude.Int,
    -- | The name of the snapshot copy grant.
    DescribeSnapshotCopyGrants -> Maybe Text
snapshotCopyGrantName :: Prelude.Maybe Prelude.Text,
    -- | A tag key or keys for which you want to return all matching resources
    -- that are associated with the specified key or keys. For example, suppose
    -- that you have resources tagged with keys called @owner@ and
    -- @environment@. If you specify both of these tag keys in the request,
    -- Amazon Redshift returns a response with all resources that have either
    -- or both of these tag keys associated with them.
    DescribeSnapshotCopyGrants -> Maybe [Text]
tagKeys :: Prelude.Maybe [Prelude.Text],
    -- | A tag value or values for which you want to return all matching
    -- resources that are associated with the specified value or values. For
    -- example, suppose that you have resources tagged with values called
    -- @admin@ and @test@. If you specify both of these tag values in the
    -- request, Amazon Redshift returns a response with all resources that have
    -- either or both of these tag values associated with them.
    DescribeSnapshotCopyGrants -> Maybe [Text]
tagValues :: Prelude.Maybe [Prelude.Text]
  }
  deriving (DescribeSnapshotCopyGrants -> DescribeSnapshotCopyGrants -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSnapshotCopyGrants -> DescribeSnapshotCopyGrants -> Bool
$c/= :: DescribeSnapshotCopyGrants -> DescribeSnapshotCopyGrants -> Bool
== :: DescribeSnapshotCopyGrants -> DescribeSnapshotCopyGrants -> Bool
$c== :: DescribeSnapshotCopyGrants -> DescribeSnapshotCopyGrants -> Bool
Prelude.Eq, ReadPrec [DescribeSnapshotCopyGrants]
ReadPrec DescribeSnapshotCopyGrants
Int -> ReadS DescribeSnapshotCopyGrants
ReadS [DescribeSnapshotCopyGrants]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeSnapshotCopyGrants]
$creadListPrec :: ReadPrec [DescribeSnapshotCopyGrants]
readPrec :: ReadPrec DescribeSnapshotCopyGrants
$creadPrec :: ReadPrec DescribeSnapshotCopyGrants
readList :: ReadS [DescribeSnapshotCopyGrants]
$creadList :: ReadS [DescribeSnapshotCopyGrants]
readsPrec :: Int -> ReadS DescribeSnapshotCopyGrants
$creadsPrec :: Int -> ReadS DescribeSnapshotCopyGrants
Prelude.Read, Int -> DescribeSnapshotCopyGrants -> ShowS
[DescribeSnapshotCopyGrants] -> ShowS
DescribeSnapshotCopyGrants -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSnapshotCopyGrants] -> ShowS
$cshowList :: [DescribeSnapshotCopyGrants] -> ShowS
show :: DescribeSnapshotCopyGrants -> String
$cshow :: DescribeSnapshotCopyGrants -> String
showsPrec :: Int -> DescribeSnapshotCopyGrants -> ShowS
$cshowsPrec :: Int -> DescribeSnapshotCopyGrants -> ShowS
Prelude.Show, forall x.
Rep DescribeSnapshotCopyGrants x -> DescribeSnapshotCopyGrants
forall x.
DescribeSnapshotCopyGrants -> Rep DescribeSnapshotCopyGrants x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeSnapshotCopyGrants x -> DescribeSnapshotCopyGrants
$cfrom :: forall x.
DescribeSnapshotCopyGrants -> Rep DescribeSnapshotCopyGrants x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSnapshotCopyGrants' 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:
--
-- 'marker', 'describeSnapshotCopyGrants_marker' - An optional parameter that specifies the starting point to return a set
-- of response records. When the results of a @DescribeSnapshotCopyGrant@
-- request exceed the value specified in @MaxRecords@, Amazon Web Services
-- returns a value in the @Marker@ field of the response. You can retrieve
-- the next set of response records by providing the returned marker value
-- in the @Marker@ parameter and retrying the request.
--
-- Constraints: You can specify either the __SnapshotCopyGrantName__
-- parameter or the __Marker__ parameter, but not both.
--
-- 'maxRecords', 'describeSnapshotCopyGrants_maxRecords' - The maximum number of response records to return in each call. If the
-- number of remaining response records exceeds the specified @MaxRecords@
-- value, a value is returned in a @marker@ field of the response. You can
-- retrieve the next set of records by retrying the command with the
-- returned marker value.
--
-- Default: @100@
--
-- Constraints: minimum 20, maximum 100.
--
-- 'snapshotCopyGrantName', 'describeSnapshotCopyGrants_snapshotCopyGrantName' - The name of the snapshot copy grant.
--
-- 'tagKeys', 'describeSnapshotCopyGrants_tagKeys' - A tag key or keys for which you want to return all matching resources
-- that are associated with the specified key or keys. For example, suppose
-- that you have resources tagged with keys called @owner@ and
-- @environment@. If you specify both of these tag keys in the request,
-- Amazon Redshift returns a response with all resources that have either
-- or both of these tag keys associated with them.
--
-- 'tagValues', 'describeSnapshotCopyGrants_tagValues' - A tag value or values for which you want to return all matching
-- resources that are associated with the specified value or values. For
-- example, suppose that you have resources tagged with values called
-- @admin@ and @test@. If you specify both of these tag values in the
-- request, Amazon Redshift returns a response with all resources that have
-- either or both of these tag values associated with them.
newDescribeSnapshotCopyGrants ::
  DescribeSnapshotCopyGrants
newDescribeSnapshotCopyGrants :: DescribeSnapshotCopyGrants
newDescribeSnapshotCopyGrants =
  DescribeSnapshotCopyGrants'
    { $sel:marker:DescribeSnapshotCopyGrants' :: Maybe Text
marker =
        forall a. Maybe a
Prelude.Nothing,
      $sel:maxRecords:DescribeSnapshotCopyGrants' :: Maybe Int
maxRecords = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotCopyGrantName:DescribeSnapshotCopyGrants' :: Maybe Text
snapshotCopyGrantName = forall a. Maybe a
Prelude.Nothing,
      $sel:tagKeys:DescribeSnapshotCopyGrants' :: Maybe [Text]
tagKeys = forall a. Maybe a
Prelude.Nothing,
      $sel:tagValues:DescribeSnapshotCopyGrants' :: Maybe [Text]
tagValues = forall a. Maybe a
Prelude.Nothing
    }

-- | An optional parameter that specifies the starting point to return a set
-- of response records. When the results of a @DescribeSnapshotCopyGrant@
-- request exceed the value specified in @MaxRecords@, Amazon Web Services
-- returns a value in the @Marker@ field of the response. You can retrieve
-- the next set of response records by providing the returned marker value
-- in the @Marker@ parameter and retrying the request.
--
-- Constraints: You can specify either the __SnapshotCopyGrantName__
-- parameter or the __Marker__ parameter, but not both.
describeSnapshotCopyGrants_marker :: Lens.Lens' DescribeSnapshotCopyGrants (Prelude.Maybe Prelude.Text)
describeSnapshotCopyGrants_marker :: Lens' DescribeSnapshotCopyGrants (Maybe Text)
describeSnapshotCopyGrants_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotCopyGrants' {Maybe Text
marker :: Maybe Text
$sel:marker:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe Text
marker} -> Maybe Text
marker) (\s :: DescribeSnapshotCopyGrants
s@DescribeSnapshotCopyGrants' {} Maybe Text
a -> DescribeSnapshotCopyGrants
s {$sel:marker:DescribeSnapshotCopyGrants' :: Maybe Text
marker = Maybe Text
a} :: DescribeSnapshotCopyGrants)

-- | The maximum number of response records to return in each call. If the
-- number of remaining response records exceeds the specified @MaxRecords@
-- value, a value is returned in a @marker@ field of the response. You can
-- retrieve the next set of records by retrying the command with the
-- returned marker value.
--
-- Default: @100@
--
-- Constraints: minimum 20, maximum 100.
describeSnapshotCopyGrants_maxRecords :: Lens.Lens' DescribeSnapshotCopyGrants (Prelude.Maybe Prelude.Int)
describeSnapshotCopyGrants_maxRecords :: Lens' DescribeSnapshotCopyGrants (Maybe Int)
describeSnapshotCopyGrants_maxRecords = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotCopyGrants' {Maybe Int
maxRecords :: Maybe Int
$sel:maxRecords:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe Int
maxRecords} -> Maybe Int
maxRecords) (\s :: DescribeSnapshotCopyGrants
s@DescribeSnapshotCopyGrants' {} Maybe Int
a -> DescribeSnapshotCopyGrants
s {$sel:maxRecords:DescribeSnapshotCopyGrants' :: Maybe Int
maxRecords = Maybe Int
a} :: DescribeSnapshotCopyGrants)

-- | The name of the snapshot copy grant.
describeSnapshotCopyGrants_snapshotCopyGrantName :: Lens.Lens' DescribeSnapshotCopyGrants (Prelude.Maybe Prelude.Text)
describeSnapshotCopyGrants_snapshotCopyGrantName :: Lens' DescribeSnapshotCopyGrants (Maybe Text)
describeSnapshotCopyGrants_snapshotCopyGrantName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotCopyGrants' {Maybe Text
snapshotCopyGrantName :: Maybe Text
$sel:snapshotCopyGrantName:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe Text
snapshotCopyGrantName} -> Maybe Text
snapshotCopyGrantName) (\s :: DescribeSnapshotCopyGrants
s@DescribeSnapshotCopyGrants' {} Maybe Text
a -> DescribeSnapshotCopyGrants
s {$sel:snapshotCopyGrantName:DescribeSnapshotCopyGrants' :: Maybe Text
snapshotCopyGrantName = Maybe Text
a} :: DescribeSnapshotCopyGrants)

-- | A tag key or keys for which you want to return all matching resources
-- that are associated with the specified key or keys. For example, suppose
-- that you have resources tagged with keys called @owner@ and
-- @environment@. If you specify both of these tag keys in the request,
-- Amazon Redshift returns a response with all resources that have either
-- or both of these tag keys associated with them.
describeSnapshotCopyGrants_tagKeys :: Lens.Lens' DescribeSnapshotCopyGrants (Prelude.Maybe [Prelude.Text])
describeSnapshotCopyGrants_tagKeys :: Lens' DescribeSnapshotCopyGrants (Maybe [Text])
describeSnapshotCopyGrants_tagKeys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotCopyGrants' {Maybe [Text]
tagKeys :: Maybe [Text]
$sel:tagKeys:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe [Text]
tagKeys} -> Maybe [Text]
tagKeys) (\s :: DescribeSnapshotCopyGrants
s@DescribeSnapshotCopyGrants' {} Maybe [Text]
a -> DescribeSnapshotCopyGrants
s {$sel:tagKeys:DescribeSnapshotCopyGrants' :: Maybe [Text]
tagKeys = Maybe [Text]
a} :: DescribeSnapshotCopyGrants) 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

-- | A tag value or values for which you want to return all matching
-- resources that are associated with the specified value or values. For
-- example, suppose that you have resources tagged with values called
-- @admin@ and @test@. If you specify both of these tag values in the
-- request, Amazon Redshift returns a response with all resources that have
-- either or both of these tag values associated with them.
describeSnapshotCopyGrants_tagValues :: Lens.Lens' DescribeSnapshotCopyGrants (Prelude.Maybe [Prelude.Text])
describeSnapshotCopyGrants_tagValues :: Lens' DescribeSnapshotCopyGrants (Maybe [Text])
describeSnapshotCopyGrants_tagValues = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotCopyGrants' {Maybe [Text]
tagValues :: Maybe [Text]
$sel:tagValues:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe [Text]
tagValues} -> Maybe [Text]
tagValues) (\s :: DescribeSnapshotCopyGrants
s@DescribeSnapshotCopyGrants' {} Maybe [Text]
a -> DescribeSnapshotCopyGrants
s {$sel:tagValues:DescribeSnapshotCopyGrants' :: Maybe [Text]
tagValues = Maybe [Text]
a} :: DescribeSnapshotCopyGrants) 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

instance Core.AWSPager DescribeSnapshotCopyGrants where
  page :: DescribeSnapshotCopyGrants
-> AWSResponse DescribeSnapshotCopyGrants
-> Maybe DescribeSnapshotCopyGrants
page DescribeSnapshotCopyGrants
rq AWSResponse DescribeSnapshotCopyGrants
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeSnapshotCopyGrants
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeSnapshotCopyGrantsResponse (Maybe Text)
describeSnapshotCopyGrantsResponse_marker
            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 DescribeSnapshotCopyGrants
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  DescribeSnapshotCopyGrantsResponse (Maybe [SnapshotCopyGrant])
describeSnapshotCopyGrantsResponse_snapshotCopyGrants
            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.$ DescribeSnapshotCopyGrants
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeSnapshotCopyGrants (Maybe Text)
describeSnapshotCopyGrants_marker
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeSnapshotCopyGrants
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeSnapshotCopyGrantsResponse (Maybe Text)
describeSnapshotCopyGrantsResponse_marker
          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 DescribeSnapshotCopyGrants where
  type
    AWSResponse DescribeSnapshotCopyGrants =
      DescribeSnapshotCopyGrantsResponse
  request :: (Service -> Service)
-> DescribeSnapshotCopyGrants -> Request DescribeSnapshotCopyGrants
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeSnapshotCopyGrants
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeSnapshotCopyGrants)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"DescribeSnapshotCopyGrantsResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text
-> Maybe [SnapshotCopyGrant]
-> Int
-> DescribeSnapshotCopyGrantsResponse
DescribeSnapshotCopyGrantsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Marker")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"SnapshotCopyGrants"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"SnapshotCopyGrant")
                        )
            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 DescribeSnapshotCopyGrants where
  hashWithSalt :: Int -> DescribeSnapshotCopyGrants -> Int
hashWithSalt Int
_salt DescribeSnapshotCopyGrants' {Maybe Int
Maybe [Text]
Maybe Text
tagValues :: Maybe [Text]
tagKeys :: Maybe [Text]
snapshotCopyGrantName :: Maybe Text
maxRecords :: Maybe Int
marker :: Maybe Text
$sel:tagValues:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe [Text]
$sel:tagKeys:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe [Text]
$sel:snapshotCopyGrantName:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe Text
$sel:maxRecords:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe Int
$sel:marker:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxRecords
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
snapshotCopyGrantName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
tagKeys
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
tagValues

instance Prelude.NFData DescribeSnapshotCopyGrants where
  rnf :: DescribeSnapshotCopyGrants -> ()
rnf DescribeSnapshotCopyGrants' {Maybe Int
Maybe [Text]
Maybe Text
tagValues :: Maybe [Text]
tagKeys :: Maybe [Text]
snapshotCopyGrantName :: Maybe Text
maxRecords :: Maybe Int
marker :: Maybe Text
$sel:tagValues:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe [Text]
$sel:tagKeys:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe [Text]
$sel:snapshotCopyGrantName:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe Text
$sel:maxRecords:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe Int
$sel:marker:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxRecords
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
snapshotCopyGrantName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
tagKeys
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
tagValues

instance Data.ToHeaders DescribeSnapshotCopyGrants where
  toHeaders :: DescribeSnapshotCopyGrants -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery DescribeSnapshotCopyGrants where
  toQuery :: DescribeSnapshotCopyGrants -> QueryString
toQuery DescribeSnapshotCopyGrants' {Maybe Int
Maybe [Text]
Maybe Text
tagValues :: Maybe [Text]
tagKeys :: Maybe [Text]
snapshotCopyGrantName :: Maybe Text
maxRecords :: Maybe Int
marker :: Maybe Text
$sel:tagValues:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe [Text]
$sel:tagKeys:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe [Text]
$sel:snapshotCopyGrantName:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe Text
$sel:maxRecords:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe Int
$sel:marker:DescribeSnapshotCopyGrants' :: DescribeSnapshotCopyGrants -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DescribeSnapshotCopyGrants" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2012-12-01" :: Prelude.ByteString),
        ByteString
"Marker" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
marker,
        ByteString
"MaxRecords" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
maxRecords,
        ByteString
"SnapshotCopyGrantName"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
snapshotCopyGrantName,
        ByteString
"TagKeys"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"TagKey" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
tagKeys),
        ByteString
"TagValues"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"TagValue" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
tagValues)
      ]

-- |
--
-- /See:/ 'newDescribeSnapshotCopyGrantsResponse' smart constructor.
data DescribeSnapshotCopyGrantsResponse = DescribeSnapshotCopyGrantsResponse'
  { -- | An optional parameter that specifies the starting point to return a set
    -- of response records. When the results of a @DescribeSnapshotCopyGrant@
    -- request exceed the value specified in @MaxRecords@, Amazon Web Services
    -- returns a value in the @Marker@ field of the response. You can retrieve
    -- the next set of response records by providing the returned marker value
    -- in the @Marker@ parameter and retrying the request.
    --
    -- Constraints: You can specify either the __SnapshotCopyGrantName__
    -- parameter or the __Marker__ parameter, but not both.
    DescribeSnapshotCopyGrantsResponse -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The list of @SnapshotCopyGrant@ objects.
    DescribeSnapshotCopyGrantsResponse -> Maybe [SnapshotCopyGrant]
snapshotCopyGrants :: Prelude.Maybe [SnapshotCopyGrant],
    -- | The response's http status code.
    DescribeSnapshotCopyGrantsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeSnapshotCopyGrantsResponse
-> DescribeSnapshotCopyGrantsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSnapshotCopyGrantsResponse
-> DescribeSnapshotCopyGrantsResponse -> Bool
$c/= :: DescribeSnapshotCopyGrantsResponse
-> DescribeSnapshotCopyGrantsResponse -> Bool
== :: DescribeSnapshotCopyGrantsResponse
-> DescribeSnapshotCopyGrantsResponse -> Bool
$c== :: DescribeSnapshotCopyGrantsResponse
-> DescribeSnapshotCopyGrantsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeSnapshotCopyGrantsResponse]
ReadPrec DescribeSnapshotCopyGrantsResponse
Int -> ReadS DescribeSnapshotCopyGrantsResponse
ReadS [DescribeSnapshotCopyGrantsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeSnapshotCopyGrantsResponse]
$creadListPrec :: ReadPrec [DescribeSnapshotCopyGrantsResponse]
readPrec :: ReadPrec DescribeSnapshotCopyGrantsResponse
$creadPrec :: ReadPrec DescribeSnapshotCopyGrantsResponse
readList :: ReadS [DescribeSnapshotCopyGrantsResponse]
$creadList :: ReadS [DescribeSnapshotCopyGrantsResponse]
readsPrec :: Int -> ReadS DescribeSnapshotCopyGrantsResponse
$creadsPrec :: Int -> ReadS DescribeSnapshotCopyGrantsResponse
Prelude.Read, Int -> DescribeSnapshotCopyGrantsResponse -> ShowS
[DescribeSnapshotCopyGrantsResponse] -> ShowS
DescribeSnapshotCopyGrantsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSnapshotCopyGrantsResponse] -> ShowS
$cshowList :: [DescribeSnapshotCopyGrantsResponse] -> ShowS
show :: DescribeSnapshotCopyGrantsResponse -> String
$cshow :: DescribeSnapshotCopyGrantsResponse -> String
showsPrec :: Int -> DescribeSnapshotCopyGrantsResponse -> ShowS
$cshowsPrec :: Int -> DescribeSnapshotCopyGrantsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeSnapshotCopyGrantsResponse x
-> DescribeSnapshotCopyGrantsResponse
forall x.
DescribeSnapshotCopyGrantsResponse
-> Rep DescribeSnapshotCopyGrantsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeSnapshotCopyGrantsResponse x
-> DescribeSnapshotCopyGrantsResponse
$cfrom :: forall x.
DescribeSnapshotCopyGrantsResponse
-> Rep DescribeSnapshotCopyGrantsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSnapshotCopyGrantsResponse' 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:
--
-- 'marker', 'describeSnapshotCopyGrantsResponse_marker' - An optional parameter that specifies the starting point to return a set
-- of response records. When the results of a @DescribeSnapshotCopyGrant@
-- request exceed the value specified in @MaxRecords@, Amazon Web Services
-- returns a value in the @Marker@ field of the response. You can retrieve
-- the next set of response records by providing the returned marker value
-- in the @Marker@ parameter and retrying the request.
--
-- Constraints: You can specify either the __SnapshotCopyGrantName__
-- parameter or the __Marker__ parameter, but not both.
--
-- 'snapshotCopyGrants', 'describeSnapshotCopyGrantsResponse_snapshotCopyGrants' - The list of @SnapshotCopyGrant@ objects.
--
-- 'httpStatus', 'describeSnapshotCopyGrantsResponse_httpStatus' - The response's http status code.
newDescribeSnapshotCopyGrantsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeSnapshotCopyGrantsResponse
newDescribeSnapshotCopyGrantsResponse :: Int -> DescribeSnapshotCopyGrantsResponse
newDescribeSnapshotCopyGrantsResponse Int
pHttpStatus_ =
  DescribeSnapshotCopyGrantsResponse'
    { $sel:marker:DescribeSnapshotCopyGrantsResponse' :: Maybe Text
marker =
        forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotCopyGrants:DescribeSnapshotCopyGrantsResponse' :: Maybe [SnapshotCopyGrant]
snapshotCopyGrants = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeSnapshotCopyGrantsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An optional parameter that specifies the starting point to return a set
-- of response records. When the results of a @DescribeSnapshotCopyGrant@
-- request exceed the value specified in @MaxRecords@, Amazon Web Services
-- returns a value in the @Marker@ field of the response. You can retrieve
-- the next set of response records by providing the returned marker value
-- in the @Marker@ parameter and retrying the request.
--
-- Constraints: You can specify either the __SnapshotCopyGrantName__
-- parameter or the __Marker__ parameter, but not both.
describeSnapshotCopyGrantsResponse_marker :: Lens.Lens' DescribeSnapshotCopyGrantsResponse (Prelude.Maybe Prelude.Text)
describeSnapshotCopyGrantsResponse_marker :: Lens' DescribeSnapshotCopyGrantsResponse (Maybe Text)
describeSnapshotCopyGrantsResponse_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotCopyGrantsResponse' {Maybe Text
marker :: Maybe Text
$sel:marker:DescribeSnapshotCopyGrantsResponse' :: DescribeSnapshotCopyGrantsResponse -> Maybe Text
marker} -> Maybe Text
marker) (\s :: DescribeSnapshotCopyGrantsResponse
s@DescribeSnapshotCopyGrantsResponse' {} Maybe Text
a -> DescribeSnapshotCopyGrantsResponse
s {$sel:marker:DescribeSnapshotCopyGrantsResponse' :: Maybe Text
marker = Maybe Text
a} :: DescribeSnapshotCopyGrantsResponse)

-- | The list of @SnapshotCopyGrant@ objects.
describeSnapshotCopyGrantsResponse_snapshotCopyGrants :: Lens.Lens' DescribeSnapshotCopyGrantsResponse (Prelude.Maybe [SnapshotCopyGrant])
describeSnapshotCopyGrantsResponse_snapshotCopyGrants :: Lens'
  DescribeSnapshotCopyGrantsResponse (Maybe [SnapshotCopyGrant])
describeSnapshotCopyGrantsResponse_snapshotCopyGrants = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotCopyGrantsResponse' {Maybe [SnapshotCopyGrant]
snapshotCopyGrants :: Maybe [SnapshotCopyGrant]
$sel:snapshotCopyGrants:DescribeSnapshotCopyGrantsResponse' :: DescribeSnapshotCopyGrantsResponse -> Maybe [SnapshotCopyGrant]
snapshotCopyGrants} -> Maybe [SnapshotCopyGrant]
snapshotCopyGrants) (\s :: DescribeSnapshotCopyGrantsResponse
s@DescribeSnapshotCopyGrantsResponse' {} Maybe [SnapshotCopyGrant]
a -> DescribeSnapshotCopyGrantsResponse
s {$sel:snapshotCopyGrants:DescribeSnapshotCopyGrantsResponse' :: Maybe [SnapshotCopyGrant]
snapshotCopyGrants = Maybe [SnapshotCopyGrant]
a} :: DescribeSnapshotCopyGrantsResponse) 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.
describeSnapshotCopyGrantsResponse_httpStatus :: Lens.Lens' DescribeSnapshotCopyGrantsResponse Prelude.Int
describeSnapshotCopyGrantsResponse_httpStatus :: Lens' DescribeSnapshotCopyGrantsResponse Int
describeSnapshotCopyGrantsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotCopyGrantsResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeSnapshotCopyGrantsResponse' :: DescribeSnapshotCopyGrantsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeSnapshotCopyGrantsResponse
s@DescribeSnapshotCopyGrantsResponse' {} Int
a -> DescribeSnapshotCopyGrantsResponse
s {$sel:httpStatus:DescribeSnapshotCopyGrantsResponse' :: Int
httpStatus = Int
a} :: DescribeSnapshotCopyGrantsResponse)

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