{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.VpcIngressConnection
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.AppRunner.Types.VpcIngressConnection where

import Amazonka.AppRunner.Types.IngressVpcConfiguration
import Amazonka.AppRunner.Types.VpcIngressConnectionStatus
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

-- | The App Runner resource that specifies an App Runner endpoint for
-- incoming traffic. It establishes a connection between a VPC interface
-- endpoint and a App Runner service, to make your App Runner service
-- accessible from only within an Amazon VPC.
--
-- /See:/ 'newVpcIngressConnection' smart constructor.
data VpcIngressConnection = VpcIngressConnection'
  { -- | The Account Id you use to create the VPC Ingress Connection resource.
    VpcIngressConnection -> Maybe Text
accountId :: Prelude.Maybe Prelude.Text,
    -- | The time when the VPC Ingress Connection was created. It\'s in the Unix
    -- time stamp format.
    --
    -- -   Type: Timestamp
    --
    -- -   Required: Yes
    VpcIngressConnection -> Maybe POSIX
createdAt :: Prelude.Maybe Data.POSIX,
    -- | The time when the App Runner service was deleted. It\'s in the Unix time
    -- stamp format.
    --
    -- -   Type: Timestamp
    --
    -- -   Required: No
    VpcIngressConnection -> Maybe POSIX
deletedAt :: Prelude.Maybe Data.POSIX,
    -- | The domain name associated with the VPC Ingress Connection resource.
    VpcIngressConnection -> Maybe Text
domainName :: Prelude.Maybe Prelude.Text,
    -- | Specifications for the customer’s VPC and related PrivateLink VPC
    -- endpoint that are used to associate with the VPC Ingress Connection
    -- resource.
    VpcIngressConnection -> Maybe IngressVpcConfiguration
ingressVpcConfiguration :: Prelude.Maybe IngressVpcConfiguration,
    -- | The Amazon Resource Name (ARN) of the service associated with the VPC
    -- Ingress Connection.
    VpcIngressConnection -> Maybe Text
serviceArn :: Prelude.Maybe Prelude.Text,
    -- | The current status of the VPC Ingress Connection. The VPC Ingress
    -- Connection displays one of the following statuses: @AVAILABLE@,
    -- @PENDING_CREATION@, @PENDING_UPDATE@,
    -- @PENDING_DELETION@,@FAILED_CREATION@, @FAILED_UPDATE@,
    -- @FAILED_DELETION@, and @DELETED@..
    VpcIngressConnection -> Maybe VpcIngressConnectionStatus
status :: Prelude.Maybe VpcIngressConnectionStatus,
    -- | The Amazon Resource Name (ARN) of the VPC Ingress Connection.
    VpcIngressConnection -> Maybe Text
vpcIngressConnectionArn :: Prelude.Maybe Prelude.Text,
    -- | The customer-provided VPC Ingress Connection name.
    VpcIngressConnection -> Maybe Text
vpcIngressConnectionName :: Prelude.Maybe Prelude.Text
  }
  deriving (VpcIngressConnection -> VpcIngressConnection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VpcIngressConnection -> VpcIngressConnection -> Bool
$c/= :: VpcIngressConnection -> VpcIngressConnection -> Bool
== :: VpcIngressConnection -> VpcIngressConnection -> Bool
$c== :: VpcIngressConnection -> VpcIngressConnection -> Bool
Prelude.Eq, ReadPrec [VpcIngressConnection]
ReadPrec VpcIngressConnection
Int -> ReadS VpcIngressConnection
ReadS [VpcIngressConnection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VpcIngressConnection]
$creadListPrec :: ReadPrec [VpcIngressConnection]
readPrec :: ReadPrec VpcIngressConnection
$creadPrec :: ReadPrec VpcIngressConnection
readList :: ReadS [VpcIngressConnection]
$creadList :: ReadS [VpcIngressConnection]
readsPrec :: Int -> ReadS VpcIngressConnection
$creadsPrec :: Int -> ReadS VpcIngressConnection
Prelude.Read, Int -> VpcIngressConnection -> ShowS
[VpcIngressConnection] -> ShowS
VpcIngressConnection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VpcIngressConnection] -> ShowS
$cshowList :: [VpcIngressConnection] -> ShowS
show :: VpcIngressConnection -> String
$cshow :: VpcIngressConnection -> String
showsPrec :: Int -> VpcIngressConnection -> ShowS
$cshowsPrec :: Int -> VpcIngressConnection -> ShowS
Prelude.Show, forall x. Rep VpcIngressConnection x -> VpcIngressConnection
forall x. VpcIngressConnection -> Rep VpcIngressConnection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VpcIngressConnection x -> VpcIngressConnection
$cfrom :: forall x. VpcIngressConnection -> Rep VpcIngressConnection x
Prelude.Generic)

-- |
-- Create a value of 'VpcIngressConnection' 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:
--
-- 'accountId', 'vpcIngressConnection_accountId' - The Account Id you use to create the VPC Ingress Connection resource.
--
-- 'createdAt', 'vpcIngressConnection_createdAt' - The time when the VPC Ingress Connection was created. It\'s in the Unix
-- time stamp format.
--
-- -   Type: Timestamp
--
-- -   Required: Yes
--
-- 'deletedAt', 'vpcIngressConnection_deletedAt' - The time when the App Runner service was deleted. It\'s in the Unix time
-- stamp format.
--
-- -   Type: Timestamp
--
-- -   Required: No
--
-- 'domainName', 'vpcIngressConnection_domainName' - The domain name associated with the VPC Ingress Connection resource.
--
-- 'ingressVpcConfiguration', 'vpcIngressConnection_ingressVpcConfiguration' - Specifications for the customer’s VPC and related PrivateLink VPC
-- endpoint that are used to associate with the VPC Ingress Connection
-- resource.
--
-- 'serviceArn', 'vpcIngressConnection_serviceArn' - The Amazon Resource Name (ARN) of the service associated with the VPC
-- Ingress Connection.
--
-- 'status', 'vpcIngressConnection_status' - The current status of the VPC Ingress Connection. The VPC Ingress
-- Connection displays one of the following statuses: @AVAILABLE@,
-- @PENDING_CREATION@, @PENDING_UPDATE@,
-- @PENDING_DELETION@,@FAILED_CREATION@, @FAILED_UPDATE@,
-- @FAILED_DELETION@, and @DELETED@..
--
-- 'vpcIngressConnectionArn', 'vpcIngressConnection_vpcIngressConnectionArn' - The Amazon Resource Name (ARN) of the VPC Ingress Connection.
--
-- 'vpcIngressConnectionName', 'vpcIngressConnection_vpcIngressConnectionName' - The customer-provided VPC Ingress Connection name.
newVpcIngressConnection ::
  VpcIngressConnection
newVpcIngressConnection :: VpcIngressConnection
newVpcIngressConnection =
  VpcIngressConnection'
    { $sel:accountId:VpcIngressConnection' :: Maybe Text
accountId = forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:VpcIngressConnection' :: Maybe POSIX
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:deletedAt:VpcIngressConnection' :: Maybe POSIX
deletedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:domainName:VpcIngressConnection' :: Maybe Text
domainName = forall a. Maybe a
Prelude.Nothing,
      $sel:ingressVpcConfiguration:VpcIngressConnection' :: Maybe IngressVpcConfiguration
ingressVpcConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:serviceArn:VpcIngressConnection' :: Maybe Text
serviceArn = forall a. Maybe a
Prelude.Nothing,
      $sel:status:VpcIngressConnection' :: Maybe VpcIngressConnectionStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcIngressConnectionArn:VpcIngressConnection' :: Maybe Text
vpcIngressConnectionArn = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcIngressConnectionName:VpcIngressConnection' :: Maybe Text
vpcIngressConnectionName = forall a. Maybe a
Prelude.Nothing
    }

-- | The Account Id you use to create the VPC Ingress Connection resource.
vpcIngressConnection_accountId :: Lens.Lens' VpcIngressConnection (Prelude.Maybe Prelude.Text)
vpcIngressConnection_accountId :: Lens' VpcIngressConnection (Maybe Text)
vpcIngressConnection_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcIngressConnection' {Maybe Text
accountId :: Maybe Text
$sel:accountId:VpcIngressConnection' :: VpcIngressConnection -> Maybe Text
accountId} -> Maybe Text
accountId) (\s :: VpcIngressConnection
s@VpcIngressConnection' {} Maybe Text
a -> VpcIngressConnection
s {$sel:accountId:VpcIngressConnection' :: Maybe Text
accountId = Maybe Text
a} :: VpcIngressConnection)

-- | The time when the VPC Ingress Connection was created. It\'s in the Unix
-- time stamp format.
--
-- -   Type: Timestamp
--
-- -   Required: Yes
vpcIngressConnection_createdAt :: Lens.Lens' VpcIngressConnection (Prelude.Maybe Prelude.UTCTime)
vpcIngressConnection_createdAt :: Lens' VpcIngressConnection (Maybe UTCTime)
vpcIngressConnection_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcIngressConnection' {Maybe POSIX
createdAt :: Maybe POSIX
$sel:createdAt:VpcIngressConnection' :: VpcIngressConnection -> Maybe POSIX
createdAt} -> Maybe POSIX
createdAt) (\s :: VpcIngressConnection
s@VpcIngressConnection' {} Maybe POSIX
a -> VpcIngressConnection
s {$sel:createdAt:VpcIngressConnection' :: Maybe POSIX
createdAt = Maybe POSIX
a} :: VpcIngressConnection) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The time when the App Runner service was deleted. It\'s in the Unix time
-- stamp format.
--
-- -   Type: Timestamp
--
-- -   Required: No
vpcIngressConnection_deletedAt :: Lens.Lens' VpcIngressConnection (Prelude.Maybe Prelude.UTCTime)
vpcIngressConnection_deletedAt :: Lens' VpcIngressConnection (Maybe UTCTime)
vpcIngressConnection_deletedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcIngressConnection' {Maybe POSIX
deletedAt :: Maybe POSIX
$sel:deletedAt:VpcIngressConnection' :: VpcIngressConnection -> Maybe POSIX
deletedAt} -> Maybe POSIX
deletedAt) (\s :: VpcIngressConnection
s@VpcIngressConnection' {} Maybe POSIX
a -> VpcIngressConnection
s {$sel:deletedAt:VpcIngressConnection' :: Maybe POSIX
deletedAt = Maybe POSIX
a} :: VpcIngressConnection) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The domain name associated with the VPC Ingress Connection resource.
vpcIngressConnection_domainName :: Lens.Lens' VpcIngressConnection (Prelude.Maybe Prelude.Text)
vpcIngressConnection_domainName :: Lens' VpcIngressConnection (Maybe Text)
vpcIngressConnection_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcIngressConnection' {Maybe Text
domainName :: Maybe Text
$sel:domainName:VpcIngressConnection' :: VpcIngressConnection -> Maybe Text
domainName} -> Maybe Text
domainName) (\s :: VpcIngressConnection
s@VpcIngressConnection' {} Maybe Text
a -> VpcIngressConnection
s {$sel:domainName:VpcIngressConnection' :: Maybe Text
domainName = Maybe Text
a} :: VpcIngressConnection)

-- | Specifications for the customer’s VPC and related PrivateLink VPC
-- endpoint that are used to associate with the VPC Ingress Connection
-- resource.
vpcIngressConnection_ingressVpcConfiguration :: Lens.Lens' VpcIngressConnection (Prelude.Maybe IngressVpcConfiguration)
vpcIngressConnection_ingressVpcConfiguration :: Lens' VpcIngressConnection (Maybe IngressVpcConfiguration)
vpcIngressConnection_ingressVpcConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcIngressConnection' {Maybe IngressVpcConfiguration
ingressVpcConfiguration :: Maybe IngressVpcConfiguration
$sel:ingressVpcConfiguration:VpcIngressConnection' :: VpcIngressConnection -> Maybe IngressVpcConfiguration
ingressVpcConfiguration} -> Maybe IngressVpcConfiguration
ingressVpcConfiguration) (\s :: VpcIngressConnection
s@VpcIngressConnection' {} Maybe IngressVpcConfiguration
a -> VpcIngressConnection
s {$sel:ingressVpcConfiguration:VpcIngressConnection' :: Maybe IngressVpcConfiguration
ingressVpcConfiguration = Maybe IngressVpcConfiguration
a} :: VpcIngressConnection)

-- | The Amazon Resource Name (ARN) of the service associated with the VPC
-- Ingress Connection.
vpcIngressConnection_serviceArn :: Lens.Lens' VpcIngressConnection (Prelude.Maybe Prelude.Text)
vpcIngressConnection_serviceArn :: Lens' VpcIngressConnection (Maybe Text)
vpcIngressConnection_serviceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcIngressConnection' {Maybe Text
serviceArn :: Maybe Text
$sel:serviceArn:VpcIngressConnection' :: VpcIngressConnection -> Maybe Text
serviceArn} -> Maybe Text
serviceArn) (\s :: VpcIngressConnection
s@VpcIngressConnection' {} Maybe Text
a -> VpcIngressConnection
s {$sel:serviceArn:VpcIngressConnection' :: Maybe Text
serviceArn = Maybe Text
a} :: VpcIngressConnection)

-- | The current status of the VPC Ingress Connection. The VPC Ingress
-- Connection displays one of the following statuses: @AVAILABLE@,
-- @PENDING_CREATION@, @PENDING_UPDATE@,
-- @PENDING_DELETION@,@FAILED_CREATION@, @FAILED_UPDATE@,
-- @FAILED_DELETION@, and @DELETED@..
vpcIngressConnection_status :: Lens.Lens' VpcIngressConnection (Prelude.Maybe VpcIngressConnectionStatus)
vpcIngressConnection_status :: Lens' VpcIngressConnection (Maybe VpcIngressConnectionStatus)
vpcIngressConnection_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcIngressConnection' {Maybe VpcIngressConnectionStatus
status :: Maybe VpcIngressConnectionStatus
$sel:status:VpcIngressConnection' :: VpcIngressConnection -> Maybe VpcIngressConnectionStatus
status} -> Maybe VpcIngressConnectionStatus
status) (\s :: VpcIngressConnection
s@VpcIngressConnection' {} Maybe VpcIngressConnectionStatus
a -> VpcIngressConnection
s {$sel:status:VpcIngressConnection' :: Maybe VpcIngressConnectionStatus
status = Maybe VpcIngressConnectionStatus
a} :: VpcIngressConnection)

-- | The Amazon Resource Name (ARN) of the VPC Ingress Connection.
vpcIngressConnection_vpcIngressConnectionArn :: Lens.Lens' VpcIngressConnection (Prelude.Maybe Prelude.Text)
vpcIngressConnection_vpcIngressConnectionArn :: Lens' VpcIngressConnection (Maybe Text)
vpcIngressConnection_vpcIngressConnectionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcIngressConnection' {Maybe Text
vpcIngressConnectionArn :: Maybe Text
$sel:vpcIngressConnectionArn:VpcIngressConnection' :: VpcIngressConnection -> Maybe Text
vpcIngressConnectionArn} -> Maybe Text
vpcIngressConnectionArn) (\s :: VpcIngressConnection
s@VpcIngressConnection' {} Maybe Text
a -> VpcIngressConnection
s {$sel:vpcIngressConnectionArn:VpcIngressConnection' :: Maybe Text
vpcIngressConnectionArn = Maybe Text
a} :: VpcIngressConnection)

-- | The customer-provided VPC Ingress Connection name.
vpcIngressConnection_vpcIngressConnectionName :: Lens.Lens' VpcIngressConnection (Prelude.Maybe Prelude.Text)
vpcIngressConnection_vpcIngressConnectionName :: Lens' VpcIngressConnection (Maybe Text)
vpcIngressConnection_vpcIngressConnectionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcIngressConnection' {Maybe Text
vpcIngressConnectionName :: Maybe Text
$sel:vpcIngressConnectionName:VpcIngressConnection' :: VpcIngressConnection -> Maybe Text
vpcIngressConnectionName} -> Maybe Text
vpcIngressConnectionName) (\s :: VpcIngressConnection
s@VpcIngressConnection' {} Maybe Text
a -> VpcIngressConnection
s {$sel:vpcIngressConnectionName:VpcIngressConnection' :: Maybe Text
vpcIngressConnectionName = Maybe Text
a} :: VpcIngressConnection)

instance Data.FromJSON VpcIngressConnection where
  parseJSON :: Value -> Parser VpcIngressConnection
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"VpcIngressConnection"
      ( \Object
x ->
          Maybe Text
-> Maybe POSIX
-> Maybe POSIX
-> Maybe Text
-> Maybe IngressVpcConfiguration
-> Maybe Text
-> Maybe VpcIngressConnectionStatus
-> Maybe Text
-> Maybe Text
-> VpcIngressConnection
VpcIngressConnection'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AccountId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CreatedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"DeletedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"DomainName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"IngressVpcConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ServiceArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"VpcIngressConnectionArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"VpcIngressConnectionName")
      )

instance Prelude.Hashable VpcIngressConnection where
  hashWithSalt :: Int -> VpcIngressConnection -> Int
hashWithSalt Int
_salt VpcIngressConnection' {Maybe Text
Maybe POSIX
Maybe IngressVpcConfiguration
Maybe VpcIngressConnectionStatus
vpcIngressConnectionName :: Maybe Text
vpcIngressConnectionArn :: Maybe Text
status :: Maybe VpcIngressConnectionStatus
serviceArn :: Maybe Text
ingressVpcConfiguration :: Maybe IngressVpcConfiguration
domainName :: Maybe Text
deletedAt :: Maybe POSIX
createdAt :: Maybe POSIX
accountId :: Maybe Text
$sel:vpcIngressConnectionName:VpcIngressConnection' :: VpcIngressConnection -> Maybe Text
$sel:vpcIngressConnectionArn:VpcIngressConnection' :: VpcIngressConnection -> Maybe Text
$sel:status:VpcIngressConnection' :: VpcIngressConnection -> Maybe VpcIngressConnectionStatus
$sel:serviceArn:VpcIngressConnection' :: VpcIngressConnection -> Maybe Text
$sel:ingressVpcConfiguration:VpcIngressConnection' :: VpcIngressConnection -> Maybe IngressVpcConfiguration
$sel:domainName:VpcIngressConnection' :: VpcIngressConnection -> Maybe Text
$sel:deletedAt:VpcIngressConnection' :: VpcIngressConnection -> Maybe POSIX
$sel:createdAt:VpcIngressConnection' :: VpcIngressConnection -> Maybe POSIX
$sel:accountId:VpcIngressConnection' :: VpcIngressConnection -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
accountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
deletedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
domainName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe IngressVpcConfiguration
ingressVpcConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
serviceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VpcIngressConnectionStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcIngressConnectionArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcIngressConnectionName

instance Prelude.NFData VpcIngressConnection where
  rnf :: VpcIngressConnection -> ()
rnf VpcIngressConnection' {Maybe Text
Maybe POSIX
Maybe IngressVpcConfiguration
Maybe VpcIngressConnectionStatus
vpcIngressConnectionName :: Maybe Text
vpcIngressConnectionArn :: Maybe Text
status :: Maybe VpcIngressConnectionStatus
serviceArn :: Maybe Text
ingressVpcConfiguration :: Maybe IngressVpcConfiguration
domainName :: Maybe Text
deletedAt :: Maybe POSIX
createdAt :: Maybe POSIX
accountId :: Maybe Text
$sel:vpcIngressConnectionName:VpcIngressConnection' :: VpcIngressConnection -> Maybe Text
$sel:vpcIngressConnectionArn:VpcIngressConnection' :: VpcIngressConnection -> Maybe Text
$sel:status:VpcIngressConnection' :: VpcIngressConnection -> Maybe VpcIngressConnectionStatus
$sel:serviceArn:VpcIngressConnection' :: VpcIngressConnection -> Maybe Text
$sel:ingressVpcConfiguration:VpcIngressConnection' :: VpcIngressConnection -> Maybe IngressVpcConfiguration
$sel:domainName:VpcIngressConnection' :: VpcIngressConnection -> Maybe Text
$sel:deletedAt:VpcIngressConnection' :: VpcIngressConnection -> Maybe POSIX
$sel:createdAt:VpcIngressConnection' :: VpcIngressConnection -> Maybe POSIX
$sel:accountId:VpcIngressConnection' :: VpcIngressConnection -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
accountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
deletedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
domainName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe IngressVpcConfiguration
ingressVpcConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
serviceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VpcIngressConnectionStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vpcIngressConnectionArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vpcIngressConnectionName