{-# 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.CreateSnapshotCopyGrant
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a snapshot copy grant that permits Amazon Redshift to use an
-- encrypted symmetric key from Key Management Service (KMS) to encrypt
-- copied snapshots in a 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/.
module Amazonka.Redshift.CreateSnapshotCopyGrant
  ( -- * Creating a Request
    CreateSnapshotCopyGrant (..),
    newCreateSnapshotCopyGrant,

    -- * Request Lenses
    createSnapshotCopyGrant_kmsKeyId,
    createSnapshotCopyGrant_tags,
    createSnapshotCopyGrant_snapshotCopyGrantName,

    -- * Destructuring the Response
    CreateSnapshotCopyGrantResponse (..),
    newCreateSnapshotCopyGrantResponse,

    -- * Response Lenses
    createSnapshotCopyGrantResponse_snapshotCopyGrant,
    createSnapshotCopyGrantResponse_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 @CreateSnapshotCopyGrant@ action.
--
-- /See:/ 'newCreateSnapshotCopyGrant' smart constructor.
data CreateSnapshotCopyGrant = CreateSnapshotCopyGrant'
  { -- | The unique identifier of the encrypted symmetric key to which to grant
    -- Amazon Redshift permission. If no key is specified, the default key is
    -- used.
    CreateSnapshotCopyGrant -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | A list of tag instances.
    CreateSnapshotCopyGrant -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The name of the snapshot copy grant. This name must be unique in the
    -- region for the Amazon Web Services account.
    --
    -- Constraints:
    --
    -- -   Must contain from 1 to 63 alphanumeric characters or hyphens.
    --
    -- -   Alphabetic characters must be lowercase.
    --
    -- -   First character must be a letter.
    --
    -- -   Cannot end with a hyphen or contain two consecutive hyphens.
    --
    -- -   Must be unique for all clusters within an Amazon Web Services
    --     account.
    CreateSnapshotCopyGrant -> Text
snapshotCopyGrantName :: Prelude.Text
  }
  deriving (CreateSnapshotCopyGrant -> CreateSnapshotCopyGrant -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSnapshotCopyGrant -> CreateSnapshotCopyGrant -> Bool
$c/= :: CreateSnapshotCopyGrant -> CreateSnapshotCopyGrant -> Bool
== :: CreateSnapshotCopyGrant -> CreateSnapshotCopyGrant -> Bool
$c== :: CreateSnapshotCopyGrant -> CreateSnapshotCopyGrant -> Bool
Prelude.Eq, ReadPrec [CreateSnapshotCopyGrant]
ReadPrec CreateSnapshotCopyGrant
Int -> ReadS CreateSnapshotCopyGrant
ReadS [CreateSnapshotCopyGrant]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateSnapshotCopyGrant]
$creadListPrec :: ReadPrec [CreateSnapshotCopyGrant]
readPrec :: ReadPrec CreateSnapshotCopyGrant
$creadPrec :: ReadPrec CreateSnapshotCopyGrant
readList :: ReadS [CreateSnapshotCopyGrant]
$creadList :: ReadS [CreateSnapshotCopyGrant]
readsPrec :: Int -> ReadS CreateSnapshotCopyGrant
$creadsPrec :: Int -> ReadS CreateSnapshotCopyGrant
Prelude.Read, Int -> CreateSnapshotCopyGrant -> ShowS
[CreateSnapshotCopyGrant] -> ShowS
CreateSnapshotCopyGrant -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSnapshotCopyGrant] -> ShowS
$cshowList :: [CreateSnapshotCopyGrant] -> ShowS
show :: CreateSnapshotCopyGrant -> String
$cshow :: CreateSnapshotCopyGrant -> String
showsPrec :: Int -> CreateSnapshotCopyGrant -> ShowS
$cshowsPrec :: Int -> CreateSnapshotCopyGrant -> ShowS
Prelude.Show, forall x. Rep CreateSnapshotCopyGrant x -> CreateSnapshotCopyGrant
forall x. CreateSnapshotCopyGrant -> Rep CreateSnapshotCopyGrant x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateSnapshotCopyGrant x -> CreateSnapshotCopyGrant
$cfrom :: forall x. CreateSnapshotCopyGrant -> Rep CreateSnapshotCopyGrant x
Prelude.Generic)

-- |
-- Create a value of 'CreateSnapshotCopyGrant' 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:
--
-- 'kmsKeyId', 'createSnapshotCopyGrant_kmsKeyId' - The unique identifier of the encrypted symmetric key to which to grant
-- Amazon Redshift permission. If no key is specified, the default key is
-- used.
--
-- 'tags', 'createSnapshotCopyGrant_tags' - A list of tag instances.
--
-- 'snapshotCopyGrantName', 'createSnapshotCopyGrant_snapshotCopyGrantName' - The name of the snapshot copy grant. This name must be unique in the
-- region for the Amazon Web Services account.
--
-- Constraints:
--
-- -   Must contain from 1 to 63 alphanumeric characters or hyphens.
--
-- -   Alphabetic characters must be lowercase.
--
-- -   First character must be a letter.
--
-- -   Cannot end with a hyphen or contain two consecutive hyphens.
--
-- -   Must be unique for all clusters within an Amazon Web Services
--     account.
newCreateSnapshotCopyGrant ::
  -- | 'snapshotCopyGrantName'
  Prelude.Text ->
  CreateSnapshotCopyGrant
newCreateSnapshotCopyGrant :: Text -> CreateSnapshotCopyGrant
newCreateSnapshotCopyGrant Text
pSnapshotCopyGrantName_ =
  CreateSnapshotCopyGrant'
    { $sel:kmsKeyId:CreateSnapshotCopyGrant' :: Maybe Text
kmsKeyId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateSnapshotCopyGrant' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotCopyGrantName:CreateSnapshotCopyGrant' :: Text
snapshotCopyGrantName = Text
pSnapshotCopyGrantName_
    }

-- | The unique identifier of the encrypted symmetric key to which to grant
-- Amazon Redshift permission. If no key is specified, the default key is
-- used.
createSnapshotCopyGrant_kmsKeyId :: Lens.Lens' CreateSnapshotCopyGrant (Prelude.Maybe Prelude.Text)
createSnapshotCopyGrant_kmsKeyId :: Lens' CreateSnapshotCopyGrant (Maybe Text)
createSnapshotCopyGrant_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshotCopyGrant' {Maybe Text
kmsKeyId :: Maybe Text
$sel:kmsKeyId:CreateSnapshotCopyGrant' :: CreateSnapshotCopyGrant -> Maybe Text
kmsKeyId} -> Maybe Text
kmsKeyId) (\s :: CreateSnapshotCopyGrant
s@CreateSnapshotCopyGrant' {} Maybe Text
a -> CreateSnapshotCopyGrant
s {$sel:kmsKeyId:CreateSnapshotCopyGrant' :: Maybe Text
kmsKeyId = Maybe Text
a} :: CreateSnapshotCopyGrant)

-- | A list of tag instances.
createSnapshotCopyGrant_tags :: Lens.Lens' CreateSnapshotCopyGrant (Prelude.Maybe [Tag])
createSnapshotCopyGrant_tags :: Lens' CreateSnapshotCopyGrant (Maybe [Tag])
createSnapshotCopyGrant_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshotCopyGrant' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateSnapshotCopyGrant' :: CreateSnapshotCopyGrant -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateSnapshotCopyGrant
s@CreateSnapshotCopyGrant' {} Maybe [Tag]
a -> CreateSnapshotCopyGrant
s {$sel:tags:CreateSnapshotCopyGrant' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateSnapshotCopyGrant) 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 name of the snapshot copy grant. This name must be unique in the
-- region for the Amazon Web Services account.
--
-- Constraints:
--
-- -   Must contain from 1 to 63 alphanumeric characters or hyphens.
--
-- -   Alphabetic characters must be lowercase.
--
-- -   First character must be a letter.
--
-- -   Cannot end with a hyphen or contain two consecutive hyphens.
--
-- -   Must be unique for all clusters within an Amazon Web Services
--     account.
createSnapshotCopyGrant_snapshotCopyGrantName :: Lens.Lens' CreateSnapshotCopyGrant Prelude.Text
createSnapshotCopyGrant_snapshotCopyGrantName :: Lens' CreateSnapshotCopyGrant Text
createSnapshotCopyGrant_snapshotCopyGrantName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshotCopyGrant' {Text
snapshotCopyGrantName :: Text
$sel:snapshotCopyGrantName:CreateSnapshotCopyGrant' :: CreateSnapshotCopyGrant -> Text
snapshotCopyGrantName} -> Text
snapshotCopyGrantName) (\s :: CreateSnapshotCopyGrant
s@CreateSnapshotCopyGrant' {} Text
a -> CreateSnapshotCopyGrant
s {$sel:snapshotCopyGrantName:CreateSnapshotCopyGrant' :: Text
snapshotCopyGrantName = Text
a} :: CreateSnapshotCopyGrant)

instance Core.AWSRequest CreateSnapshotCopyGrant where
  type
    AWSResponse CreateSnapshotCopyGrant =
      CreateSnapshotCopyGrantResponse
  request :: (Service -> Service)
-> CreateSnapshotCopyGrant -> Request CreateSnapshotCopyGrant
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 CreateSnapshotCopyGrant
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateSnapshotCopyGrant)))
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
"CreateSnapshotCopyGrantResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe SnapshotCopyGrant -> Int -> CreateSnapshotCopyGrantResponse
CreateSnapshotCopyGrantResponse'
            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
"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 CreateSnapshotCopyGrant where
  hashWithSalt :: Int -> CreateSnapshotCopyGrant -> Int
hashWithSalt Int
_salt CreateSnapshotCopyGrant' {Maybe [Tag]
Maybe Text
Text
snapshotCopyGrantName :: Text
tags :: Maybe [Tag]
kmsKeyId :: Maybe Text
$sel:snapshotCopyGrantName:CreateSnapshotCopyGrant' :: CreateSnapshotCopyGrant -> Text
$sel:tags:CreateSnapshotCopyGrant' :: CreateSnapshotCopyGrant -> Maybe [Tag]
$sel:kmsKeyId:CreateSnapshotCopyGrant' :: CreateSnapshotCopyGrant -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kmsKeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
snapshotCopyGrantName

instance Prelude.NFData CreateSnapshotCopyGrant where
  rnf :: CreateSnapshotCopyGrant -> ()
rnf CreateSnapshotCopyGrant' {Maybe [Tag]
Maybe Text
Text
snapshotCopyGrantName :: Text
tags :: Maybe [Tag]
kmsKeyId :: Maybe Text
$sel:snapshotCopyGrantName:CreateSnapshotCopyGrant' :: CreateSnapshotCopyGrant -> Text
$sel:tags:CreateSnapshotCopyGrant' :: CreateSnapshotCopyGrant -> Maybe [Tag]
$sel:kmsKeyId:CreateSnapshotCopyGrant' :: CreateSnapshotCopyGrant -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsKeyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
snapshotCopyGrantName

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

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

instance Data.ToQuery CreateSnapshotCopyGrant where
  toQuery :: CreateSnapshotCopyGrant -> QueryString
toQuery CreateSnapshotCopyGrant' {Maybe [Tag]
Maybe Text
Text
snapshotCopyGrantName :: Text
tags :: Maybe [Tag]
kmsKeyId :: Maybe Text
$sel:snapshotCopyGrantName:CreateSnapshotCopyGrant' :: CreateSnapshotCopyGrant -> Text
$sel:tags:CreateSnapshotCopyGrant' :: CreateSnapshotCopyGrant -> Maybe [Tag]
$sel:kmsKeyId:CreateSnapshotCopyGrant' :: CreateSnapshotCopyGrant -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"CreateSnapshotCopyGrant" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2012-12-01" :: Prelude.ByteString),
        ByteString
"KmsKeyId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
kmsKeyId,
        ByteString
"Tags"
          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
"Tag" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags),
        ByteString
"SnapshotCopyGrantName"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
snapshotCopyGrantName
      ]

-- | /See:/ 'newCreateSnapshotCopyGrantResponse' smart constructor.
data CreateSnapshotCopyGrantResponse = CreateSnapshotCopyGrantResponse'
  { CreateSnapshotCopyGrantResponse -> Maybe SnapshotCopyGrant
snapshotCopyGrant :: Prelude.Maybe SnapshotCopyGrant,
    -- | The response's http status code.
    CreateSnapshotCopyGrantResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateSnapshotCopyGrantResponse
-> CreateSnapshotCopyGrantResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSnapshotCopyGrantResponse
-> CreateSnapshotCopyGrantResponse -> Bool
$c/= :: CreateSnapshotCopyGrantResponse
-> CreateSnapshotCopyGrantResponse -> Bool
== :: CreateSnapshotCopyGrantResponse
-> CreateSnapshotCopyGrantResponse -> Bool
$c== :: CreateSnapshotCopyGrantResponse
-> CreateSnapshotCopyGrantResponse -> Bool
Prelude.Eq, ReadPrec [CreateSnapshotCopyGrantResponse]
ReadPrec CreateSnapshotCopyGrantResponse
Int -> ReadS CreateSnapshotCopyGrantResponse
ReadS [CreateSnapshotCopyGrantResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateSnapshotCopyGrantResponse]
$creadListPrec :: ReadPrec [CreateSnapshotCopyGrantResponse]
readPrec :: ReadPrec CreateSnapshotCopyGrantResponse
$creadPrec :: ReadPrec CreateSnapshotCopyGrantResponse
readList :: ReadS [CreateSnapshotCopyGrantResponse]
$creadList :: ReadS [CreateSnapshotCopyGrantResponse]
readsPrec :: Int -> ReadS CreateSnapshotCopyGrantResponse
$creadsPrec :: Int -> ReadS CreateSnapshotCopyGrantResponse
Prelude.Read, Int -> CreateSnapshotCopyGrantResponse -> ShowS
[CreateSnapshotCopyGrantResponse] -> ShowS
CreateSnapshotCopyGrantResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSnapshotCopyGrantResponse] -> ShowS
$cshowList :: [CreateSnapshotCopyGrantResponse] -> ShowS
show :: CreateSnapshotCopyGrantResponse -> String
$cshow :: CreateSnapshotCopyGrantResponse -> String
showsPrec :: Int -> CreateSnapshotCopyGrantResponse -> ShowS
$cshowsPrec :: Int -> CreateSnapshotCopyGrantResponse -> ShowS
Prelude.Show, forall x.
Rep CreateSnapshotCopyGrantResponse x
-> CreateSnapshotCopyGrantResponse
forall x.
CreateSnapshotCopyGrantResponse
-> Rep CreateSnapshotCopyGrantResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateSnapshotCopyGrantResponse x
-> CreateSnapshotCopyGrantResponse
$cfrom :: forall x.
CreateSnapshotCopyGrantResponse
-> Rep CreateSnapshotCopyGrantResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateSnapshotCopyGrantResponse' 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:
--
-- 'snapshotCopyGrant', 'createSnapshotCopyGrantResponse_snapshotCopyGrant' - Undocumented member.
--
-- 'httpStatus', 'createSnapshotCopyGrantResponse_httpStatus' - The response's http status code.
newCreateSnapshotCopyGrantResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateSnapshotCopyGrantResponse
newCreateSnapshotCopyGrantResponse :: Int -> CreateSnapshotCopyGrantResponse
newCreateSnapshotCopyGrantResponse Int
pHttpStatus_ =
  CreateSnapshotCopyGrantResponse'
    { $sel:snapshotCopyGrant:CreateSnapshotCopyGrantResponse' :: Maybe SnapshotCopyGrant
snapshotCopyGrant =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateSnapshotCopyGrantResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
createSnapshotCopyGrantResponse_snapshotCopyGrant :: Lens.Lens' CreateSnapshotCopyGrantResponse (Prelude.Maybe SnapshotCopyGrant)
createSnapshotCopyGrantResponse_snapshotCopyGrant :: Lens' CreateSnapshotCopyGrantResponse (Maybe SnapshotCopyGrant)
createSnapshotCopyGrantResponse_snapshotCopyGrant = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateSnapshotCopyGrantResponse' {Maybe SnapshotCopyGrant
snapshotCopyGrant :: Maybe SnapshotCopyGrant
$sel:snapshotCopyGrant:CreateSnapshotCopyGrantResponse' :: CreateSnapshotCopyGrantResponse -> Maybe SnapshotCopyGrant
snapshotCopyGrant} -> Maybe SnapshotCopyGrant
snapshotCopyGrant) (\s :: CreateSnapshotCopyGrantResponse
s@CreateSnapshotCopyGrantResponse' {} Maybe SnapshotCopyGrant
a -> CreateSnapshotCopyGrantResponse
s {$sel:snapshotCopyGrant:CreateSnapshotCopyGrantResponse' :: Maybe SnapshotCopyGrant
snapshotCopyGrant = Maybe SnapshotCopyGrant
a} :: CreateSnapshotCopyGrantResponse)

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

instance
  Prelude.NFData
    CreateSnapshotCopyGrantResponse
  where
  rnf :: CreateSnapshotCopyGrantResponse -> ()
rnf CreateSnapshotCopyGrantResponse' {Int
Maybe SnapshotCopyGrant
httpStatus :: Int
snapshotCopyGrant :: Maybe SnapshotCopyGrant
$sel:httpStatus:CreateSnapshotCopyGrantResponse' :: CreateSnapshotCopyGrantResponse -> Int
$sel:snapshotCopyGrant:CreateSnapshotCopyGrantResponse' :: CreateSnapshotCopyGrantResponse -> Maybe SnapshotCopyGrant
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe SnapshotCopyGrant
snapshotCopyGrant
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus