{-# 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.S3Outposts.Types.Endpoint
-- 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.S3Outposts.Types.Endpoint where

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 Amazonka.S3Outposts.Types.EndpointAccessType
import Amazonka.S3Outposts.Types.EndpointStatus
import Amazonka.S3Outposts.Types.NetworkInterface

-- | Amazon S3 on Outposts Access Points simplify managing data access at
-- scale for shared datasets in S3 on Outposts. S3 on Outposts uses
-- endpoints to connect to Outposts buckets so that you can perform actions
-- within your virtual private cloud (VPC). For more information, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/WorkingWithS3Outposts.html Accessing S3 on Outposts using VPC-only access points>
-- in the /Amazon Simple Storage Service User Guide/.
--
-- /See:/ 'newEndpoint' smart constructor.
data Endpoint = Endpoint'
  { -- | The type of connectivity used to access the Amazon S3 on Outposts
    -- endpoint.
    Endpoint -> Maybe EndpointAccessType
accessType :: Prelude.Maybe EndpointAccessType,
    -- | The VPC CIDR committed by this endpoint.
    Endpoint -> Maybe Text
cidrBlock :: Prelude.Maybe Prelude.Text,
    -- | The time the endpoint was created.
    Endpoint -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The ID of the customer-owned IPv4 address pool used for the endpoint.
    Endpoint -> Maybe Text
customerOwnedIpv4Pool :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the endpoint.
    Endpoint -> Maybe Text
endpointArn :: Prelude.Maybe Prelude.Text,
    -- | The network interface of the endpoint.
    Endpoint -> Maybe [NetworkInterface]
networkInterfaces :: Prelude.Maybe [NetworkInterface],
    -- | The ID of the Outposts.
    Endpoint -> Maybe Text
outpostsId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the security group used for the endpoint.
    Endpoint -> Maybe Text
securityGroupId :: Prelude.Maybe Prelude.Text,
    -- | The status of the endpoint.
    Endpoint -> Maybe EndpointStatus
status :: Prelude.Maybe EndpointStatus,
    -- | The ID of the subnet used for the endpoint.
    Endpoint -> Maybe Text
subnetId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the VPC used for the endpoint.
    Endpoint -> Maybe Text
vpcId :: Prelude.Maybe Prelude.Text
  }
  deriving (Endpoint -> Endpoint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Endpoint -> Endpoint -> Bool
$c/= :: Endpoint -> Endpoint -> Bool
== :: Endpoint -> Endpoint -> Bool
$c== :: Endpoint -> Endpoint -> Bool
Prelude.Eq, ReadPrec [Endpoint]
ReadPrec Endpoint
Int -> ReadS Endpoint
ReadS [Endpoint]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Endpoint]
$creadListPrec :: ReadPrec [Endpoint]
readPrec :: ReadPrec Endpoint
$creadPrec :: ReadPrec Endpoint
readList :: ReadS [Endpoint]
$creadList :: ReadS [Endpoint]
readsPrec :: Int -> ReadS Endpoint
$creadsPrec :: Int -> ReadS Endpoint
Prelude.Read, Int -> Endpoint -> ShowS
[Endpoint] -> ShowS
Endpoint -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Endpoint] -> ShowS
$cshowList :: [Endpoint] -> ShowS
show :: Endpoint -> String
$cshow :: Endpoint -> String
showsPrec :: Int -> Endpoint -> ShowS
$cshowsPrec :: Int -> Endpoint -> ShowS
Prelude.Show, forall x. Rep Endpoint x -> Endpoint
forall x. Endpoint -> Rep Endpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Endpoint x -> Endpoint
$cfrom :: forall x. Endpoint -> Rep Endpoint x
Prelude.Generic)

-- |
-- Create a value of 'Endpoint' 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:
--
-- 'accessType', 'endpoint_accessType' - The type of connectivity used to access the Amazon S3 on Outposts
-- endpoint.
--
-- 'cidrBlock', 'endpoint_cidrBlock' - The VPC CIDR committed by this endpoint.
--
-- 'creationTime', 'endpoint_creationTime' - The time the endpoint was created.
--
-- 'customerOwnedIpv4Pool', 'endpoint_customerOwnedIpv4Pool' - The ID of the customer-owned IPv4 address pool used for the endpoint.
--
-- 'endpointArn', 'endpoint_endpointArn' - The Amazon Resource Name (ARN) of the endpoint.
--
-- 'networkInterfaces', 'endpoint_networkInterfaces' - The network interface of the endpoint.
--
-- 'outpostsId', 'endpoint_outpostsId' - The ID of the Outposts.
--
-- 'securityGroupId', 'endpoint_securityGroupId' - The ID of the security group used for the endpoint.
--
-- 'status', 'endpoint_status' - The status of the endpoint.
--
-- 'subnetId', 'endpoint_subnetId' - The ID of the subnet used for the endpoint.
--
-- 'vpcId', 'endpoint_vpcId' - The ID of the VPC used for the endpoint.
newEndpoint ::
  Endpoint
newEndpoint :: Endpoint
newEndpoint =
  Endpoint'
    { $sel:accessType:Endpoint' :: Maybe EndpointAccessType
accessType = forall a. Maybe a
Prelude.Nothing,
      $sel:cidrBlock:Endpoint' :: Maybe Text
cidrBlock = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:Endpoint' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:customerOwnedIpv4Pool:Endpoint' :: Maybe Text
customerOwnedIpv4Pool = forall a. Maybe a
Prelude.Nothing,
      $sel:endpointArn:Endpoint' :: Maybe Text
endpointArn = forall a. Maybe a
Prelude.Nothing,
      $sel:networkInterfaces:Endpoint' :: Maybe [NetworkInterface]
networkInterfaces = forall a. Maybe a
Prelude.Nothing,
      $sel:outpostsId:Endpoint' :: Maybe Text
outpostsId = forall a. Maybe a
Prelude.Nothing,
      $sel:securityGroupId:Endpoint' :: Maybe Text
securityGroupId = forall a. Maybe a
Prelude.Nothing,
      $sel:status:Endpoint' :: Maybe EndpointStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetId:Endpoint' :: Maybe Text
subnetId = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:Endpoint' :: Maybe Text
vpcId = forall a. Maybe a
Prelude.Nothing
    }

-- | The type of connectivity used to access the Amazon S3 on Outposts
-- endpoint.
endpoint_accessType :: Lens.Lens' Endpoint (Prelude.Maybe EndpointAccessType)
endpoint_accessType :: Lens' Endpoint (Maybe EndpointAccessType)
endpoint_accessType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {Maybe EndpointAccessType
accessType :: Maybe EndpointAccessType
$sel:accessType:Endpoint' :: Endpoint -> Maybe EndpointAccessType
accessType} -> Maybe EndpointAccessType
accessType) (\s :: Endpoint
s@Endpoint' {} Maybe EndpointAccessType
a -> Endpoint
s {$sel:accessType:Endpoint' :: Maybe EndpointAccessType
accessType = Maybe EndpointAccessType
a} :: Endpoint)

-- | The VPC CIDR committed by this endpoint.
endpoint_cidrBlock :: Lens.Lens' Endpoint (Prelude.Maybe Prelude.Text)
endpoint_cidrBlock :: Lens' Endpoint (Maybe Text)
endpoint_cidrBlock = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {Maybe Text
cidrBlock :: Maybe Text
$sel:cidrBlock:Endpoint' :: Endpoint -> Maybe Text
cidrBlock} -> Maybe Text
cidrBlock) (\s :: Endpoint
s@Endpoint' {} Maybe Text
a -> Endpoint
s {$sel:cidrBlock:Endpoint' :: Maybe Text
cidrBlock = Maybe Text
a} :: Endpoint)

-- | The time the endpoint was created.
endpoint_creationTime :: Lens.Lens' Endpoint (Prelude.Maybe Prelude.UTCTime)
endpoint_creationTime :: Lens' Endpoint (Maybe UTCTime)
endpoint_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:Endpoint' :: Endpoint -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: Endpoint
s@Endpoint' {} Maybe POSIX
a -> Endpoint
s {$sel:creationTime:Endpoint' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: Endpoint) 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 ID of the customer-owned IPv4 address pool used for the endpoint.
endpoint_customerOwnedIpv4Pool :: Lens.Lens' Endpoint (Prelude.Maybe Prelude.Text)
endpoint_customerOwnedIpv4Pool :: Lens' Endpoint (Maybe Text)
endpoint_customerOwnedIpv4Pool = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {Maybe Text
customerOwnedIpv4Pool :: Maybe Text
$sel:customerOwnedIpv4Pool:Endpoint' :: Endpoint -> Maybe Text
customerOwnedIpv4Pool} -> Maybe Text
customerOwnedIpv4Pool) (\s :: Endpoint
s@Endpoint' {} Maybe Text
a -> Endpoint
s {$sel:customerOwnedIpv4Pool:Endpoint' :: Maybe Text
customerOwnedIpv4Pool = Maybe Text
a} :: Endpoint)

-- | The Amazon Resource Name (ARN) of the endpoint.
endpoint_endpointArn :: Lens.Lens' Endpoint (Prelude.Maybe Prelude.Text)
endpoint_endpointArn :: Lens' Endpoint (Maybe Text)
endpoint_endpointArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {Maybe Text
endpointArn :: Maybe Text
$sel:endpointArn:Endpoint' :: Endpoint -> Maybe Text
endpointArn} -> Maybe Text
endpointArn) (\s :: Endpoint
s@Endpoint' {} Maybe Text
a -> Endpoint
s {$sel:endpointArn:Endpoint' :: Maybe Text
endpointArn = Maybe Text
a} :: Endpoint)

-- | The network interface of the endpoint.
endpoint_networkInterfaces :: Lens.Lens' Endpoint (Prelude.Maybe [NetworkInterface])
endpoint_networkInterfaces :: Lens' Endpoint (Maybe [NetworkInterface])
endpoint_networkInterfaces = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {Maybe [NetworkInterface]
networkInterfaces :: Maybe [NetworkInterface]
$sel:networkInterfaces:Endpoint' :: Endpoint -> Maybe [NetworkInterface]
networkInterfaces} -> Maybe [NetworkInterface]
networkInterfaces) (\s :: Endpoint
s@Endpoint' {} Maybe [NetworkInterface]
a -> Endpoint
s {$sel:networkInterfaces:Endpoint' :: Maybe [NetworkInterface]
networkInterfaces = Maybe [NetworkInterface]
a} :: Endpoint) 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 Outposts.
endpoint_outpostsId :: Lens.Lens' Endpoint (Prelude.Maybe Prelude.Text)
endpoint_outpostsId :: Lens' Endpoint (Maybe Text)
endpoint_outpostsId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {Maybe Text
outpostsId :: Maybe Text
$sel:outpostsId:Endpoint' :: Endpoint -> Maybe Text
outpostsId} -> Maybe Text
outpostsId) (\s :: Endpoint
s@Endpoint' {} Maybe Text
a -> Endpoint
s {$sel:outpostsId:Endpoint' :: Maybe Text
outpostsId = Maybe Text
a} :: Endpoint)

-- | The ID of the security group used for the endpoint.
endpoint_securityGroupId :: Lens.Lens' Endpoint (Prelude.Maybe Prelude.Text)
endpoint_securityGroupId :: Lens' Endpoint (Maybe Text)
endpoint_securityGroupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {Maybe Text
securityGroupId :: Maybe Text
$sel:securityGroupId:Endpoint' :: Endpoint -> Maybe Text
securityGroupId} -> Maybe Text
securityGroupId) (\s :: Endpoint
s@Endpoint' {} Maybe Text
a -> Endpoint
s {$sel:securityGroupId:Endpoint' :: Maybe Text
securityGroupId = Maybe Text
a} :: Endpoint)

-- | The status of the endpoint.
endpoint_status :: Lens.Lens' Endpoint (Prelude.Maybe EndpointStatus)
endpoint_status :: Lens' Endpoint (Maybe EndpointStatus)
endpoint_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {Maybe EndpointStatus
status :: Maybe EndpointStatus
$sel:status:Endpoint' :: Endpoint -> Maybe EndpointStatus
status} -> Maybe EndpointStatus
status) (\s :: Endpoint
s@Endpoint' {} Maybe EndpointStatus
a -> Endpoint
s {$sel:status:Endpoint' :: Maybe EndpointStatus
status = Maybe EndpointStatus
a} :: Endpoint)

-- | The ID of the subnet used for the endpoint.
endpoint_subnetId :: Lens.Lens' Endpoint (Prelude.Maybe Prelude.Text)
endpoint_subnetId :: Lens' Endpoint (Maybe Text)
endpoint_subnetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {Maybe Text
subnetId :: Maybe Text
$sel:subnetId:Endpoint' :: Endpoint -> Maybe Text
subnetId} -> Maybe Text
subnetId) (\s :: Endpoint
s@Endpoint' {} Maybe Text
a -> Endpoint
s {$sel:subnetId:Endpoint' :: Maybe Text
subnetId = Maybe Text
a} :: Endpoint)

-- | The ID of the VPC used for the endpoint.
endpoint_vpcId :: Lens.Lens' Endpoint (Prelude.Maybe Prelude.Text)
endpoint_vpcId :: Lens' Endpoint (Maybe Text)
endpoint_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Endpoint' {Maybe Text
vpcId :: Maybe Text
$sel:vpcId:Endpoint' :: Endpoint -> Maybe Text
vpcId} -> Maybe Text
vpcId) (\s :: Endpoint
s@Endpoint' {} Maybe Text
a -> Endpoint
s {$sel:vpcId:Endpoint' :: Maybe Text
vpcId = Maybe Text
a} :: Endpoint)

instance Data.FromJSON Endpoint where
  parseJSON :: Value -> Parser Endpoint
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Endpoint"
      ( \Object
x ->
          Maybe EndpointAccessType
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe [NetworkInterface]
-> Maybe Text
-> Maybe Text
-> Maybe EndpointStatus
-> Maybe Text
-> Maybe Text
-> Endpoint
Endpoint'
            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
"AccessType")
            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
"CidrBlock")
            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
"CreationTime")
            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
"CustomerOwnedIpv4Pool")
            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
"EndpointArn")
            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
"NetworkInterfaces"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            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
"OutpostsId")
            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
"SecurityGroupId")
            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
"SubnetId")
            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
"VpcId")
      )

instance Prelude.Hashable Endpoint where
  hashWithSalt :: Int -> Endpoint -> Int
hashWithSalt Int
_salt Endpoint' {Maybe [NetworkInterface]
Maybe Text
Maybe POSIX
Maybe EndpointAccessType
Maybe EndpointStatus
vpcId :: Maybe Text
subnetId :: Maybe Text
status :: Maybe EndpointStatus
securityGroupId :: Maybe Text
outpostsId :: Maybe Text
networkInterfaces :: Maybe [NetworkInterface]
endpointArn :: Maybe Text
customerOwnedIpv4Pool :: Maybe Text
creationTime :: Maybe POSIX
cidrBlock :: Maybe Text
accessType :: Maybe EndpointAccessType
$sel:vpcId:Endpoint' :: Endpoint -> Maybe Text
$sel:subnetId:Endpoint' :: Endpoint -> Maybe Text
$sel:status:Endpoint' :: Endpoint -> Maybe EndpointStatus
$sel:securityGroupId:Endpoint' :: Endpoint -> Maybe Text
$sel:outpostsId:Endpoint' :: Endpoint -> Maybe Text
$sel:networkInterfaces:Endpoint' :: Endpoint -> Maybe [NetworkInterface]
$sel:endpointArn:Endpoint' :: Endpoint -> Maybe Text
$sel:customerOwnedIpv4Pool:Endpoint' :: Endpoint -> Maybe Text
$sel:creationTime:Endpoint' :: Endpoint -> Maybe POSIX
$sel:cidrBlock:Endpoint' :: Endpoint -> Maybe Text
$sel:accessType:Endpoint' :: Endpoint -> Maybe EndpointAccessType
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EndpointAccessType
accessType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
cidrBlock
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
customerOwnedIpv4Pool
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
endpointArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [NetworkInterface]
networkInterfaces
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
outpostsId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
securityGroupId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EndpointStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
subnetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcId

instance Prelude.NFData Endpoint where
  rnf :: Endpoint -> ()
rnf Endpoint' {Maybe [NetworkInterface]
Maybe Text
Maybe POSIX
Maybe EndpointAccessType
Maybe EndpointStatus
vpcId :: Maybe Text
subnetId :: Maybe Text
status :: Maybe EndpointStatus
securityGroupId :: Maybe Text
outpostsId :: Maybe Text
networkInterfaces :: Maybe [NetworkInterface]
endpointArn :: Maybe Text
customerOwnedIpv4Pool :: Maybe Text
creationTime :: Maybe POSIX
cidrBlock :: Maybe Text
accessType :: Maybe EndpointAccessType
$sel:vpcId:Endpoint' :: Endpoint -> Maybe Text
$sel:subnetId:Endpoint' :: Endpoint -> Maybe Text
$sel:status:Endpoint' :: Endpoint -> Maybe EndpointStatus
$sel:securityGroupId:Endpoint' :: Endpoint -> Maybe Text
$sel:outpostsId:Endpoint' :: Endpoint -> Maybe Text
$sel:networkInterfaces:Endpoint' :: Endpoint -> Maybe [NetworkInterface]
$sel:endpointArn:Endpoint' :: Endpoint -> Maybe Text
$sel:customerOwnedIpv4Pool:Endpoint' :: Endpoint -> Maybe Text
$sel:creationTime:Endpoint' :: Endpoint -> Maybe POSIX
$sel:cidrBlock:Endpoint' :: Endpoint -> Maybe Text
$sel:accessType:Endpoint' :: Endpoint -> Maybe EndpointAccessType
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe EndpointAccessType
accessType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
cidrBlock
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
customerOwnedIpv4Pool
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
endpointArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [NetworkInterface]
networkInterfaces
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
outpostsId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
securityGroupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EndpointStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
subnetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vpcId