{-# 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.GameLift.CreateVpcPeeringAuthorization
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Requests authorization to create or delete a peer connection between the
-- VPC for your Amazon GameLift fleet and a virtual private cloud (VPC) in
-- your Amazon Web Services account. VPC peering enables the game servers
-- on your fleet to communicate directly with other Amazon Web Services
-- resources. After you\'ve received authorization, use
-- <https://docs.aws.amazon.com/gamelift/latest/apireference/API_CreateVpcPeeringConnection.html CreateVpcPeeringConnection>
-- to establish the peering connection. For more information, see
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/vpc-peering.html VPC Peering with Amazon GameLift Fleets>.
--
-- You can peer with VPCs that are owned by any Amazon Web Services account
-- you have access to, including the account that you use to manage your
-- Amazon GameLift fleets. You cannot peer with VPCs that are in different
-- Regions.
--
-- To request authorization to create a connection, call this operation
-- from the Amazon Web Services account with the VPC that you want to peer
-- to your Amazon GameLift fleet. For example, to enable your game servers
-- to retrieve data from a DynamoDB table, use the account that manages
-- that DynamoDB resource. Identify the following values: (1) The ID of the
-- VPC that you want to peer with, and (2) the ID of the Amazon Web
-- Services account that you use to manage Amazon GameLift. If successful,
-- VPC peering is authorized for the specified VPC.
--
-- To request authorization to delete a connection, call this operation
-- from the Amazon Web Services account with the VPC that is peered with
-- your Amazon GameLift fleet. Identify the following values: (1) VPC ID
-- that you want to delete the peering connection for, and (2) ID of the
-- Amazon Web Services account that you use to manage Amazon GameLift.
--
-- The authorization remains valid for 24 hours unless it is canceled. You
-- must create or delete the peering connection while the authorization is
-- valid.
--
-- __Related actions__
--
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/reference-awssdk.html#reference-awssdk-resources-fleets All APIs by task>
module Amazonka.GameLift.CreateVpcPeeringAuthorization
  ( -- * Creating a Request
    CreateVpcPeeringAuthorization (..),
    newCreateVpcPeeringAuthorization,

    -- * Request Lenses
    createVpcPeeringAuthorization_gameLiftAwsAccountId,
    createVpcPeeringAuthorization_peerVpcId,

    -- * Destructuring the Response
    CreateVpcPeeringAuthorizationResponse (..),
    newCreateVpcPeeringAuthorizationResponse,

    -- * Response Lenses
    createVpcPeeringAuthorizationResponse_vpcPeeringAuthorization,
    createVpcPeeringAuthorizationResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateVpcPeeringAuthorization' smart constructor.
data CreateVpcPeeringAuthorization = CreateVpcPeeringAuthorization'
  { -- | A unique identifier for the Amazon Web Services account that you use to
    -- manage your GameLift fleet. You can find your Account ID in the Amazon
    -- Web Services Management Console under account settings.
    CreateVpcPeeringAuthorization -> Text
gameLiftAwsAccountId :: Prelude.Text,
    -- | A unique identifier for a VPC with resources to be accessed by your
    -- GameLift fleet. The VPC must be in the same Region as your fleet. To
    -- look up a VPC ID, use the
    -- <https://console.aws.amazon.com/vpc/ VPC Dashboard> in the Amazon Web
    -- Services Management Console. Learn more about VPC peering in
    -- <https://docs.aws.amazon.com/gamelift/latest/developerguide/vpc-peering.html VPC Peering with GameLift Fleets>.
    CreateVpcPeeringAuthorization -> Text
peerVpcId :: Prelude.Text
  }
  deriving (CreateVpcPeeringAuthorization
-> CreateVpcPeeringAuthorization -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateVpcPeeringAuthorization
-> CreateVpcPeeringAuthorization -> Bool
$c/= :: CreateVpcPeeringAuthorization
-> CreateVpcPeeringAuthorization -> Bool
== :: CreateVpcPeeringAuthorization
-> CreateVpcPeeringAuthorization -> Bool
$c== :: CreateVpcPeeringAuthorization
-> CreateVpcPeeringAuthorization -> Bool
Prelude.Eq, ReadPrec [CreateVpcPeeringAuthorization]
ReadPrec CreateVpcPeeringAuthorization
Int -> ReadS CreateVpcPeeringAuthorization
ReadS [CreateVpcPeeringAuthorization]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateVpcPeeringAuthorization]
$creadListPrec :: ReadPrec [CreateVpcPeeringAuthorization]
readPrec :: ReadPrec CreateVpcPeeringAuthorization
$creadPrec :: ReadPrec CreateVpcPeeringAuthorization
readList :: ReadS [CreateVpcPeeringAuthorization]
$creadList :: ReadS [CreateVpcPeeringAuthorization]
readsPrec :: Int -> ReadS CreateVpcPeeringAuthorization
$creadsPrec :: Int -> ReadS CreateVpcPeeringAuthorization
Prelude.Read, Int -> CreateVpcPeeringAuthorization -> ShowS
[CreateVpcPeeringAuthorization] -> ShowS
CreateVpcPeeringAuthorization -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateVpcPeeringAuthorization] -> ShowS
$cshowList :: [CreateVpcPeeringAuthorization] -> ShowS
show :: CreateVpcPeeringAuthorization -> String
$cshow :: CreateVpcPeeringAuthorization -> String
showsPrec :: Int -> CreateVpcPeeringAuthorization -> ShowS
$cshowsPrec :: Int -> CreateVpcPeeringAuthorization -> ShowS
Prelude.Show, forall x.
Rep CreateVpcPeeringAuthorization x
-> CreateVpcPeeringAuthorization
forall x.
CreateVpcPeeringAuthorization
-> Rep CreateVpcPeeringAuthorization x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateVpcPeeringAuthorization x
-> CreateVpcPeeringAuthorization
$cfrom :: forall x.
CreateVpcPeeringAuthorization
-> Rep CreateVpcPeeringAuthorization x
Prelude.Generic)

-- |
-- Create a value of 'CreateVpcPeeringAuthorization' 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:
--
-- 'gameLiftAwsAccountId', 'createVpcPeeringAuthorization_gameLiftAwsAccountId' - A unique identifier for the Amazon Web Services account that you use to
-- manage your GameLift fleet. You can find your Account ID in the Amazon
-- Web Services Management Console under account settings.
--
-- 'peerVpcId', 'createVpcPeeringAuthorization_peerVpcId' - A unique identifier for a VPC with resources to be accessed by your
-- GameLift fleet. The VPC must be in the same Region as your fleet. To
-- look up a VPC ID, use the
-- <https://console.aws.amazon.com/vpc/ VPC Dashboard> in the Amazon Web
-- Services Management Console. Learn more about VPC peering in
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/vpc-peering.html VPC Peering with GameLift Fleets>.
newCreateVpcPeeringAuthorization ::
  -- | 'gameLiftAwsAccountId'
  Prelude.Text ->
  -- | 'peerVpcId'
  Prelude.Text ->
  CreateVpcPeeringAuthorization
newCreateVpcPeeringAuthorization :: Text -> Text -> CreateVpcPeeringAuthorization
newCreateVpcPeeringAuthorization
  Text
pGameLiftAwsAccountId_
  Text
pPeerVpcId_ =
    CreateVpcPeeringAuthorization'
      { $sel:gameLiftAwsAccountId:CreateVpcPeeringAuthorization' :: Text
gameLiftAwsAccountId =
          Text
pGameLiftAwsAccountId_,
        $sel:peerVpcId:CreateVpcPeeringAuthorization' :: Text
peerVpcId = Text
pPeerVpcId_
      }

-- | A unique identifier for the Amazon Web Services account that you use to
-- manage your GameLift fleet. You can find your Account ID in the Amazon
-- Web Services Management Console under account settings.
createVpcPeeringAuthorization_gameLiftAwsAccountId :: Lens.Lens' CreateVpcPeeringAuthorization Prelude.Text
createVpcPeeringAuthorization_gameLiftAwsAccountId :: Lens' CreateVpcPeeringAuthorization Text
createVpcPeeringAuthorization_gameLiftAwsAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVpcPeeringAuthorization' {Text
gameLiftAwsAccountId :: Text
$sel:gameLiftAwsAccountId:CreateVpcPeeringAuthorization' :: CreateVpcPeeringAuthorization -> Text
gameLiftAwsAccountId} -> Text
gameLiftAwsAccountId) (\s :: CreateVpcPeeringAuthorization
s@CreateVpcPeeringAuthorization' {} Text
a -> CreateVpcPeeringAuthorization
s {$sel:gameLiftAwsAccountId:CreateVpcPeeringAuthorization' :: Text
gameLiftAwsAccountId = Text
a} :: CreateVpcPeeringAuthorization)

-- | A unique identifier for a VPC with resources to be accessed by your
-- GameLift fleet. The VPC must be in the same Region as your fleet. To
-- look up a VPC ID, use the
-- <https://console.aws.amazon.com/vpc/ VPC Dashboard> in the Amazon Web
-- Services Management Console. Learn more about VPC peering in
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/vpc-peering.html VPC Peering with GameLift Fleets>.
createVpcPeeringAuthorization_peerVpcId :: Lens.Lens' CreateVpcPeeringAuthorization Prelude.Text
createVpcPeeringAuthorization_peerVpcId :: Lens' CreateVpcPeeringAuthorization Text
createVpcPeeringAuthorization_peerVpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVpcPeeringAuthorization' {Text
peerVpcId :: Text
$sel:peerVpcId:CreateVpcPeeringAuthorization' :: CreateVpcPeeringAuthorization -> Text
peerVpcId} -> Text
peerVpcId) (\s :: CreateVpcPeeringAuthorization
s@CreateVpcPeeringAuthorization' {} Text
a -> CreateVpcPeeringAuthorization
s {$sel:peerVpcId:CreateVpcPeeringAuthorization' :: Text
peerVpcId = Text
a} :: CreateVpcPeeringAuthorization)

instance
  Core.AWSRequest
    CreateVpcPeeringAuthorization
  where
  type
    AWSResponse CreateVpcPeeringAuthorization =
      CreateVpcPeeringAuthorizationResponse
  request :: (Service -> Service)
-> CreateVpcPeeringAuthorization
-> Request CreateVpcPeeringAuthorization
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 CreateVpcPeeringAuthorization
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateVpcPeeringAuthorization)))
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 VpcPeeringAuthorization
-> Int -> CreateVpcPeeringAuthorizationResponse
CreateVpcPeeringAuthorizationResponse'
            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
"VpcPeeringAuthorization")
            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
    CreateVpcPeeringAuthorization
  where
  hashWithSalt :: Int -> CreateVpcPeeringAuthorization -> Int
hashWithSalt Int
_salt CreateVpcPeeringAuthorization' {Text
peerVpcId :: Text
gameLiftAwsAccountId :: Text
$sel:peerVpcId:CreateVpcPeeringAuthorization' :: CreateVpcPeeringAuthorization -> Text
$sel:gameLiftAwsAccountId:CreateVpcPeeringAuthorization' :: CreateVpcPeeringAuthorization -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
gameLiftAwsAccountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
peerVpcId

instance Prelude.NFData CreateVpcPeeringAuthorization where
  rnf :: CreateVpcPeeringAuthorization -> ()
rnf CreateVpcPeeringAuthorization' {Text
peerVpcId :: Text
gameLiftAwsAccountId :: Text
$sel:peerVpcId:CreateVpcPeeringAuthorization' :: CreateVpcPeeringAuthorization -> Text
$sel:gameLiftAwsAccountId:CreateVpcPeeringAuthorization' :: CreateVpcPeeringAuthorization -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
gameLiftAwsAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
peerVpcId

instance Data.ToHeaders CreateVpcPeeringAuthorization where
  toHeaders :: CreateVpcPeeringAuthorization -> 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
"GameLift.CreateVpcPeeringAuthorization" ::
                          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 CreateVpcPeeringAuthorization where
  toJSON :: CreateVpcPeeringAuthorization -> Value
toJSON CreateVpcPeeringAuthorization' {Text
peerVpcId :: Text
gameLiftAwsAccountId :: Text
$sel:peerVpcId:CreateVpcPeeringAuthorization' :: CreateVpcPeeringAuthorization -> Text
$sel:gameLiftAwsAccountId:CreateVpcPeeringAuthorization' :: CreateVpcPeeringAuthorization -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              ( Key
"GameLiftAwsAccountId"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
gameLiftAwsAccountId
              ),
            forall a. a -> Maybe a
Prelude.Just (Key
"PeerVpcId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
peerVpcId)
          ]
      )

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

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

-- | /See:/ 'newCreateVpcPeeringAuthorizationResponse' smart constructor.
data CreateVpcPeeringAuthorizationResponse = CreateVpcPeeringAuthorizationResponse'
  { -- | Details on the requested VPC peering authorization, including
    -- expiration.
    CreateVpcPeeringAuthorizationResponse
-> Maybe VpcPeeringAuthorization
vpcPeeringAuthorization :: Prelude.Maybe VpcPeeringAuthorization,
    -- | The response's http status code.
    CreateVpcPeeringAuthorizationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateVpcPeeringAuthorizationResponse
-> CreateVpcPeeringAuthorizationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateVpcPeeringAuthorizationResponse
-> CreateVpcPeeringAuthorizationResponse -> Bool
$c/= :: CreateVpcPeeringAuthorizationResponse
-> CreateVpcPeeringAuthorizationResponse -> Bool
== :: CreateVpcPeeringAuthorizationResponse
-> CreateVpcPeeringAuthorizationResponse -> Bool
$c== :: CreateVpcPeeringAuthorizationResponse
-> CreateVpcPeeringAuthorizationResponse -> Bool
Prelude.Eq, ReadPrec [CreateVpcPeeringAuthorizationResponse]
ReadPrec CreateVpcPeeringAuthorizationResponse
Int -> ReadS CreateVpcPeeringAuthorizationResponse
ReadS [CreateVpcPeeringAuthorizationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateVpcPeeringAuthorizationResponse]
$creadListPrec :: ReadPrec [CreateVpcPeeringAuthorizationResponse]
readPrec :: ReadPrec CreateVpcPeeringAuthorizationResponse
$creadPrec :: ReadPrec CreateVpcPeeringAuthorizationResponse
readList :: ReadS [CreateVpcPeeringAuthorizationResponse]
$creadList :: ReadS [CreateVpcPeeringAuthorizationResponse]
readsPrec :: Int -> ReadS CreateVpcPeeringAuthorizationResponse
$creadsPrec :: Int -> ReadS CreateVpcPeeringAuthorizationResponse
Prelude.Read, Int -> CreateVpcPeeringAuthorizationResponse -> ShowS
[CreateVpcPeeringAuthorizationResponse] -> ShowS
CreateVpcPeeringAuthorizationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateVpcPeeringAuthorizationResponse] -> ShowS
$cshowList :: [CreateVpcPeeringAuthorizationResponse] -> ShowS
show :: CreateVpcPeeringAuthorizationResponse -> String
$cshow :: CreateVpcPeeringAuthorizationResponse -> String
showsPrec :: Int -> CreateVpcPeeringAuthorizationResponse -> ShowS
$cshowsPrec :: Int -> CreateVpcPeeringAuthorizationResponse -> ShowS
Prelude.Show, forall x.
Rep CreateVpcPeeringAuthorizationResponse x
-> CreateVpcPeeringAuthorizationResponse
forall x.
CreateVpcPeeringAuthorizationResponse
-> Rep CreateVpcPeeringAuthorizationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateVpcPeeringAuthorizationResponse x
-> CreateVpcPeeringAuthorizationResponse
$cfrom :: forall x.
CreateVpcPeeringAuthorizationResponse
-> Rep CreateVpcPeeringAuthorizationResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateVpcPeeringAuthorizationResponse' 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:
--
-- 'vpcPeeringAuthorization', 'createVpcPeeringAuthorizationResponse_vpcPeeringAuthorization' - Details on the requested VPC peering authorization, including
-- expiration.
--
-- 'httpStatus', 'createVpcPeeringAuthorizationResponse_httpStatus' - The response's http status code.
newCreateVpcPeeringAuthorizationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateVpcPeeringAuthorizationResponse
newCreateVpcPeeringAuthorizationResponse :: Int -> CreateVpcPeeringAuthorizationResponse
newCreateVpcPeeringAuthorizationResponse Int
pHttpStatus_ =
  CreateVpcPeeringAuthorizationResponse'
    { $sel:vpcPeeringAuthorization:CreateVpcPeeringAuthorizationResponse' :: Maybe VpcPeeringAuthorization
vpcPeeringAuthorization =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateVpcPeeringAuthorizationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Details on the requested VPC peering authorization, including
-- expiration.
createVpcPeeringAuthorizationResponse_vpcPeeringAuthorization :: Lens.Lens' CreateVpcPeeringAuthorizationResponse (Prelude.Maybe VpcPeeringAuthorization)
createVpcPeeringAuthorizationResponse_vpcPeeringAuthorization :: Lens'
  CreateVpcPeeringAuthorizationResponse
  (Maybe VpcPeeringAuthorization)
createVpcPeeringAuthorizationResponse_vpcPeeringAuthorization = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVpcPeeringAuthorizationResponse' {Maybe VpcPeeringAuthorization
vpcPeeringAuthorization :: Maybe VpcPeeringAuthorization
$sel:vpcPeeringAuthorization:CreateVpcPeeringAuthorizationResponse' :: CreateVpcPeeringAuthorizationResponse
-> Maybe VpcPeeringAuthorization
vpcPeeringAuthorization} -> Maybe VpcPeeringAuthorization
vpcPeeringAuthorization) (\s :: CreateVpcPeeringAuthorizationResponse
s@CreateVpcPeeringAuthorizationResponse' {} Maybe VpcPeeringAuthorization
a -> CreateVpcPeeringAuthorizationResponse
s {$sel:vpcPeeringAuthorization:CreateVpcPeeringAuthorizationResponse' :: Maybe VpcPeeringAuthorization
vpcPeeringAuthorization = Maybe VpcPeeringAuthorization
a} :: CreateVpcPeeringAuthorizationResponse)

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

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