{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.EC2.AttachNetworkInterface
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Attaches a network interface to an instance.
module Amazonka.EC2.AttachNetworkInterface
  ( -- * Creating a Request
    AttachNetworkInterface (..),
    newAttachNetworkInterface,

    -- * Request Lenses
    attachNetworkInterface_dryRun,
    attachNetworkInterface_enaSrdSpecification,
    attachNetworkInterface_networkCardIndex,
    attachNetworkInterface_deviceIndex,
    attachNetworkInterface_instanceId,
    attachNetworkInterface_networkInterfaceId,

    -- * Destructuring the Response
    AttachNetworkInterfaceResponse (..),
    newAttachNetworkInterfaceResponse,

    -- * Response Lenses
    attachNetworkInterfaceResponse_attachmentId,
    attachNetworkInterfaceResponse_networkCardIndex,
    attachNetworkInterfaceResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | Contains the parameters for AttachNetworkInterface.
--
-- /See:/ 'newAttachNetworkInterface' smart constructor.
data AttachNetworkInterface = AttachNetworkInterface'
  { -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    AttachNetworkInterface -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | Configures ENA Express for the network interface that this action
    -- attaches to the instance.
    AttachNetworkInterface -> Maybe EnaSrdSpecification
enaSrdSpecification :: Prelude.Maybe EnaSrdSpecification,
    -- | The index of the network card. Some instance types support multiple
    -- network cards. The primary network interface must be assigned to network
    -- card index 0. The default is network card index 0.
    AttachNetworkInterface -> Maybe Int
networkCardIndex :: Prelude.Maybe Prelude.Int,
    -- | The index of the device for the network interface attachment.
    AttachNetworkInterface -> Int
deviceIndex :: Prelude.Int,
    -- | The ID of the instance.
    AttachNetworkInterface -> Text
instanceId :: Prelude.Text,
    -- | The ID of the network interface.
    AttachNetworkInterface -> Text
networkInterfaceId :: Prelude.Text
  }
  deriving (AttachNetworkInterface -> AttachNetworkInterface -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachNetworkInterface -> AttachNetworkInterface -> Bool
$c/= :: AttachNetworkInterface -> AttachNetworkInterface -> Bool
== :: AttachNetworkInterface -> AttachNetworkInterface -> Bool
$c== :: AttachNetworkInterface -> AttachNetworkInterface -> Bool
Prelude.Eq, ReadPrec [AttachNetworkInterface]
ReadPrec AttachNetworkInterface
Int -> ReadS AttachNetworkInterface
ReadS [AttachNetworkInterface]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttachNetworkInterface]
$creadListPrec :: ReadPrec [AttachNetworkInterface]
readPrec :: ReadPrec AttachNetworkInterface
$creadPrec :: ReadPrec AttachNetworkInterface
readList :: ReadS [AttachNetworkInterface]
$creadList :: ReadS [AttachNetworkInterface]
readsPrec :: Int -> ReadS AttachNetworkInterface
$creadsPrec :: Int -> ReadS AttachNetworkInterface
Prelude.Read, Int -> AttachNetworkInterface -> ShowS
[AttachNetworkInterface] -> ShowS
AttachNetworkInterface -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachNetworkInterface] -> ShowS
$cshowList :: [AttachNetworkInterface] -> ShowS
show :: AttachNetworkInterface -> String
$cshow :: AttachNetworkInterface -> String
showsPrec :: Int -> AttachNetworkInterface -> ShowS
$cshowsPrec :: Int -> AttachNetworkInterface -> ShowS
Prelude.Show, forall x. Rep AttachNetworkInterface x -> AttachNetworkInterface
forall x. AttachNetworkInterface -> Rep AttachNetworkInterface x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AttachNetworkInterface x -> AttachNetworkInterface
$cfrom :: forall x. AttachNetworkInterface -> Rep AttachNetworkInterface x
Prelude.Generic)

-- |
-- Create a value of 'AttachNetworkInterface' 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:
--
-- 'dryRun', 'attachNetworkInterface_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'enaSrdSpecification', 'attachNetworkInterface_enaSrdSpecification' - Configures ENA Express for the network interface that this action
-- attaches to the instance.
--
-- 'networkCardIndex', 'attachNetworkInterface_networkCardIndex' - The index of the network card. Some instance types support multiple
-- network cards. The primary network interface must be assigned to network
-- card index 0. The default is network card index 0.
--
-- 'deviceIndex', 'attachNetworkInterface_deviceIndex' - The index of the device for the network interface attachment.
--
-- 'instanceId', 'attachNetworkInterface_instanceId' - The ID of the instance.
--
-- 'networkInterfaceId', 'attachNetworkInterface_networkInterfaceId' - The ID of the network interface.
newAttachNetworkInterface ::
  -- | 'deviceIndex'
  Prelude.Int ->
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'networkInterfaceId'
  Prelude.Text ->
  AttachNetworkInterface
newAttachNetworkInterface :: Int -> Text -> Text -> AttachNetworkInterface
newAttachNetworkInterface
  Int
pDeviceIndex_
  Text
pInstanceId_
  Text
pNetworkInterfaceId_ =
    AttachNetworkInterface'
      { $sel:dryRun:AttachNetworkInterface' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
        $sel:enaSrdSpecification:AttachNetworkInterface' :: Maybe EnaSrdSpecification
enaSrdSpecification = forall a. Maybe a
Prelude.Nothing,
        $sel:networkCardIndex:AttachNetworkInterface' :: Maybe Int
networkCardIndex = forall a. Maybe a
Prelude.Nothing,
        $sel:deviceIndex:AttachNetworkInterface' :: Int
deviceIndex = Int
pDeviceIndex_,
        $sel:instanceId:AttachNetworkInterface' :: Text
instanceId = Text
pInstanceId_,
        $sel:networkInterfaceId:AttachNetworkInterface' :: Text
networkInterfaceId = Text
pNetworkInterfaceId_
      }

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
attachNetworkInterface_dryRun :: Lens.Lens' AttachNetworkInterface (Prelude.Maybe Prelude.Bool)
attachNetworkInterface_dryRun :: Lens' AttachNetworkInterface (Maybe Bool)
attachNetworkInterface_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachNetworkInterface' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:AttachNetworkInterface' :: AttachNetworkInterface -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: AttachNetworkInterface
s@AttachNetworkInterface' {} Maybe Bool
a -> AttachNetworkInterface
s {$sel:dryRun:AttachNetworkInterface' :: Maybe Bool
dryRun = Maybe Bool
a} :: AttachNetworkInterface)

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

-- | The index of the network card. Some instance types support multiple
-- network cards. The primary network interface must be assigned to network
-- card index 0. The default is network card index 0.
attachNetworkInterface_networkCardIndex :: Lens.Lens' AttachNetworkInterface (Prelude.Maybe Prelude.Int)
attachNetworkInterface_networkCardIndex :: Lens' AttachNetworkInterface (Maybe Int)
attachNetworkInterface_networkCardIndex = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachNetworkInterface' {Maybe Int
networkCardIndex :: Maybe Int
$sel:networkCardIndex:AttachNetworkInterface' :: AttachNetworkInterface -> Maybe Int
networkCardIndex} -> Maybe Int
networkCardIndex) (\s :: AttachNetworkInterface
s@AttachNetworkInterface' {} Maybe Int
a -> AttachNetworkInterface
s {$sel:networkCardIndex:AttachNetworkInterface' :: Maybe Int
networkCardIndex = Maybe Int
a} :: AttachNetworkInterface)

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

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

-- | The ID of the network interface.
attachNetworkInterface_networkInterfaceId :: Lens.Lens' AttachNetworkInterface Prelude.Text
attachNetworkInterface_networkInterfaceId :: Lens' AttachNetworkInterface Text
attachNetworkInterface_networkInterfaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachNetworkInterface' {Text
networkInterfaceId :: Text
$sel:networkInterfaceId:AttachNetworkInterface' :: AttachNetworkInterface -> Text
networkInterfaceId} -> Text
networkInterfaceId) (\s :: AttachNetworkInterface
s@AttachNetworkInterface' {} Text
a -> AttachNetworkInterface
s {$sel:networkInterfaceId:AttachNetworkInterface' :: Text
networkInterfaceId = Text
a} :: AttachNetworkInterface)

instance Core.AWSRequest AttachNetworkInterface where
  type
    AWSResponse AttachNetworkInterface =
      AttachNetworkInterfaceResponse
  request :: (Service -> Service)
-> AttachNetworkInterface -> Request AttachNetworkInterface
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy AttachNetworkInterface
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AttachNetworkInterface)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text -> Maybe Int -> Int -> AttachNetworkInterfaceResponse
AttachNetworkInterfaceResponse'
            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
"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
"networkCardIndex")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable AttachNetworkInterface where
  hashWithSalt :: Int -> AttachNetworkInterface -> Int
hashWithSalt Int
_salt AttachNetworkInterface' {Int
Maybe Bool
Maybe Int
Maybe EnaSrdSpecification
Text
networkInterfaceId :: Text
instanceId :: Text
deviceIndex :: Int
networkCardIndex :: Maybe Int
enaSrdSpecification :: Maybe EnaSrdSpecification
dryRun :: Maybe Bool
$sel:networkInterfaceId:AttachNetworkInterface' :: AttachNetworkInterface -> Text
$sel:instanceId:AttachNetworkInterface' :: AttachNetworkInterface -> Text
$sel:deviceIndex:AttachNetworkInterface' :: AttachNetworkInterface -> Int
$sel:networkCardIndex:AttachNetworkInterface' :: AttachNetworkInterface -> Maybe Int
$sel:enaSrdSpecification:AttachNetworkInterface' :: AttachNetworkInterface -> Maybe EnaSrdSpecification
$sel:dryRun:AttachNetworkInterface' :: AttachNetworkInterface -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EnaSrdSpecification
enaSrdSpecification
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
networkCardIndex
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Int
deviceIndex
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
networkInterfaceId

instance Prelude.NFData AttachNetworkInterface where
  rnf :: AttachNetworkInterface -> ()
rnf AttachNetworkInterface' {Int
Maybe Bool
Maybe Int
Maybe EnaSrdSpecification
Text
networkInterfaceId :: Text
instanceId :: Text
deviceIndex :: Int
networkCardIndex :: Maybe Int
enaSrdSpecification :: Maybe EnaSrdSpecification
dryRun :: Maybe Bool
$sel:networkInterfaceId:AttachNetworkInterface' :: AttachNetworkInterface -> Text
$sel:instanceId:AttachNetworkInterface' :: AttachNetworkInterface -> Text
$sel:deviceIndex:AttachNetworkInterface' :: AttachNetworkInterface -> Int
$sel:networkCardIndex:AttachNetworkInterface' :: AttachNetworkInterface -> Maybe Int
$sel:enaSrdSpecification:AttachNetworkInterface' :: AttachNetworkInterface -> Maybe EnaSrdSpecification
$sel:dryRun:AttachNetworkInterface' :: AttachNetworkInterface -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EnaSrdSpecification
enaSrdSpecification
      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 Int
deviceIndex
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
networkInterfaceId

instance Data.ToHeaders AttachNetworkInterface where
  toHeaders :: AttachNetworkInterface -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery AttachNetworkInterface where
  toQuery :: AttachNetworkInterface -> QueryString
toQuery AttachNetworkInterface' {Int
Maybe Bool
Maybe Int
Maybe EnaSrdSpecification
Text
networkInterfaceId :: Text
instanceId :: Text
deviceIndex :: Int
networkCardIndex :: Maybe Int
enaSrdSpecification :: Maybe EnaSrdSpecification
dryRun :: Maybe Bool
$sel:networkInterfaceId:AttachNetworkInterface' :: AttachNetworkInterface -> Text
$sel:instanceId:AttachNetworkInterface' :: AttachNetworkInterface -> Text
$sel:deviceIndex:AttachNetworkInterface' :: AttachNetworkInterface -> Int
$sel:networkCardIndex:AttachNetworkInterface' :: AttachNetworkInterface -> Maybe Int
$sel:enaSrdSpecification:AttachNetworkInterface' :: AttachNetworkInterface -> Maybe EnaSrdSpecification
$sel:dryRun:AttachNetworkInterface' :: AttachNetworkInterface -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"AttachNetworkInterface" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"EnaSrdSpecification" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe EnaSrdSpecification
enaSrdSpecification,
        ByteString
"NetworkCardIndex" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
networkCardIndex,
        ByteString
"DeviceIndex" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Int
deviceIndex,
        ByteString
"InstanceId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
instanceId,
        ByteString
"NetworkInterfaceId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
networkInterfaceId
      ]

-- | Contains the output of AttachNetworkInterface.
--
-- /See:/ 'newAttachNetworkInterfaceResponse' smart constructor.
data AttachNetworkInterfaceResponse = AttachNetworkInterfaceResponse'
  { -- | The ID of the network interface attachment.
    AttachNetworkInterfaceResponse -> Maybe Text
attachmentId :: Prelude.Maybe Prelude.Text,
    -- | The index of the network card.
    AttachNetworkInterfaceResponse -> Maybe Int
networkCardIndex :: Prelude.Maybe Prelude.Int,
    -- | The response's http status code.
    AttachNetworkInterfaceResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (AttachNetworkInterfaceResponse
-> AttachNetworkInterfaceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachNetworkInterfaceResponse
-> AttachNetworkInterfaceResponse -> Bool
$c/= :: AttachNetworkInterfaceResponse
-> AttachNetworkInterfaceResponse -> Bool
== :: AttachNetworkInterfaceResponse
-> AttachNetworkInterfaceResponse -> Bool
$c== :: AttachNetworkInterfaceResponse
-> AttachNetworkInterfaceResponse -> Bool
Prelude.Eq, ReadPrec [AttachNetworkInterfaceResponse]
ReadPrec AttachNetworkInterfaceResponse
Int -> ReadS AttachNetworkInterfaceResponse
ReadS [AttachNetworkInterfaceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttachNetworkInterfaceResponse]
$creadListPrec :: ReadPrec [AttachNetworkInterfaceResponse]
readPrec :: ReadPrec AttachNetworkInterfaceResponse
$creadPrec :: ReadPrec AttachNetworkInterfaceResponse
readList :: ReadS [AttachNetworkInterfaceResponse]
$creadList :: ReadS [AttachNetworkInterfaceResponse]
readsPrec :: Int -> ReadS AttachNetworkInterfaceResponse
$creadsPrec :: Int -> ReadS AttachNetworkInterfaceResponse
Prelude.Read, Int -> AttachNetworkInterfaceResponse -> ShowS
[AttachNetworkInterfaceResponse] -> ShowS
AttachNetworkInterfaceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachNetworkInterfaceResponse] -> ShowS
$cshowList :: [AttachNetworkInterfaceResponse] -> ShowS
show :: AttachNetworkInterfaceResponse -> String
$cshow :: AttachNetworkInterfaceResponse -> String
showsPrec :: Int -> AttachNetworkInterfaceResponse -> ShowS
$cshowsPrec :: Int -> AttachNetworkInterfaceResponse -> ShowS
Prelude.Show, forall x.
Rep AttachNetworkInterfaceResponse x
-> AttachNetworkInterfaceResponse
forall x.
AttachNetworkInterfaceResponse
-> Rep AttachNetworkInterfaceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AttachNetworkInterfaceResponse x
-> AttachNetworkInterfaceResponse
$cfrom :: forall x.
AttachNetworkInterfaceResponse
-> Rep AttachNetworkInterfaceResponse x
Prelude.Generic)

-- |
-- Create a value of 'AttachNetworkInterfaceResponse' 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:
--
-- 'attachmentId', 'attachNetworkInterfaceResponse_attachmentId' - The ID of the network interface attachment.
--
-- 'networkCardIndex', 'attachNetworkInterfaceResponse_networkCardIndex' - The index of the network card.
--
-- 'httpStatus', 'attachNetworkInterfaceResponse_httpStatus' - The response's http status code.
newAttachNetworkInterfaceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AttachNetworkInterfaceResponse
newAttachNetworkInterfaceResponse :: Int -> AttachNetworkInterfaceResponse
newAttachNetworkInterfaceResponse Int
pHttpStatus_ =
  AttachNetworkInterfaceResponse'
    { $sel:attachmentId:AttachNetworkInterfaceResponse' :: Maybe Text
attachmentId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:networkCardIndex:AttachNetworkInterfaceResponse' :: Maybe Int
networkCardIndex = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:AttachNetworkInterfaceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ID of the network interface attachment.
attachNetworkInterfaceResponse_attachmentId :: Lens.Lens' AttachNetworkInterfaceResponse (Prelude.Maybe Prelude.Text)
attachNetworkInterfaceResponse_attachmentId :: Lens' AttachNetworkInterfaceResponse (Maybe Text)
attachNetworkInterfaceResponse_attachmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachNetworkInterfaceResponse' {Maybe Text
attachmentId :: Maybe Text
$sel:attachmentId:AttachNetworkInterfaceResponse' :: AttachNetworkInterfaceResponse -> Maybe Text
attachmentId} -> Maybe Text
attachmentId) (\s :: AttachNetworkInterfaceResponse
s@AttachNetworkInterfaceResponse' {} Maybe Text
a -> AttachNetworkInterfaceResponse
s {$sel:attachmentId:AttachNetworkInterfaceResponse' :: Maybe Text
attachmentId = Maybe Text
a} :: AttachNetworkInterfaceResponse)

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

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

instance
  Prelude.NFData
    AttachNetworkInterfaceResponse
  where
  rnf :: AttachNetworkInterfaceResponse -> ()
rnf AttachNetworkInterfaceResponse' {Int
Maybe Int
Maybe Text
httpStatus :: Int
networkCardIndex :: Maybe Int
attachmentId :: Maybe Text
$sel:httpStatus:AttachNetworkInterfaceResponse' :: AttachNetworkInterfaceResponse -> Int
$sel:networkCardIndex:AttachNetworkInterfaceResponse' :: AttachNetworkInterfaceResponse -> Maybe Int
$sel:attachmentId:AttachNetworkInterfaceResponse' :: AttachNetworkInterfaceResponse -> Maybe Text
..} =
    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 Int
networkCardIndex
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus