{-# 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.EC2.Types.VpcEndpointConnection
-- 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.EC2.Types.VpcEndpointConnection where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Internal
import Amazonka.EC2.Types.DnsEntry
import Amazonka.EC2.Types.IpAddressType
import Amazonka.EC2.Types.State
import Amazonka.EC2.Types.Tag
import qualified Amazonka.Prelude as Prelude

-- | Describes a VPC endpoint connection to a service.
--
-- /See:/ 'newVpcEndpointConnection' smart constructor.
data VpcEndpointConnection = VpcEndpointConnection'
  { -- | The date and time that the VPC endpoint was created.
    VpcEndpointConnection -> Maybe ISO8601
creationTimestamp :: Prelude.Maybe Data.ISO8601,
    -- | The DNS entries for the VPC endpoint.
    VpcEndpointConnection -> Maybe [DnsEntry]
dnsEntries :: Prelude.Maybe [DnsEntry],
    -- | The Amazon Resource Names (ARNs) of the Gateway Load Balancers for the
    -- service.
    VpcEndpointConnection -> Maybe [Text]
gatewayLoadBalancerArns :: Prelude.Maybe [Prelude.Text],
    -- | The IP address type for the endpoint.
    VpcEndpointConnection -> Maybe IpAddressType
ipAddressType :: Prelude.Maybe IpAddressType,
    -- | The Amazon Resource Names (ARNs) of the network load balancers for the
    -- service.
    VpcEndpointConnection -> Maybe [Text]
networkLoadBalancerArns :: Prelude.Maybe [Prelude.Text],
    -- | The ID of the service to which the endpoint is connected.
    VpcEndpointConnection -> Maybe Text
serviceId :: Prelude.Maybe Prelude.Text,
    -- | The tags.
    VpcEndpointConnection -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The ID of the VPC endpoint connection.
    VpcEndpointConnection -> Maybe Text
vpcEndpointConnectionId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the VPC endpoint.
    VpcEndpointConnection -> Maybe Text
vpcEndpointId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the Amazon Web Services account that owns the VPC endpoint.
    VpcEndpointConnection -> Maybe Text
vpcEndpointOwner :: Prelude.Maybe Prelude.Text,
    -- | The state of the VPC endpoint.
    VpcEndpointConnection -> Maybe State
vpcEndpointState :: Prelude.Maybe State
  }
  deriving (VpcEndpointConnection -> VpcEndpointConnection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VpcEndpointConnection -> VpcEndpointConnection -> Bool
$c/= :: VpcEndpointConnection -> VpcEndpointConnection -> Bool
== :: VpcEndpointConnection -> VpcEndpointConnection -> Bool
$c== :: VpcEndpointConnection -> VpcEndpointConnection -> Bool
Prelude.Eq, ReadPrec [VpcEndpointConnection]
ReadPrec VpcEndpointConnection
Int -> ReadS VpcEndpointConnection
ReadS [VpcEndpointConnection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VpcEndpointConnection]
$creadListPrec :: ReadPrec [VpcEndpointConnection]
readPrec :: ReadPrec VpcEndpointConnection
$creadPrec :: ReadPrec VpcEndpointConnection
readList :: ReadS [VpcEndpointConnection]
$creadList :: ReadS [VpcEndpointConnection]
readsPrec :: Int -> ReadS VpcEndpointConnection
$creadsPrec :: Int -> ReadS VpcEndpointConnection
Prelude.Read, Int -> VpcEndpointConnection -> ShowS
[VpcEndpointConnection] -> ShowS
VpcEndpointConnection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VpcEndpointConnection] -> ShowS
$cshowList :: [VpcEndpointConnection] -> ShowS
show :: VpcEndpointConnection -> String
$cshow :: VpcEndpointConnection -> String
showsPrec :: Int -> VpcEndpointConnection -> ShowS
$cshowsPrec :: Int -> VpcEndpointConnection -> ShowS
Prelude.Show, forall x. Rep VpcEndpointConnection x -> VpcEndpointConnection
forall x. VpcEndpointConnection -> Rep VpcEndpointConnection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VpcEndpointConnection x -> VpcEndpointConnection
$cfrom :: forall x. VpcEndpointConnection -> Rep VpcEndpointConnection x
Prelude.Generic)

-- |
-- Create a value of 'VpcEndpointConnection' 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:
--
-- 'creationTimestamp', 'vpcEndpointConnection_creationTimestamp' - The date and time that the VPC endpoint was created.
--
-- 'dnsEntries', 'vpcEndpointConnection_dnsEntries' - The DNS entries for the VPC endpoint.
--
-- 'gatewayLoadBalancerArns', 'vpcEndpointConnection_gatewayLoadBalancerArns' - The Amazon Resource Names (ARNs) of the Gateway Load Balancers for the
-- service.
--
-- 'ipAddressType', 'vpcEndpointConnection_ipAddressType' - The IP address type for the endpoint.
--
-- 'networkLoadBalancerArns', 'vpcEndpointConnection_networkLoadBalancerArns' - The Amazon Resource Names (ARNs) of the network load balancers for the
-- service.
--
-- 'serviceId', 'vpcEndpointConnection_serviceId' - The ID of the service to which the endpoint is connected.
--
-- 'tags', 'vpcEndpointConnection_tags' - The tags.
--
-- 'vpcEndpointConnectionId', 'vpcEndpointConnection_vpcEndpointConnectionId' - The ID of the VPC endpoint connection.
--
-- 'vpcEndpointId', 'vpcEndpointConnection_vpcEndpointId' - The ID of the VPC endpoint.
--
-- 'vpcEndpointOwner', 'vpcEndpointConnection_vpcEndpointOwner' - The ID of the Amazon Web Services account that owns the VPC endpoint.
--
-- 'vpcEndpointState', 'vpcEndpointConnection_vpcEndpointState' - The state of the VPC endpoint.
newVpcEndpointConnection ::
  VpcEndpointConnection
newVpcEndpointConnection :: VpcEndpointConnection
newVpcEndpointConnection =
  VpcEndpointConnection'
    { $sel:creationTimestamp:VpcEndpointConnection' :: Maybe ISO8601
creationTimestamp =
        forall a. Maybe a
Prelude.Nothing,
      $sel:dnsEntries:VpcEndpointConnection' :: Maybe [DnsEntry]
dnsEntries = forall a. Maybe a
Prelude.Nothing,
      $sel:gatewayLoadBalancerArns:VpcEndpointConnection' :: Maybe [Text]
gatewayLoadBalancerArns = forall a. Maybe a
Prelude.Nothing,
      $sel:ipAddressType:VpcEndpointConnection' :: Maybe IpAddressType
ipAddressType = forall a. Maybe a
Prelude.Nothing,
      $sel:networkLoadBalancerArns:VpcEndpointConnection' :: Maybe [Text]
networkLoadBalancerArns = forall a. Maybe a
Prelude.Nothing,
      $sel:serviceId:VpcEndpointConnection' :: Maybe Text
serviceId = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:VpcEndpointConnection' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcEndpointConnectionId:VpcEndpointConnection' :: Maybe Text
vpcEndpointConnectionId = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcEndpointId:VpcEndpointConnection' :: Maybe Text
vpcEndpointId = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcEndpointOwner:VpcEndpointConnection' :: Maybe Text
vpcEndpointOwner = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcEndpointState:VpcEndpointConnection' :: Maybe State
vpcEndpointState = forall a. Maybe a
Prelude.Nothing
    }

-- | The date and time that the VPC endpoint was created.
vpcEndpointConnection_creationTimestamp :: Lens.Lens' VpcEndpointConnection (Prelude.Maybe Prelude.UTCTime)
vpcEndpointConnection_creationTimestamp :: Lens' VpcEndpointConnection (Maybe UTCTime)
vpcEndpointConnection_creationTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcEndpointConnection' {Maybe ISO8601
creationTimestamp :: Maybe ISO8601
$sel:creationTimestamp:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe ISO8601
creationTimestamp} -> Maybe ISO8601
creationTimestamp) (\s :: VpcEndpointConnection
s@VpcEndpointConnection' {} Maybe ISO8601
a -> VpcEndpointConnection
s {$sel:creationTimestamp:VpcEndpointConnection' :: Maybe ISO8601
creationTimestamp = Maybe ISO8601
a} :: VpcEndpointConnection) 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 DNS entries for the VPC endpoint.
vpcEndpointConnection_dnsEntries :: Lens.Lens' VpcEndpointConnection (Prelude.Maybe [DnsEntry])
vpcEndpointConnection_dnsEntries :: Lens' VpcEndpointConnection (Maybe [DnsEntry])
vpcEndpointConnection_dnsEntries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcEndpointConnection' {Maybe [DnsEntry]
dnsEntries :: Maybe [DnsEntry]
$sel:dnsEntries:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe [DnsEntry]
dnsEntries} -> Maybe [DnsEntry]
dnsEntries) (\s :: VpcEndpointConnection
s@VpcEndpointConnection' {} Maybe [DnsEntry]
a -> VpcEndpointConnection
s {$sel:dnsEntries:VpcEndpointConnection' :: Maybe [DnsEntry]
dnsEntries = Maybe [DnsEntry]
a} :: VpcEndpointConnection) 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 Names (ARNs) of the Gateway Load Balancers for the
-- service.
vpcEndpointConnection_gatewayLoadBalancerArns :: Lens.Lens' VpcEndpointConnection (Prelude.Maybe [Prelude.Text])
vpcEndpointConnection_gatewayLoadBalancerArns :: Lens' VpcEndpointConnection (Maybe [Text])
vpcEndpointConnection_gatewayLoadBalancerArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcEndpointConnection' {Maybe [Text]
gatewayLoadBalancerArns :: Maybe [Text]
$sel:gatewayLoadBalancerArns:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe [Text]
gatewayLoadBalancerArns} -> Maybe [Text]
gatewayLoadBalancerArns) (\s :: VpcEndpointConnection
s@VpcEndpointConnection' {} Maybe [Text]
a -> VpcEndpointConnection
s {$sel:gatewayLoadBalancerArns:VpcEndpointConnection' :: Maybe [Text]
gatewayLoadBalancerArns = Maybe [Text]
a} :: VpcEndpointConnection) 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 IP address type for the endpoint.
vpcEndpointConnection_ipAddressType :: Lens.Lens' VpcEndpointConnection (Prelude.Maybe IpAddressType)
vpcEndpointConnection_ipAddressType :: Lens' VpcEndpointConnection (Maybe IpAddressType)
vpcEndpointConnection_ipAddressType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcEndpointConnection' {Maybe IpAddressType
ipAddressType :: Maybe IpAddressType
$sel:ipAddressType:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe IpAddressType
ipAddressType} -> Maybe IpAddressType
ipAddressType) (\s :: VpcEndpointConnection
s@VpcEndpointConnection' {} Maybe IpAddressType
a -> VpcEndpointConnection
s {$sel:ipAddressType:VpcEndpointConnection' :: Maybe IpAddressType
ipAddressType = Maybe IpAddressType
a} :: VpcEndpointConnection)

-- | The Amazon Resource Names (ARNs) of the network load balancers for the
-- service.
vpcEndpointConnection_networkLoadBalancerArns :: Lens.Lens' VpcEndpointConnection (Prelude.Maybe [Prelude.Text])
vpcEndpointConnection_networkLoadBalancerArns :: Lens' VpcEndpointConnection (Maybe [Text])
vpcEndpointConnection_networkLoadBalancerArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcEndpointConnection' {Maybe [Text]
networkLoadBalancerArns :: Maybe [Text]
$sel:networkLoadBalancerArns:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe [Text]
networkLoadBalancerArns} -> Maybe [Text]
networkLoadBalancerArns) (\s :: VpcEndpointConnection
s@VpcEndpointConnection' {} Maybe [Text]
a -> VpcEndpointConnection
s {$sel:networkLoadBalancerArns:VpcEndpointConnection' :: Maybe [Text]
networkLoadBalancerArns = Maybe [Text]
a} :: VpcEndpointConnection) 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 ID of the service to which the endpoint is connected.
vpcEndpointConnection_serviceId :: Lens.Lens' VpcEndpointConnection (Prelude.Maybe Prelude.Text)
vpcEndpointConnection_serviceId :: Lens' VpcEndpointConnection (Maybe Text)
vpcEndpointConnection_serviceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcEndpointConnection' {Maybe Text
serviceId :: Maybe Text
$sel:serviceId:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe Text
serviceId} -> Maybe Text
serviceId) (\s :: VpcEndpointConnection
s@VpcEndpointConnection' {} Maybe Text
a -> VpcEndpointConnection
s {$sel:serviceId:VpcEndpointConnection' :: Maybe Text
serviceId = Maybe Text
a} :: VpcEndpointConnection)

-- | The tags.
vpcEndpointConnection_tags :: Lens.Lens' VpcEndpointConnection (Prelude.Maybe [Tag])
vpcEndpointConnection_tags :: Lens' VpcEndpointConnection (Maybe [Tag])
vpcEndpointConnection_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcEndpointConnection' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: VpcEndpointConnection
s@VpcEndpointConnection' {} Maybe [Tag]
a -> VpcEndpointConnection
s {$sel:tags:VpcEndpointConnection' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: VpcEndpointConnection) 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 ID of the VPC endpoint connection.
vpcEndpointConnection_vpcEndpointConnectionId :: Lens.Lens' VpcEndpointConnection (Prelude.Maybe Prelude.Text)
vpcEndpointConnection_vpcEndpointConnectionId :: Lens' VpcEndpointConnection (Maybe Text)
vpcEndpointConnection_vpcEndpointConnectionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcEndpointConnection' {Maybe Text
vpcEndpointConnectionId :: Maybe Text
$sel:vpcEndpointConnectionId:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe Text
vpcEndpointConnectionId} -> Maybe Text
vpcEndpointConnectionId) (\s :: VpcEndpointConnection
s@VpcEndpointConnection' {} Maybe Text
a -> VpcEndpointConnection
s {$sel:vpcEndpointConnectionId:VpcEndpointConnection' :: Maybe Text
vpcEndpointConnectionId = Maybe Text
a} :: VpcEndpointConnection)

-- | The ID of the VPC endpoint.
vpcEndpointConnection_vpcEndpointId :: Lens.Lens' VpcEndpointConnection (Prelude.Maybe Prelude.Text)
vpcEndpointConnection_vpcEndpointId :: Lens' VpcEndpointConnection (Maybe Text)
vpcEndpointConnection_vpcEndpointId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcEndpointConnection' {Maybe Text
vpcEndpointId :: Maybe Text
$sel:vpcEndpointId:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe Text
vpcEndpointId} -> Maybe Text
vpcEndpointId) (\s :: VpcEndpointConnection
s@VpcEndpointConnection' {} Maybe Text
a -> VpcEndpointConnection
s {$sel:vpcEndpointId:VpcEndpointConnection' :: Maybe Text
vpcEndpointId = Maybe Text
a} :: VpcEndpointConnection)

-- | The ID of the Amazon Web Services account that owns the VPC endpoint.
vpcEndpointConnection_vpcEndpointOwner :: Lens.Lens' VpcEndpointConnection (Prelude.Maybe Prelude.Text)
vpcEndpointConnection_vpcEndpointOwner :: Lens' VpcEndpointConnection (Maybe Text)
vpcEndpointConnection_vpcEndpointOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcEndpointConnection' {Maybe Text
vpcEndpointOwner :: Maybe Text
$sel:vpcEndpointOwner:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe Text
vpcEndpointOwner} -> Maybe Text
vpcEndpointOwner) (\s :: VpcEndpointConnection
s@VpcEndpointConnection' {} Maybe Text
a -> VpcEndpointConnection
s {$sel:vpcEndpointOwner:VpcEndpointConnection' :: Maybe Text
vpcEndpointOwner = Maybe Text
a} :: VpcEndpointConnection)

-- | The state of the VPC endpoint.
vpcEndpointConnection_vpcEndpointState :: Lens.Lens' VpcEndpointConnection (Prelude.Maybe State)
vpcEndpointConnection_vpcEndpointState :: Lens' VpcEndpointConnection (Maybe State)
vpcEndpointConnection_vpcEndpointState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\VpcEndpointConnection' {Maybe State
vpcEndpointState :: Maybe State
$sel:vpcEndpointState:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe State
vpcEndpointState} -> Maybe State
vpcEndpointState) (\s :: VpcEndpointConnection
s@VpcEndpointConnection' {} Maybe State
a -> VpcEndpointConnection
s {$sel:vpcEndpointState:VpcEndpointConnection' :: Maybe State
vpcEndpointState = Maybe State
a} :: VpcEndpointConnection)

instance Data.FromXML VpcEndpointConnection where
  parseXML :: [Node] -> Either String VpcEndpointConnection
parseXML [Node]
x =
    Maybe ISO8601
-> Maybe [DnsEntry]
-> Maybe [Text]
-> Maybe IpAddressType
-> Maybe [Text]
-> Maybe Text
-> Maybe [Tag]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe State
-> VpcEndpointConnection
VpcEndpointConnection'
      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
"creationTimestamp")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"dnsEntrySet"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"gatewayLoadBalancerArnSet"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ipAddressType")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"networkLoadBalancerArnSet"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"serviceId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"tagSet"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"vpcEndpointConnectionId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"vpcEndpointId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"vpcEndpointOwner")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"vpcEndpointState")

instance Prelude.Hashable VpcEndpointConnection where
  hashWithSalt :: Int -> VpcEndpointConnection -> Int
hashWithSalt Int
_salt VpcEndpointConnection' {Maybe [Text]
Maybe [DnsEntry]
Maybe [Tag]
Maybe Text
Maybe ISO8601
Maybe IpAddressType
Maybe State
vpcEndpointState :: Maybe State
vpcEndpointOwner :: Maybe Text
vpcEndpointId :: Maybe Text
vpcEndpointConnectionId :: Maybe Text
tags :: Maybe [Tag]
serviceId :: Maybe Text
networkLoadBalancerArns :: Maybe [Text]
ipAddressType :: Maybe IpAddressType
gatewayLoadBalancerArns :: Maybe [Text]
dnsEntries :: Maybe [DnsEntry]
creationTimestamp :: Maybe ISO8601
$sel:vpcEndpointState:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe State
$sel:vpcEndpointOwner:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe Text
$sel:vpcEndpointId:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe Text
$sel:vpcEndpointConnectionId:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe Text
$sel:tags:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe [Tag]
$sel:serviceId:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe Text
$sel:networkLoadBalancerArns:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe [Text]
$sel:ipAddressType:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe IpAddressType
$sel:gatewayLoadBalancerArns:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe [Text]
$sel:dnsEntries:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe [DnsEntry]
$sel:creationTimestamp:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe ISO8601
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
creationTimestamp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [DnsEntry]
dnsEntries
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
gatewayLoadBalancerArns
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe IpAddressType
ipAddressType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
networkLoadBalancerArns
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
serviceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcEndpointConnectionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcEndpointId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcEndpointOwner
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe State
vpcEndpointState

instance Prelude.NFData VpcEndpointConnection where
  rnf :: VpcEndpointConnection -> ()
rnf VpcEndpointConnection' {Maybe [Text]
Maybe [DnsEntry]
Maybe [Tag]
Maybe Text
Maybe ISO8601
Maybe IpAddressType
Maybe State
vpcEndpointState :: Maybe State
vpcEndpointOwner :: Maybe Text
vpcEndpointId :: Maybe Text
vpcEndpointConnectionId :: Maybe Text
tags :: Maybe [Tag]
serviceId :: Maybe Text
networkLoadBalancerArns :: Maybe [Text]
ipAddressType :: Maybe IpAddressType
gatewayLoadBalancerArns :: Maybe [Text]
dnsEntries :: Maybe [DnsEntry]
creationTimestamp :: Maybe ISO8601
$sel:vpcEndpointState:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe State
$sel:vpcEndpointOwner:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe Text
$sel:vpcEndpointId:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe Text
$sel:vpcEndpointConnectionId:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe Text
$sel:tags:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe [Tag]
$sel:serviceId:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe Text
$sel:networkLoadBalancerArns:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe [Text]
$sel:ipAddressType:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe IpAddressType
$sel:gatewayLoadBalancerArns:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe [Text]
$sel:dnsEntries:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe [DnsEntry]
$sel:creationTimestamp:VpcEndpointConnection' :: VpcEndpointConnection -> Maybe ISO8601
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
creationTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [DnsEntry]
dnsEntries
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
gatewayLoadBalancerArns
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe IpAddressType
ipAddressType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
networkLoadBalancerArns
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
serviceId
      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 Maybe Text
vpcEndpointConnectionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vpcEndpointId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vpcEndpointOwner
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe State
vpcEndpointState