{-# 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.CreateVpcPeeringConnection
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Establishes a VPC peering connection between a virtual private cloud
-- (VPC) in an Amazon Web Services account with the VPC for your Amazon
-- GameLift fleet. VPC peering enables the game servers on your fleet to
-- communicate directly with other Amazon Web Services resources. You can
-- peer with VPCs in any Amazon Web Services account that 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. For
-- more information, see
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/vpc-peering.html VPC Peering with Amazon GameLift Fleets>.
--
-- Before calling this operation to establish the peering connection, you
-- first need to use
-- <https://docs.aws.amazon.com/gamelift/latest/apireference/API_CreateVpcPeeringAuthorization.html CreateVpcPeeringAuthorization>
-- and identify the VPC you want to peer with. Once the authorization for
-- the specified VPC is issued, you have 24 hours to establish the
-- connection. These two operations handle all tasks necessary to peer the
-- two VPCs, including acceptance, updating routing tables, etc.
--
-- To establish the connection, call this operation from the Amazon Web
-- Services account that is used to manage the Amazon GameLift fleets.
-- Identify the following values: (1) The ID of the fleet you want to be
-- enable a VPC peering connection for; (2) The Amazon Web Services account
-- with the VPC that you want to peer with; and (3) The ID of the VPC you
-- want to peer with. This operation is asynchronous. If successful, a
-- connection request is created. You can use continuous polling to track
-- the request\'s status using
-- <https://docs.aws.amazon.com/gamelift/latest/apireference/API_DescribeVpcPeeringConnections.html DescribeVpcPeeringConnections>
-- , or by monitoring fleet events for success or failure using
-- <https://docs.aws.amazon.com/gamelift/latest/apireference/API_DescribeFleetEvents.html DescribeFleetEvents>
-- .
--
-- __Related actions__
--
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/reference-awssdk.html#reference-awssdk-resources-fleets All APIs by task>
module Amazonka.GameLift.CreateVpcPeeringConnection
  ( -- * Creating a Request
    CreateVpcPeeringConnection (..),
    newCreateVpcPeeringConnection,

    -- * Request Lenses
    createVpcPeeringConnection_fleetId,
    createVpcPeeringConnection_peerVpcAwsAccountId,
    createVpcPeeringConnection_peerVpcId,

    -- * Destructuring the Response
    CreateVpcPeeringConnectionResponse (..),
    newCreateVpcPeeringConnectionResponse,

    -- * Response Lenses
    createVpcPeeringConnectionResponse_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:/ 'newCreateVpcPeeringConnection' smart constructor.
data CreateVpcPeeringConnection = CreateVpcPeeringConnection'
  { -- | A unique identifier for the fleet. You can use either the fleet ID or
    -- ARN value. This tells Amazon GameLift which GameLift VPC to peer with.
    CreateVpcPeeringConnection -> Text
fleetId :: Prelude.Text,
    -- | A unique identifier for the Amazon Web Services account with the VPC
    -- that you want to peer your Amazon GameLift fleet with. You can find your
    -- Account ID in the Amazon Web Services Management Console under account
    -- settings.
    CreateVpcPeeringConnection -> Text
peerVpcAwsAccountId :: 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>.
    CreateVpcPeeringConnection -> Text
peerVpcId :: Prelude.Text
  }
  deriving (CreateVpcPeeringConnection -> CreateVpcPeeringConnection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateVpcPeeringConnection -> CreateVpcPeeringConnection -> Bool
$c/= :: CreateVpcPeeringConnection -> CreateVpcPeeringConnection -> Bool
== :: CreateVpcPeeringConnection -> CreateVpcPeeringConnection -> Bool
$c== :: CreateVpcPeeringConnection -> CreateVpcPeeringConnection -> Bool
Prelude.Eq, ReadPrec [CreateVpcPeeringConnection]
ReadPrec CreateVpcPeeringConnection
Int -> ReadS CreateVpcPeeringConnection
ReadS [CreateVpcPeeringConnection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateVpcPeeringConnection]
$creadListPrec :: ReadPrec [CreateVpcPeeringConnection]
readPrec :: ReadPrec CreateVpcPeeringConnection
$creadPrec :: ReadPrec CreateVpcPeeringConnection
readList :: ReadS [CreateVpcPeeringConnection]
$creadList :: ReadS [CreateVpcPeeringConnection]
readsPrec :: Int -> ReadS CreateVpcPeeringConnection
$creadsPrec :: Int -> ReadS CreateVpcPeeringConnection
Prelude.Read, Int -> CreateVpcPeeringConnection -> ShowS
[CreateVpcPeeringConnection] -> ShowS
CreateVpcPeeringConnection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateVpcPeeringConnection] -> ShowS
$cshowList :: [CreateVpcPeeringConnection] -> ShowS
show :: CreateVpcPeeringConnection -> String
$cshow :: CreateVpcPeeringConnection -> String
showsPrec :: Int -> CreateVpcPeeringConnection -> ShowS
$cshowsPrec :: Int -> CreateVpcPeeringConnection -> ShowS
Prelude.Show, forall x.
Rep CreateVpcPeeringConnection x -> CreateVpcPeeringConnection
forall x.
CreateVpcPeeringConnection -> Rep CreateVpcPeeringConnection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateVpcPeeringConnection x -> CreateVpcPeeringConnection
$cfrom :: forall x.
CreateVpcPeeringConnection -> Rep CreateVpcPeeringConnection x
Prelude.Generic)

-- |
-- Create a value of 'CreateVpcPeeringConnection' 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:
--
-- 'fleetId', 'createVpcPeeringConnection_fleetId' - A unique identifier for the fleet. You can use either the fleet ID or
-- ARN value. This tells Amazon GameLift which GameLift VPC to peer with.
--
-- 'peerVpcAwsAccountId', 'createVpcPeeringConnection_peerVpcAwsAccountId' - A unique identifier for the Amazon Web Services account with the VPC
-- that you want to peer your Amazon GameLift fleet with. You can find your
-- Account ID in the Amazon Web Services Management Console under account
-- settings.
--
-- 'peerVpcId', 'createVpcPeeringConnection_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>.
newCreateVpcPeeringConnection ::
  -- | 'fleetId'
  Prelude.Text ->
  -- | 'peerVpcAwsAccountId'
  Prelude.Text ->
  -- | 'peerVpcId'
  Prelude.Text ->
  CreateVpcPeeringConnection
newCreateVpcPeeringConnection :: Text -> Text -> Text -> CreateVpcPeeringConnection
newCreateVpcPeeringConnection
  Text
pFleetId_
  Text
pPeerVpcAwsAccountId_
  Text
pPeerVpcId_ =
    CreateVpcPeeringConnection'
      { $sel:fleetId:CreateVpcPeeringConnection' :: Text
fleetId = Text
pFleetId_,
        $sel:peerVpcAwsAccountId:CreateVpcPeeringConnection' :: Text
peerVpcAwsAccountId = Text
pPeerVpcAwsAccountId_,
        $sel:peerVpcId:CreateVpcPeeringConnection' :: Text
peerVpcId = Text
pPeerVpcId_
      }

-- | A unique identifier for the fleet. You can use either the fleet ID or
-- ARN value. This tells Amazon GameLift which GameLift VPC to peer with.
createVpcPeeringConnection_fleetId :: Lens.Lens' CreateVpcPeeringConnection Prelude.Text
createVpcPeeringConnection_fleetId :: Lens' CreateVpcPeeringConnection Text
createVpcPeeringConnection_fleetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVpcPeeringConnection' {Text
fleetId :: Text
$sel:fleetId:CreateVpcPeeringConnection' :: CreateVpcPeeringConnection -> Text
fleetId} -> Text
fleetId) (\s :: CreateVpcPeeringConnection
s@CreateVpcPeeringConnection' {} Text
a -> CreateVpcPeeringConnection
s {$sel:fleetId:CreateVpcPeeringConnection' :: Text
fleetId = Text
a} :: CreateVpcPeeringConnection)

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

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

instance Core.AWSRequest CreateVpcPeeringConnection where
  type
    AWSResponse CreateVpcPeeringConnection =
      CreateVpcPeeringConnectionResponse
  request :: (Service -> Service)
-> CreateVpcPeeringConnection -> Request CreateVpcPeeringConnection
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 CreateVpcPeeringConnection
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateVpcPeeringConnection)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> CreateVpcPeeringConnectionResponse
CreateVpcPeeringConnectionResponse'
            forall (f :: * -> *) a b. Functor 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 CreateVpcPeeringConnection where
  hashWithSalt :: Int -> CreateVpcPeeringConnection -> Int
hashWithSalt Int
_salt CreateVpcPeeringConnection' {Text
peerVpcId :: Text
peerVpcAwsAccountId :: Text
fleetId :: Text
$sel:peerVpcId:CreateVpcPeeringConnection' :: CreateVpcPeeringConnection -> Text
$sel:peerVpcAwsAccountId:CreateVpcPeeringConnection' :: CreateVpcPeeringConnection -> Text
$sel:fleetId:CreateVpcPeeringConnection' :: CreateVpcPeeringConnection -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
fleetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
peerVpcAwsAccountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
peerVpcId

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

instance Data.ToHeaders CreateVpcPeeringConnection where
  toHeaders :: CreateVpcPeeringConnection -> 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.CreateVpcPeeringConnection" ::
                          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 CreateVpcPeeringConnection where
  toJSON :: CreateVpcPeeringConnection -> Value
toJSON CreateVpcPeeringConnection' {Text
peerVpcId :: Text
peerVpcAwsAccountId :: Text
fleetId :: Text
$sel:peerVpcId:CreateVpcPeeringConnection' :: CreateVpcPeeringConnection -> Text
$sel:peerVpcAwsAccountId:CreateVpcPeeringConnection' :: CreateVpcPeeringConnection -> Text
$sel:fleetId:CreateVpcPeeringConnection' :: CreateVpcPeeringConnection -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"FleetId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
fleetId),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"PeerVpcAwsAccountId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
peerVpcAwsAccountId),
            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 CreateVpcPeeringConnection where
  toPath :: CreateVpcPeeringConnection -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'CreateVpcPeeringConnectionResponse' 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:
--
-- 'httpStatus', 'createVpcPeeringConnectionResponse_httpStatus' - The response's http status code.
newCreateVpcPeeringConnectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateVpcPeeringConnectionResponse
newCreateVpcPeeringConnectionResponse :: Int -> CreateVpcPeeringConnectionResponse
newCreateVpcPeeringConnectionResponse Int
pHttpStatus_ =
  CreateVpcPeeringConnectionResponse'
    { $sel:httpStatus:CreateVpcPeeringConnectionResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance
  Prelude.NFData
    CreateVpcPeeringConnectionResponse
  where
  rnf :: CreateVpcPeeringConnectionResponse -> ()
rnf CreateVpcPeeringConnectionResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateVpcPeeringConnectionResponse' :: CreateVpcPeeringConnectionResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus