{-# 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.NetworkInterfaceAttachment
-- 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.NetworkInterfaceAttachment 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.AttachmentEnaSrdSpecification
import Amazonka.EC2.Types.AttachmentStatus
import qualified Amazonka.Prelude as Prelude

-- | Describes a network interface attachment.
--
-- /See:/ 'newNetworkInterfaceAttachment' smart constructor.
data NetworkInterfaceAttachment = NetworkInterfaceAttachment'
  { -- | The timestamp indicating when the attachment initiated.
    NetworkInterfaceAttachment -> Maybe ISO8601
attachTime :: Prelude.Maybe Data.ISO8601,
    -- | The ID of the network interface attachment.
    NetworkInterfaceAttachment -> Maybe Text
attachmentId :: Prelude.Maybe Prelude.Text,
    -- | Indicates whether the network interface is deleted when the instance is
    -- terminated.
    NetworkInterfaceAttachment -> Maybe Bool
deleteOnTermination :: Prelude.Maybe Prelude.Bool,
    -- | The device index of the network interface attachment on the instance.
    NetworkInterfaceAttachment -> Maybe Int
deviceIndex :: Prelude.Maybe Prelude.Int,
    -- | Configures ENA Express for the network interface that this action
    -- attaches to the instance.
    NetworkInterfaceAttachment -> Maybe AttachmentEnaSrdSpecification
enaSrdSpecification :: Prelude.Maybe AttachmentEnaSrdSpecification,
    -- | The ID of the instance.
    NetworkInterfaceAttachment -> Maybe Text
instanceId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services account ID of the owner of the instance.
    NetworkInterfaceAttachment -> Maybe Text
instanceOwnerId :: Prelude.Maybe Prelude.Text,
    -- | The index of the network card.
    NetworkInterfaceAttachment -> Maybe Int
networkCardIndex :: Prelude.Maybe Prelude.Int,
    -- | The attachment state.
    NetworkInterfaceAttachment -> Maybe AttachmentStatus
status :: Prelude.Maybe AttachmentStatus
  }
  deriving (NetworkInterfaceAttachment -> NetworkInterfaceAttachment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NetworkInterfaceAttachment -> NetworkInterfaceAttachment -> Bool
$c/= :: NetworkInterfaceAttachment -> NetworkInterfaceAttachment -> Bool
== :: NetworkInterfaceAttachment -> NetworkInterfaceAttachment -> Bool
$c== :: NetworkInterfaceAttachment -> NetworkInterfaceAttachment -> Bool
Prelude.Eq, ReadPrec [NetworkInterfaceAttachment]
ReadPrec NetworkInterfaceAttachment
Int -> ReadS NetworkInterfaceAttachment
ReadS [NetworkInterfaceAttachment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NetworkInterfaceAttachment]
$creadListPrec :: ReadPrec [NetworkInterfaceAttachment]
readPrec :: ReadPrec NetworkInterfaceAttachment
$creadPrec :: ReadPrec NetworkInterfaceAttachment
readList :: ReadS [NetworkInterfaceAttachment]
$creadList :: ReadS [NetworkInterfaceAttachment]
readsPrec :: Int -> ReadS NetworkInterfaceAttachment
$creadsPrec :: Int -> ReadS NetworkInterfaceAttachment
Prelude.Read, Int -> NetworkInterfaceAttachment -> ShowS
[NetworkInterfaceAttachment] -> ShowS
NetworkInterfaceAttachment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NetworkInterfaceAttachment] -> ShowS
$cshowList :: [NetworkInterfaceAttachment] -> ShowS
show :: NetworkInterfaceAttachment -> String
$cshow :: NetworkInterfaceAttachment -> String
showsPrec :: Int -> NetworkInterfaceAttachment -> ShowS
$cshowsPrec :: Int -> NetworkInterfaceAttachment -> ShowS
Prelude.Show, forall x.
Rep NetworkInterfaceAttachment x -> NetworkInterfaceAttachment
forall x.
NetworkInterfaceAttachment -> Rep NetworkInterfaceAttachment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep NetworkInterfaceAttachment x -> NetworkInterfaceAttachment
$cfrom :: forall x.
NetworkInterfaceAttachment -> Rep NetworkInterfaceAttachment x
Prelude.Generic)

-- |
-- Create a value of 'NetworkInterfaceAttachment' 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:
--
-- 'attachTime', 'networkInterfaceAttachment_attachTime' - The timestamp indicating when the attachment initiated.
--
-- 'attachmentId', 'networkInterfaceAttachment_attachmentId' - The ID of the network interface attachment.
--
-- 'deleteOnTermination', 'networkInterfaceAttachment_deleteOnTermination' - Indicates whether the network interface is deleted when the instance is
-- terminated.
--
-- 'deviceIndex', 'networkInterfaceAttachment_deviceIndex' - The device index of the network interface attachment on the instance.
--
-- 'enaSrdSpecification', 'networkInterfaceAttachment_enaSrdSpecification' - Configures ENA Express for the network interface that this action
-- attaches to the instance.
--
-- 'instanceId', 'networkInterfaceAttachment_instanceId' - The ID of the instance.
--
-- 'instanceOwnerId', 'networkInterfaceAttachment_instanceOwnerId' - The Amazon Web Services account ID of the owner of the instance.
--
-- 'networkCardIndex', 'networkInterfaceAttachment_networkCardIndex' - The index of the network card.
--
-- 'status', 'networkInterfaceAttachment_status' - The attachment state.
newNetworkInterfaceAttachment ::
  NetworkInterfaceAttachment
newNetworkInterfaceAttachment :: NetworkInterfaceAttachment
newNetworkInterfaceAttachment =
  NetworkInterfaceAttachment'
    { $sel:attachTime:NetworkInterfaceAttachment' :: Maybe ISO8601
attachTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:attachmentId:NetworkInterfaceAttachment' :: Maybe Text
attachmentId = forall a. Maybe a
Prelude.Nothing,
      $sel:deleteOnTermination:NetworkInterfaceAttachment' :: Maybe Bool
deleteOnTermination = forall a. Maybe a
Prelude.Nothing,
      $sel:deviceIndex:NetworkInterfaceAttachment' :: Maybe Int
deviceIndex = forall a. Maybe a
Prelude.Nothing,
      $sel:enaSrdSpecification:NetworkInterfaceAttachment' :: Maybe AttachmentEnaSrdSpecification
enaSrdSpecification = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:NetworkInterfaceAttachment' :: Maybe Text
instanceId = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceOwnerId:NetworkInterfaceAttachment' :: Maybe Text
instanceOwnerId = forall a. Maybe a
Prelude.Nothing,
      $sel:networkCardIndex:NetworkInterfaceAttachment' :: Maybe Int
networkCardIndex = forall a. Maybe a
Prelude.Nothing,
      $sel:status:NetworkInterfaceAttachment' :: Maybe AttachmentStatus
status = forall a. Maybe a
Prelude.Nothing
    }

-- | The timestamp indicating when the attachment initiated.
networkInterfaceAttachment_attachTime :: Lens.Lens' NetworkInterfaceAttachment (Prelude.Maybe Prelude.UTCTime)
networkInterfaceAttachment_attachTime :: Lens' NetworkInterfaceAttachment (Maybe UTCTime)
networkInterfaceAttachment_attachTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterfaceAttachment' {Maybe ISO8601
attachTime :: Maybe ISO8601
$sel:attachTime:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe ISO8601
attachTime} -> Maybe ISO8601
attachTime) (\s :: NetworkInterfaceAttachment
s@NetworkInterfaceAttachment' {} Maybe ISO8601
a -> NetworkInterfaceAttachment
s {$sel:attachTime:NetworkInterfaceAttachment' :: Maybe ISO8601
attachTime = Maybe ISO8601
a} :: NetworkInterfaceAttachment) 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 network interface attachment.
networkInterfaceAttachment_attachmentId :: Lens.Lens' NetworkInterfaceAttachment (Prelude.Maybe Prelude.Text)
networkInterfaceAttachment_attachmentId :: Lens' NetworkInterfaceAttachment (Maybe Text)
networkInterfaceAttachment_attachmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterfaceAttachment' {Maybe Text
attachmentId :: Maybe Text
$sel:attachmentId:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe Text
attachmentId} -> Maybe Text
attachmentId) (\s :: NetworkInterfaceAttachment
s@NetworkInterfaceAttachment' {} Maybe Text
a -> NetworkInterfaceAttachment
s {$sel:attachmentId:NetworkInterfaceAttachment' :: Maybe Text
attachmentId = Maybe Text
a} :: NetworkInterfaceAttachment)

-- | Indicates whether the network interface is deleted when the instance is
-- terminated.
networkInterfaceAttachment_deleteOnTermination :: Lens.Lens' NetworkInterfaceAttachment (Prelude.Maybe Prelude.Bool)
networkInterfaceAttachment_deleteOnTermination :: Lens' NetworkInterfaceAttachment (Maybe Bool)
networkInterfaceAttachment_deleteOnTermination = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterfaceAttachment' {Maybe Bool
deleteOnTermination :: Maybe Bool
$sel:deleteOnTermination:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe Bool
deleteOnTermination} -> Maybe Bool
deleteOnTermination) (\s :: NetworkInterfaceAttachment
s@NetworkInterfaceAttachment' {} Maybe Bool
a -> NetworkInterfaceAttachment
s {$sel:deleteOnTermination:NetworkInterfaceAttachment' :: Maybe Bool
deleteOnTermination = Maybe Bool
a} :: NetworkInterfaceAttachment)

-- | The device index of the network interface attachment on the instance.
networkInterfaceAttachment_deviceIndex :: Lens.Lens' NetworkInterfaceAttachment (Prelude.Maybe Prelude.Int)
networkInterfaceAttachment_deviceIndex :: Lens' NetworkInterfaceAttachment (Maybe Int)
networkInterfaceAttachment_deviceIndex = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterfaceAttachment' {Maybe Int
deviceIndex :: Maybe Int
$sel:deviceIndex:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe Int
deviceIndex} -> Maybe Int
deviceIndex) (\s :: NetworkInterfaceAttachment
s@NetworkInterfaceAttachment' {} Maybe Int
a -> NetworkInterfaceAttachment
s {$sel:deviceIndex:NetworkInterfaceAttachment' :: Maybe Int
deviceIndex = Maybe Int
a} :: NetworkInterfaceAttachment)

-- | Configures ENA Express for the network interface that this action
-- attaches to the instance.
networkInterfaceAttachment_enaSrdSpecification :: Lens.Lens' NetworkInterfaceAttachment (Prelude.Maybe AttachmentEnaSrdSpecification)
networkInterfaceAttachment_enaSrdSpecification :: Lens'
  NetworkInterfaceAttachment (Maybe AttachmentEnaSrdSpecification)
networkInterfaceAttachment_enaSrdSpecification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterfaceAttachment' {Maybe AttachmentEnaSrdSpecification
enaSrdSpecification :: Maybe AttachmentEnaSrdSpecification
$sel:enaSrdSpecification:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe AttachmentEnaSrdSpecification
enaSrdSpecification} -> Maybe AttachmentEnaSrdSpecification
enaSrdSpecification) (\s :: NetworkInterfaceAttachment
s@NetworkInterfaceAttachment' {} Maybe AttachmentEnaSrdSpecification
a -> NetworkInterfaceAttachment
s {$sel:enaSrdSpecification:NetworkInterfaceAttachment' :: Maybe AttachmentEnaSrdSpecification
enaSrdSpecification = Maybe AttachmentEnaSrdSpecification
a} :: NetworkInterfaceAttachment)

-- | The ID of the instance.
networkInterfaceAttachment_instanceId :: Lens.Lens' NetworkInterfaceAttachment (Prelude.Maybe Prelude.Text)
networkInterfaceAttachment_instanceId :: Lens' NetworkInterfaceAttachment (Maybe Text)
networkInterfaceAttachment_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterfaceAttachment' {Maybe Text
instanceId :: Maybe Text
$sel:instanceId:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe Text
instanceId} -> Maybe Text
instanceId) (\s :: NetworkInterfaceAttachment
s@NetworkInterfaceAttachment' {} Maybe Text
a -> NetworkInterfaceAttachment
s {$sel:instanceId:NetworkInterfaceAttachment' :: Maybe Text
instanceId = Maybe Text
a} :: NetworkInterfaceAttachment)

-- | The Amazon Web Services account ID of the owner of the instance.
networkInterfaceAttachment_instanceOwnerId :: Lens.Lens' NetworkInterfaceAttachment (Prelude.Maybe Prelude.Text)
networkInterfaceAttachment_instanceOwnerId :: Lens' NetworkInterfaceAttachment (Maybe Text)
networkInterfaceAttachment_instanceOwnerId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterfaceAttachment' {Maybe Text
instanceOwnerId :: Maybe Text
$sel:instanceOwnerId:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe Text
instanceOwnerId} -> Maybe Text
instanceOwnerId) (\s :: NetworkInterfaceAttachment
s@NetworkInterfaceAttachment' {} Maybe Text
a -> NetworkInterfaceAttachment
s {$sel:instanceOwnerId:NetworkInterfaceAttachment' :: Maybe Text
instanceOwnerId = Maybe Text
a} :: NetworkInterfaceAttachment)

-- | The index of the network card.
networkInterfaceAttachment_networkCardIndex :: Lens.Lens' NetworkInterfaceAttachment (Prelude.Maybe Prelude.Int)
networkInterfaceAttachment_networkCardIndex :: Lens' NetworkInterfaceAttachment (Maybe Int)
networkInterfaceAttachment_networkCardIndex = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterfaceAttachment' {Maybe Int
networkCardIndex :: Maybe Int
$sel:networkCardIndex:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe Int
networkCardIndex} -> Maybe Int
networkCardIndex) (\s :: NetworkInterfaceAttachment
s@NetworkInterfaceAttachment' {} Maybe Int
a -> NetworkInterfaceAttachment
s {$sel:networkCardIndex:NetworkInterfaceAttachment' :: Maybe Int
networkCardIndex = Maybe Int
a} :: NetworkInterfaceAttachment)

-- | The attachment state.
networkInterfaceAttachment_status :: Lens.Lens' NetworkInterfaceAttachment (Prelude.Maybe AttachmentStatus)
networkInterfaceAttachment_status :: Lens' NetworkInterfaceAttachment (Maybe AttachmentStatus)
networkInterfaceAttachment_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NetworkInterfaceAttachment' {Maybe AttachmentStatus
status :: Maybe AttachmentStatus
$sel:status:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe AttachmentStatus
status} -> Maybe AttachmentStatus
status) (\s :: NetworkInterfaceAttachment
s@NetworkInterfaceAttachment' {} Maybe AttachmentStatus
a -> NetworkInterfaceAttachment
s {$sel:status:NetworkInterfaceAttachment' :: Maybe AttachmentStatus
status = Maybe AttachmentStatus
a} :: NetworkInterfaceAttachment)

instance Data.FromXML NetworkInterfaceAttachment where
  parseXML :: [Node] -> Either String NetworkInterfaceAttachment
parseXML [Node]
x =
    Maybe ISO8601
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe AttachmentEnaSrdSpecification
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe AttachmentStatus
-> NetworkInterfaceAttachment
NetworkInterfaceAttachment'
      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
"attachTime")
      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
"attachmentId")
      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
"deleteOnTermination")
      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
"deviceIndex")
      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
"enaSrdSpecification")
      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
"instanceId")
      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
"instanceOwnerId")
      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
"networkCardIndex")
      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
"status")

instance Prelude.Hashable NetworkInterfaceAttachment where
  hashWithSalt :: Int -> NetworkInterfaceAttachment -> Int
hashWithSalt Int
_salt NetworkInterfaceAttachment' {Maybe Bool
Maybe Int
Maybe Text
Maybe ISO8601
Maybe AttachmentEnaSrdSpecification
Maybe AttachmentStatus
status :: Maybe AttachmentStatus
networkCardIndex :: Maybe Int
instanceOwnerId :: Maybe Text
instanceId :: Maybe Text
enaSrdSpecification :: Maybe AttachmentEnaSrdSpecification
deviceIndex :: Maybe Int
deleteOnTermination :: Maybe Bool
attachmentId :: Maybe Text
attachTime :: Maybe ISO8601
$sel:status:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe AttachmentStatus
$sel:networkCardIndex:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe Int
$sel:instanceOwnerId:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe Text
$sel:instanceId:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe Text
$sel:enaSrdSpecification:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe AttachmentEnaSrdSpecification
$sel:deviceIndex:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe Int
$sel:deleteOnTermination:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe Bool
$sel:attachmentId:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe Text
$sel:attachTime:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe ISO8601
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
attachTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
attachmentId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
deleteOnTermination
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
deviceIndex
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AttachmentEnaSrdSpecification
enaSrdSpecification
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
instanceOwnerId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
networkCardIndex
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AttachmentStatus
status

instance Prelude.NFData NetworkInterfaceAttachment where
  rnf :: NetworkInterfaceAttachment -> ()
rnf NetworkInterfaceAttachment' {Maybe Bool
Maybe Int
Maybe Text
Maybe ISO8601
Maybe AttachmentEnaSrdSpecification
Maybe AttachmentStatus
status :: Maybe AttachmentStatus
networkCardIndex :: Maybe Int
instanceOwnerId :: Maybe Text
instanceId :: Maybe Text
enaSrdSpecification :: Maybe AttachmentEnaSrdSpecification
deviceIndex :: Maybe Int
deleteOnTermination :: Maybe Bool
attachmentId :: Maybe Text
attachTime :: Maybe ISO8601
$sel:status:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe AttachmentStatus
$sel:networkCardIndex:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe Int
$sel:instanceOwnerId:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe Text
$sel:instanceId:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe Text
$sel:enaSrdSpecification:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe AttachmentEnaSrdSpecification
$sel:deviceIndex:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe Int
$sel:deleteOnTermination:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe Bool
$sel:attachmentId:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe Text
$sel:attachTime:NetworkInterfaceAttachment' :: NetworkInterfaceAttachment -> Maybe ISO8601
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
attachTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
attachmentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
deleteOnTermination
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
deviceIndex
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AttachmentEnaSrdSpecification
enaSrdSpecification
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
instanceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
instanceOwnerId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
networkCardIndex
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AttachmentStatus
status