{-# 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.AppRunner.CreateVpcIngressConnection
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Create an App Runner VPC Ingress Connection resource. App Runner
-- requires this resource when you want to associate your App Runner
-- service with an Amazon VPC endpoint.
module Amazonka.AppRunner.CreateVpcIngressConnection
  ( -- * Creating a Request
    CreateVpcIngressConnection (..),
    newCreateVpcIngressConnection,

    -- * Request Lenses
    createVpcIngressConnection_tags,
    createVpcIngressConnection_serviceArn,
    createVpcIngressConnection_vpcIngressConnectionName,
    createVpcIngressConnection_ingressVpcConfiguration,

    -- * Destructuring the Response
    CreateVpcIngressConnectionResponse (..),
    newCreateVpcIngressConnectionResponse,

    -- * Response Lenses
    createVpcIngressConnectionResponse_httpStatus,
    createVpcIngressConnectionResponse_vpcIngressConnection,
  )
where

import Amazonka.AppRunner.Types
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newCreateVpcIngressConnection' smart constructor.
data CreateVpcIngressConnection = CreateVpcIngressConnection'
  { -- | An optional list of metadata items that you can associate with the VPC
    -- Ingress Connection resource. A tag is a key-value pair.
    CreateVpcIngressConnection -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The Amazon Resource Name (ARN) for this App Runner service that is used
    -- to create the VPC Ingress Connection resource.
    CreateVpcIngressConnection -> Text
serviceArn :: Prelude.Text,
    -- | A name for the VPC Ingress Connection resource. It must be unique across
    -- all the active VPC Ingress Connections in your Amazon Web Services
    -- account in the Amazon Web Services Region.
    CreateVpcIngressConnection -> Text
vpcIngressConnectionName :: Prelude.Text,
    -- | Specifications for the customer’s Amazon VPC and the related Amazon Web
    -- Services PrivateLink VPC endpoint that are used to create the VPC
    -- Ingress Connection resource.
    CreateVpcIngressConnection -> IngressVpcConfiguration
ingressVpcConfiguration :: IngressVpcConfiguration
  }
  deriving (CreateVpcIngressConnection -> CreateVpcIngressConnection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateVpcIngressConnection -> CreateVpcIngressConnection -> Bool
$c/= :: CreateVpcIngressConnection -> CreateVpcIngressConnection -> Bool
== :: CreateVpcIngressConnection -> CreateVpcIngressConnection -> Bool
$c== :: CreateVpcIngressConnection -> CreateVpcIngressConnection -> Bool
Prelude.Eq, ReadPrec [CreateVpcIngressConnection]
ReadPrec CreateVpcIngressConnection
Int -> ReadS CreateVpcIngressConnection
ReadS [CreateVpcIngressConnection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateVpcIngressConnection]
$creadListPrec :: ReadPrec [CreateVpcIngressConnection]
readPrec :: ReadPrec CreateVpcIngressConnection
$creadPrec :: ReadPrec CreateVpcIngressConnection
readList :: ReadS [CreateVpcIngressConnection]
$creadList :: ReadS [CreateVpcIngressConnection]
readsPrec :: Int -> ReadS CreateVpcIngressConnection
$creadsPrec :: Int -> ReadS CreateVpcIngressConnection
Prelude.Read, Int -> CreateVpcIngressConnection -> ShowS
[CreateVpcIngressConnection] -> ShowS
CreateVpcIngressConnection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateVpcIngressConnection] -> ShowS
$cshowList :: [CreateVpcIngressConnection] -> ShowS
show :: CreateVpcIngressConnection -> String
$cshow :: CreateVpcIngressConnection -> String
showsPrec :: Int -> CreateVpcIngressConnection -> ShowS
$cshowsPrec :: Int -> CreateVpcIngressConnection -> ShowS
Prelude.Show, forall x.
Rep CreateVpcIngressConnection x -> CreateVpcIngressConnection
forall x.
CreateVpcIngressConnection -> Rep CreateVpcIngressConnection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateVpcIngressConnection x -> CreateVpcIngressConnection
$cfrom :: forall x.
CreateVpcIngressConnection -> Rep CreateVpcIngressConnection x
Prelude.Generic)

-- |
-- Create a value of 'CreateVpcIngressConnection' 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:
--
-- 'tags', 'createVpcIngressConnection_tags' - An optional list of metadata items that you can associate with the VPC
-- Ingress Connection resource. A tag is a key-value pair.
--
-- 'serviceArn', 'createVpcIngressConnection_serviceArn' - The Amazon Resource Name (ARN) for this App Runner service that is used
-- to create the VPC Ingress Connection resource.
--
-- 'vpcIngressConnectionName', 'createVpcIngressConnection_vpcIngressConnectionName' - A name for the VPC Ingress Connection resource. It must be unique across
-- all the active VPC Ingress Connections in your Amazon Web Services
-- account in the Amazon Web Services Region.
--
-- 'ingressVpcConfiguration', 'createVpcIngressConnection_ingressVpcConfiguration' - Specifications for the customer’s Amazon VPC and the related Amazon Web
-- Services PrivateLink VPC endpoint that are used to create the VPC
-- Ingress Connection resource.
newCreateVpcIngressConnection ::
  -- | 'serviceArn'
  Prelude.Text ->
  -- | 'vpcIngressConnectionName'
  Prelude.Text ->
  -- | 'ingressVpcConfiguration'
  IngressVpcConfiguration ->
  CreateVpcIngressConnection
newCreateVpcIngressConnection :: Text
-> Text -> IngressVpcConfiguration -> CreateVpcIngressConnection
newCreateVpcIngressConnection
  Text
pServiceArn_
  Text
pVpcIngressConnectionName_
  IngressVpcConfiguration
pIngressVpcConfiguration_ =
    CreateVpcIngressConnection'
      { $sel:tags:CreateVpcIngressConnection' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:serviceArn:CreateVpcIngressConnection' :: Text
serviceArn = Text
pServiceArn_,
        $sel:vpcIngressConnectionName:CreateVpcIngressConnection' :: Text
vpcIngressConnectionName =
          Text
pVpcIngressConnectionName_,
        $sel:ingressVpcConfiguration:CreateVpcIngressConnection' :: IngressVpcConfiguration
ingressVpcConfiguration =
          IngressVpcConfiguration
pIngressVpcConfiguration_
      }

-- | An optional list of metadata items that you can associate with the VPC
-- Ingress Connection resource. A tag is a key-value pair.
createVpcIngressConnection_tags :: Lens.Lens' CreateVpcIngressConnection (Prelude.Maybe [Tag])
createVpcIngressConnection_tags :: Lens' CreateVpcIngressConnection (Maybe [Tag])
createVpcIngressConnection_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVpcIngressConnection' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateVpcIngressConnection' :: CreateVpcIngressConnection -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateVpcIngressConnection
s@CreateVpcIngressConnection' {} Maybe [Tag]
a -> CreateVpcIngressConnection
s {$sel:tags:CreateVpcIngressConnection' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateVpcIngressConnection) 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 Amazon Resource Name (ARN) for this App Runner service that is used
-- to create the VPC Ingress Connection resource.
createVpcIngressConnection_serviceArn :: Lens.Lens' CreateVpcIngressConnection Prelude.Text
createVpcIngressConnection_serviceArn :: Lens' CreateVpcIngressConnection Text
createVpcIngressConnection_serviceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVpcIngressConnection' {Text
serviceArn :: Text
$sel:serviceArn:CreateVpcIngressConnection' :: CreateVpcIngressConnection -> Text
serviceArn} -> Text
serviceArn) (\s :: CreateVpcIngressConnection
s@CreateVpcIngressConnection' {} Text
a -> CreateVpcIngressConnection
s {$sel:serviceArn:CreateVpcIngressConnection' :: Text
serviceArn = Text
a} :: CreateVpcIngressConnection)

-- | A name for the VPC Ingress Connection resource. It must be unique across
-- all the active VPC Ingress Connections in your Amazon Web Services
-- account in the Amazon Web Services Region.
createVpcIngressConnection_vpcIngressConnectionName :: Lens.Lens' CreateVpcIngressConnection Prelude.Text
createVpcIngressConnection_vpcIngressConnectionName :: Lens' CreateVpcIngressConnection Text
createVpcIngressConnection_vpcIngressConnectionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVpcIngressConnection' {Text
vpcIngressConnectionName :: Text
$sel:vpcIngressConnectionName:CreateVpcIngressConnection' :: CreateVpcIngressConnection -> Text
vpcIngressConnectionName} -> Text
vpcIngressConnectionName) (\s :: CreateVpcIngressConnection
s@CreateVpcIngressConnection' {} Text
a -> CreateVpcIngressConnection
s {$sel:vpcIngressConnectionName:CreateVpcIngressConnection' :: Text
vpcIngressConnectionName = Text
a} :: CreateVpcIngressConnection)

-- | Specifications for the customer’s Amazon VPC and the related Amazon Web
-- Services PrivateLink VPC endpoint that are used to create the VPC
-- Ingress Connection resource.
createVpcIngressConnection_ingressVpcConfiguration :: Lens.Lens' CreateVpcIngressConnection IngressVpcConfiguration
createVpcIngressConnection_ingressVpcConfiguration :: Lens' CreateVpcIngressConnection IngressVpcConfiguration
createVpcIngressConnection_ingressVpcConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVpcIngressConnection' {IngressVpcConfiguration
ingressVpcConfiguration :: IngressVpcConfiguration
$sel:ingressVpcConfiguration:CreateVpcIngressConnection' :: CreateVpcIngressConnection -> IngressVpcConfiguration
ingressVpcConfiguration} -> IngressVpcConfiguration
ingressVpcConfiguration) (\s :: CreateVpcIngressConnection
s@CreateVpcIngressConnection' {} IngressVpcConfiguration
a -> CreateVpcIngressConnection
s {$sel:ingressVpcConfiguration:CreateVpcIngressConnection' :: IngressVpcConfiguration
ingressVpcConfiguration = IngressVpcConfiguration
a} :: CreateVpcIngressConnection)

instance Core.AWSRequest CreateVpcIngressConnection where
  type
    AWSResponse CreateVpcIngressConnection =
      CreateVpcIngressConnectionResponse
  request :: (Service -> Service)
-> CreateVpcIngressConnection -> Request CreateVpcIngressConnection
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 CreateVpcIngressConnection
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateVpcIngressConnection)))
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 ->
          Int -> VpcIngressConnection -> CreateVpcIngressConnectionResponse
CreateVpcIngressConnectionResponse'
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"VpcIngressConnection")
      )

instance Prelude.Hashable CreateVpcIngressConnection where
  hashWithSalt :: Int -> CreateVpcIngressConnection -> Int
hashWithSalt Int
_salt CreateVpcIngressConnection' {Maybe [Tag]
Text
IngressVpcConfiguration
ingressVpcConfiguration :: IngressVpcConfiguration
vpcIngressConnectionName :: Text
serviceArn :: Text
tags :: Maybe [Tag]
$sel:ingressVpcConfiguration:CreateVpcIngressConnection' :: CreateVpcIngressConnection -> IngressVpcConfiguration
$sel:vpcIngressConnectionName:CreateVpcIngressConnection' :: CreateVpcIngressConnection -> Text
$sel:serviceArn:CreateVpcIngressConnection' :: CreateVpcIngressConnection -> Text
$sel:tags:CreateVpcIngressConnection' :: CreateVpcIngressConnection -> Maybe [Tag]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serviceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
vpcIngressConnectionName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` IngressVpcConfiguration
ingressVpcConfiguration

instance Prelude.NFData CreateVpcIngressConnection where
  rnf :: CreateVpcIngressConnection -> ()
rnf CreateVpcIngressConnection' {Maybe [Tag]
Text
IngressVpcConfiguration
ingressVpcConfiguration :: IngressVpcConfiguration
vpcIngressConnectionName :: Text
serviceArn :: Text
tags :: Maybe [Tag]
$sel:ingressVpcConfiguration:CreateVpcIngressConnection' :: CreateVpcIngressConnection -> IngressVpcConfiguration
$sel:vpcIngressConnectionName:CreateVpcIngressConnection' :: CreateVpcIngressConnection -> Text
$sel:serviceArn:CreateVpcIngressConnection' :: CreateVpcIngressConnection -> Text
$sel:tags:CreateVpcIngressConnection' :: CreateVpcIngressConnection -> Maybe [Tag]
..} =
    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
serviceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
vpcIngressConnectionName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf IngressVpcConfiguration
ingressVpcConfiguration

instance Data.ToHeaders CreateVpcIngressConnection where
  toHeaders :: CreateVpcIngressConnection -> 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
"AppRunner.CreateVpcIngressConnection" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CreateVpcIngressConnection where
  toJSON :: CreateVpcIngressConnection -> Value
toJSON CreateVpcIngressConnection' {Maybe [Tag]
Text
IngressVpcConfiguration
ingressVpcConfiguration :: IngressVpcConfiguration
vpcIngressConnectionName :: Text
serviceArn :: Text
tags :: Maybe [Tag]
$sel:ingressVpcConfiguration:CreateVpcIngressConnection' :: CreateVpcIngressConnection -> IngressVpcConfiguration
$sel:vpcIngressConnectionName:CreateVpcIngressConnection' :: CreateVpcIngressConnection -> Text
$sel:serviceArn:CreateVpcIngressConnection' :: CreateVpcIngressConnection -> Text
$sel:tags:CreateVpcIngressConnection' :: CreateVpcIngressConnection -> Maybe [Tag]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"ServiceArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
serviceArn),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"VpcIngressConnectionName"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
vpcIngressConnectionName
              ),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"IngressVpcConfiguration"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= IngressVpcConfiguration
ingressVpcConfiguration
              )
          ]
      )

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

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

-- | /See:/ 'newCreateVpcIngressConnectionResponse' smart constructor.
data CreateVpcIngressConnectionResponse = CreateVpcIngressConnectionResponse'
  { -- | The response's http status code.
    CreateVpcIngressConnectionResponse -> Int
httpStatus :: Prelude.Int,
    -- | A description of the App Runner VPC Ingress Connection resource that\'s
    -- created by this request.
    CreateVpcIngressConnectionResponse -> VpcIngressConnection
vpcIngressConnection :: VpcIngressConnection
  }
  deriving (CreateVpcIngressConnectionResponse
-> CreateVpcIngressConnectionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateVpcIngressConnectionResponse
-> CreateVpcIngressConnectionResponse -> Bool
$c/= :: CreateVpcIngressConnectionResponse
-> CreateVpcIngressConnectionResponse -> Bool
== :: CreateVpcIngressConnectionResponse
-> CreateVpcIngressConnectionResponse -> Bool
$c== :: CreateVpcIngressConnectionResponse
-> CreateVpcIngressConnectionResponse -> Bool
Prelude.Eq, ReadPrec [CreateVpcIngressConnectionResponse]
ReadPrec CreateVpcIngressConnectionResponse
Int -> ReadS CreateVpcIngressConnectionResponse
ReadS [CreateVpcIngressConnectionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateVpcIngressConnectionResponse]
$creadListPrec :: ReadPrec [CreateVpcIngressConnectionResponse]
readPrec :: ReadPrec CreateVpcIngressConnectionResponse
$creadPrec :: ReadPrec CreateVpcIngressConnectionResponse
readList :: ReadS [CreateVpcIngressConnectionResponse]
$creadList :: ReadS [CreateVpcIngressConnectionResponse]
readsPrec :: Int -> ReadS CreateVpcIngressConnectionResponse
$creadsPrec :: Int -> ReadS CreateVpcIngressConnectionResponse
Prelude.Read, Int -> CreateVpcIngressConnectionResponse -> ShowS
[CreateVpcIngressConnectionResponse] -> ShowS
CreateVpcIngressConnectionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateVpcIngressConnectionResponse] -> ShowS
$cshowList :: [CreateVpcIngressConnectionResponse] -> ShowS
show :: CreateVpcIngressConnectionResponse -> String
$cshow :: CreateVpcIngressConnectionResponse -> String
showsPrec :: Int -> CreateVpcIngressConnectionResponse -> ShowS
$cshowsPrec :: Int -> CreateVpcIngressConnectionResponse -> ShowS
Prelude.Show, forall x.
Rep CreateVpcIngressConnectionResponse x
-> CreateVpcIngressConnectionResponse
forall x.
CreateVpcIngressConnectionResponse
-> Rep CreateVpcIngressConnectionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateVpcIngressConnectionResponse x
-> CreateVpcIngressConnectionResponse
$cfrom :: forall x.
CreateVpcIngressConnectionResponse
-> Rep CreateVpcIngressConnectionResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateVpcIngressConnectionResponse' 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', 'createVpcIngressConnectionResponse_httpStatus' - The response's http status code.
--
-- 'vpcIngressConnection', 'createVpcIngressConnectionResponse_vpcIngressConnection' - A description of the App Runner VPC Ingress Connection resource that\'s
-- created by this request.
newCreateVpcIngressConnectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'vpcIngressConnection'
  VpcIngressConnection ->
  CreateVpcIngressConnectionResponse
newCreateVpcIngressConnectionResponse :: Int -> VpcIngressConnection -> CreateVpcIngressConnectionResponse
newCreateVpcIngressConnectionResponse
  Int
pHttpStatus_
  VpcIngressConnection
pVpcIngressConnection_ =
    CreateVpcIngressConnectionResponse'
      { $sel:httpStatus:CreateVpcIngressConnectionResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:vpcIngressConnection:CreateVpcIngressConnectionResponse' :: VpcIngressConnection
vpcIngressConnection =
          VpcIngressConnection
pVpcIngressConnection_
      }

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

-- | A description of the App Runner VPC Ingress Connection resource that\'s
-- created by this request.
createVpcIngressConnectionResponse_vpcIngressConnection :: Lens.Lens' CreateVpcIngressConnectionResponse VpcIngressConnection
createVpcIngressConnectionResponse_vpcIngressConnection :: Lens' CreateVpcIngressConnectionResponse VpcIngressConnection
createVpcIngressConnectionResponse_vpcIngressConnection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVpcIngressConnectionResponse' {VpcIngressConnection
vpcIngressConnection :: VpcIngressConnection
$sel:vpcIngressConnection:CreateVpcIngressConnectionResponse' :: CreateVpcIngressConnectionResponse -> VpcIngressConnection
vpcIngressConnection} -> VpcIngressConnection
vpcIngressConnection) (\s :: CreateVpcIngressConnectionResponse
s@CreateVpcIngressConnectionResponse' {} VpcIngressConnection
a -> CreateVpcIngressConnectionResponse
s {$sel:vpcIngressConnection:CreateVpcIngressConnectionResponse' :: VpcIngressConnection
vpcIngressConnection = VpcIngressConnection
a} :: CreateVpcIngressConnectionResponse)

instance
  Prelude.NFData
    CreateVpcIngressConnectionResponse
  where
  rnf :: CreateVpcIngressConnectionResponse -> ()
rnf CreateVpcIngressConnectionResponse' {Int
VpcIngressConnection
vpcIngressConnection :: VpcIngressConnection
httpStatus :: Int
$sel:vpcIngressConnection:CreateVpcIngressConnectionResponse' :: CreateVpcIngressConnectionResponse -> VpcIngressConnection
$sel:httpStatus:CreateVpcIngressConnectionResponse' :: CreateVpcIngressConnectionResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf VpcIngressConnection
vpcIngressConnection