{-# 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.ModifyNetworkInterfaceAttribute
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Modifies the specified network interface attribute. You can specify only
-- one attribute at a time. You can use this action to attach and detach
-- security groups from an existing EC2 instance.
module Amazonka.EC2.ModifyNetworkInterfaceAttribute
  ( -- * Creating a Request
    ModifyNetworkInterfaceAttribute (..),
    newModifyNetworkInterfaceAttribute,

    -- * Request Lenses
    modifyNetworkInterfaceAttribute_attachment,
    modifyNetworkInterfaceAttribute_description,
    modifyNetworkInterfaceAttribute_dryRun,
    modifyNetworkInterfaceAttribute_enaSrdSpecification,
    modifyNetworkInterfaceAttribute_groups,
    modifyNetworkInterfaceAttribute_sourceDestCheck,
    modifyNetworkInterfaceAttribute_networkInterfaceId,

    -- * Destructuring the Response
    ModifyNetworkInterfaceAttributeResponse (..),
    newModifyNetworkInterfaceAttributeResponse,
  )
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 ModifyNetworkInterfaceAttribute.
--
-- /See:/ 'newModifyNetworkInterfaceAttribute' smart constructor.
data ModifyNetworkInterfaceAttribute = ModifyNetworkInterfaceAttribute'
  { -- | Information about the interface attachment. If modifying the
    -- @delete on termination@ attribute, you must specify the ID of the
    -- interface attachment.
    ModifyNetworkInterfaceAttribute
-> Maybe NetworkInterfaceAttachmentChanges
attachment :: Prelude.Maybe NetworkInterfaceAttachmentChanges,
    -- | A description for the network interface.
    ModifyNetworkInterfaceAttribute -> Maybe AttributeValue
description :: Prelude.Maybe AttributeValue,
    -- | 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@.
    ModifyNetworkInterfaceAttribute -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | Updates the ENA Express configuration for the network interface that’s
    -- attached to the instance.
    ModifyNetworkInterfaceAttribute -> Maybe EnaSrdSpecification
enaSrdSpecification :: Prelude.Maybe EnaSrdSpecification,
    -- | Changes the security groups for the network interface. The new set of
    -- groups you specify replaces the current set. You must specify at least
    -- one group, even if it\'s just the default security group in the VPC. You
    -- must specify the ID of the security group, not the name.
    ModifyNetworkInterfaceAttribute -> Maybe [Text]
groups :: Prelude.Maybe [Prelude.Text],
    -- | Enable or disable source\/destination checks, which ensure that the
    -- instance is either the source or the destination of any traffic that it
    -- receives. If the value is @true@, source\/destination checks are
    -- enabled; otherwise, they are disabled. The default value is @true@. You
    -- must disable source\/destination checks if the instance runs services
    -- such as network address translation, routing, or firewalls.
    ModifyNetworkInterfaceAttribute -> Maybe AttributeBooleanValue
sourceDestCheck :: Prelude.Maybe AttributeBooleanValue,
    -- | The ID of the network interface.
    ModifyNetworkInterfaceAttribute -> Text
networkInterfaceId :: Prelude.Text
  }
  deriving (ModifyNetworkInterfaceAttribute
-> ModifyNetworkInterfaceAttribute -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifyNetworkInterfaceAttribute
-> ModifyNetworkInterfaceAttribute -> Bool
$c/= :: ModifyNetworkInterfaceAttribute
-> ModifyNetworkInterfaceAttribute -> Bool
== :: ModifyNetworkInterfaceAttribute
-> ModifyNetworkInterfaceAttribute -> Bool
$c== :: ModifyNetworkInterfaceAttribute
-> ModifyNetworkInterfaceAttribute -> Bool
Prelude.Eq, ReadPrec [ModifyNetworkInterfaceAttribute]
ReadPrec ModifyNetworkInterfaceAttribute
Int -> ReadS ModifyNetworkInterfaceAttribute
ReadS [ModifyNetworkInterfaceAttribute]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifyNetworkInterfaceAttribute]
$creadListPrec :: ReadPrec [ModifyNetworkInterfaceAttribute]
readPrec :: ReadPrec ModifyNetworkInterfaceAttribute
$creadPrec :: ReadPrec ModifyNetworkInterfaceAttribute
readList :: ReadS [ModifyNetworkInterfaceAttribute]
$creadList :: ReadS [ModifyNetworkInterfaceAttribute]
readsPrec :: Int -> ReadS ModifyNetworkInterfaceAttribute
$creadsPrec :: Int -> ReadS ModifyNetworkInterfaceAttribute
Prelude.Read, Int -> ModifyNetworkInterfaceAttribute -> ShowS
[ModifyNetworkInterfaceAttribute] -> ShowS
ModifyNetworkInterfaceAttribute -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifyNetworkInterfaceAttribute] -> ShowS
$cshowList :: [ModifyNetworkInterfaceAttribute] -> ShowS
show :: ModifyNetworkInterfaceAttribute -> String
$cshow :: ModifyNetworkInterfaceAttribute -> String
showsPrec :: Int -> ModifyNetworkInterfaceAttribute -> ShowS
$cshowsPrec :: Int -> ModifyNetworkInterfaceAttribute -> ShowS
Prelude.Show, forall x.
Rep ModifyNetworkInterfaceAttribute x
-> ModifyNetworkInterfaceAttribute
forall x.
ModifyNetworkInterfaceAttribute
-> Rep ModifyNetworkInterfaceAttribute x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ModifyNetworkInterfaceAttribute x
-> ModifyNetworkInterfaceAttribute
$cfrom :: forall x.
ModifyNetworkInterfaceAttribute
-> Rep ModifyNetworkInterfaceAttribute x
Prelude.Generic)

-- |
-- Create a value of 'ModifyNetworkInterfaceAttribute' 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:
--
-- 'attachment', 'modifyNetworkInterfaceAttribute_attachment' - Information about the interface attachment. If modifying the
-- @delete on termination@ attribute, you must specify the ID of the
-- interface attachment.
--
-- 'description', 'modifyNetworkInterfaceAttribute_description' - A description for the network interface.
--
-- 'dryRun', 'modifyNetworkInterfaceAttribute_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', 'modifyNetworkInterfaceAttribute_enaSrdSpecification' - Updates the ENA Express configuration for the network interface that’s
-- attached to the instance.
--
-- 'groups', 'modifyNetworkInterfaceAttribute_groups' - Changes the security groups for the network interface. The new set of
-- groups you specify replaces the current set. You must specify at least
-- one group, even if it\'s just the default security group in the VPC. You
-- must specify the ID of the security group, not the name.
--
-- 'sourceDestCheck', 'modifyNetworkInterfaceAttribute_sourceDestCheck' - Enable or disable source\/destination checks, which ensure that the
-- instance is either the source or the destination of any traffic that it
-- receives. If the value is @true@, source\/destination checks are
-- enabled; otherwise, they are disabled. The default value is @true@. You
-- must disable source\/destination checks if the instance runs services
-- such as network address translation, routing, or firewalls.
--
-- 'networkInterfaceId', 'modifyNetworkInterfaceAttribute_networkInterfaceId' - The ID of the network interface.
newModifyNetworkInterfaceAttribute ::
  -- | 'networkInterfaceId'
  Prelude.Text ->
  ModifyNetworkInterfaceAttribute
newModifyNetworkInterfaceAttribute :: Text -> ModifyNetworkInterfaceAttribute
newModifyNetworkInterfaceAttribute
  Text
pNetworkInterfaceId_ =
    ModifyNetworkInterfaceAttribute'
      { $sel:attachment:ModifyNetworkInterfaceAttribute' :: Maybe NetworkInterfaceAttachmentChanges
attachment =
          forall a. Maybe a
Prelude.Nothing,
        $sel:description:ModifyNetworkInterfaceAttribute' :: Maybe AttributeValue
description = forall a. Maybe a
Prelude.Nothing,
        $sel:dryRun:ModifyNetworkInterfaceAttribute' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
        $sel:enaSrdSpecification:ModifyNetworkInterfaceAttribute' :: Maybe EnaSrdSpecification
enaSrdSpecification = forall a. Maybe a
Prelude.Nothing,
        $sel:groups:ModifyNetworkInterfaceAttribute' :: Maybe [Text]
groups = forall a. Maybe a
Prelude.Nothing,
        $sel:sourceDestCheck:ModifyNetworkInterfaceAttribute' :: Maybe AttributeBooleanValue
sourceDestCheck = forall a. Maybe a
Prelude.Nothing,
        $sel:networkInterfaceId:ModifyNetworkInterfaceAttribute' :: Text
networkInterfaceId = Text
pNetworkInterfaceId_
      }

-- | Information about the interface attachment. If modifying the
-- @delete on termination@ attribute, you must specify the ID of the
-- interface attachment.
modifyNetworkInterfaceAttribute_attachment :: Lens.Lens' ModifyNetworkInterfaceAttribute (Prelude.Maybe NetworkInterfaceAttachmentChanges)
modifyNetworkInterfaceAttribute_attachment :: Lens'
  ModifyNetworkInterfaceAttribute
  (Maybe NetworkInterfaceAttachmentChanges)
modifyNetworkInterfaceAttribute_attachment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyNetworkInterfaceAttribute' {Maybe NetworkInterfaceAttachmentChanges
attachment :: Maybe NetworkInterfaceAttachmentChanges
$sel:attachment:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute
-> Maybe NetworkInterfaceAttachmentChanges
attachment} -> Maybe NetworkInterfaceAttachmentChanges
attachment) (\s :: ModifyNetworkInterfaceAttribute
s@ModifyNetworkInterfaceAttribute' {} Maybe NetworkInterfaceAttachmentChanges
a -> ModifyNetworkInterfaceAttribute
s {$sel:attachment:ModifyNetworkInterfaceAttribute' :: Maybe NetworkInterfaceAttachmentChanges
attachment = Maybe NetworkInterfaceAttachmentChanges
a} :: ModifyNetworkInterfaceAttribute)

-- | A description for the network interface.
modifyNetworkInterfaceAttribute_description :: Lens.Lens' ModifyNetworkInterfaceAttribute (Prelude.Maybe AttributeValue)
modifyNetworkInterfaceAttribute_description :: Lens' ModifyNetworkInterfaceAttribute (Maybe AttributeValue)
modifyNetworkInterfaceAttribute_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyNetworkInterfaceAttribute' {Maybe AttributeValue
description :: Maybe AttributeValue
$sel:description:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe AttributeValue
description} -> Maybe AttributeValue
description) (\s :: ModifyNetworkInterfaceAttribute
s@ModifyNetworkInterfaceAttribute' {} Maybe AttributeValue
a -> ModifyNetworkInterfaceAttribute
s {$sel:description:ModifyNetworkInterfaceAttribute' :: Maybe AttributeValue
description = Maybe AttributeValue
a} :: ModifyNetworkInterfaceAttribute)

-- | 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@.
modifyNetworkInterfaceAttribute_dryRun :: Lens.Lens' ModifyNetworkInterfaceAttribute (Prelude.Maybe Prelude.Bool)
modifyNetworkInterfaceAttribute_dryRun :: Lens' ModifyNetworkInterfaceAttribute (Maybe Bool)
modifyNetworkInterfaceAttribute_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyNetworkInterfaceAttribute' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: ModifyNetworkInterfaceAttribute
s@ModifyNetworkInterfaceAttribute' {} Maybe Bool
a -> ModifyNetworkInterfaceAttribute
s {$sel:dryRun:ModifyNetworkInterfaceAttribute' :: Maybe Bool
dryRun = Maybe Bool
a} :: ModifyNetworkInterfaceAttribute)

-- | Updates the ENA Express configuration for the network interface that’s
-- attached to the instance.
modifyNetworkInterfaceAttribute_enaSrdSpecification :: Lens.Lens' ModifyNetworkInterfaceAttribute (Prelude.Maybe EnaSrdSpecification)
modifyNetworkInterfaceAttribute_enaSrdSpecification :: Lens' ModifyNetworkInterfaceAttribute (Maybe EnaSrdSpecification)
modifyNetworkInterfaceAttribute_enaSrdSpecification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyNetworkInterfaceAttribute' {Maybe EnaSrdSpecification
enaSrdSpecification :: Maybe EnaSrdSpecification
$sel:enaSrdSpecification:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe EnaSrdSpecification
enaSrdSpecification} -> Maybe EnaSrdSpecification
enaSrdSpecification) (\s :: ModifyNetworkInterfaceAttribute
s@ModifyNetworkInterfaceAttribute' {} Maybe EnaSrdSpecification
a -> ModifyNetworkInterfaceAttribute
s {$sel:enaSrdSpecification:ModifyNetworkInterfaceAttribute' :: Maybe EnaSrdSpecification
enaSrdSpecification = Maybe EnaSrdSpecification
a} :: ModifyNetworkInterfaceAttribute)

-- | Changes the security groups for the network interface. The new set of
-- groups you specify replaces the current set. You must specify at least
-- one group, even if it\'s just the default security group in the VPC. You
-- must specify the ID of the security group, not the name.
modifyNetworkInterfaceAttribute_groups :: Lens.Lens' ModifyNetworkInterfaceAttribute (Prelude.Maybe [Prelude.Text])
modifyNetworkInterfaceAttribute_groups :: Lens' ModifyNetworkInterfaceAttribute (Maybe [Text])
modifyNetworkInterfaceAttribute_groups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyNetworkInterfaceAttribute' {Maybe [Text]
groups :: Maybe [Text]
$sel:groups:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe [Text]
groups} -> Maybe [Text]
groups) (\s :: ModifyNetworkInterfaceAttribute
s@ModifyNetworkInterfaceAttribute' {} Maybe [Text]
a -> ModifyNetworkInterfaceAttribute
s {$sel:groups:ModifyNetworkInterfaceAttribute' :: Maybe [Text]
groups = Maybe [Text]
a} :: ModifyNetworkInterfaceAttribute) 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

-- | Enable or disable source\/destination checks, which ensure that the
-- instance is either the source or the destination of any traffic that it
-- receives. If the value is @true@, source\/destination checks are
-- enabled; otherwise, they are disabled. The default value is @true@. You
-- must disable source\/destination checks if the instance runs services
-- such as network address translation, routing, or firewalls.
modifyNetworkInterfaceAttribute_sourceDestCheck :: Lens.Lens' ModifyNetworkInterfaceAttribute (Prelude.Maybe AttributeBooleanValue)
modifyNetworkInterfaceAttribute_sourceDestCheck :: Lens' ModifyNetworkInterfaceAttribute (Maybe AttributeBooleanValue)
modifyNetworkInterfaceAttribute_sourceDestCheck = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyNetworkInterfaceAttribute' {Maybe AttributeBooleanValue
sourceDestCheck :: Maybe AttributeBooleanValue
$sel:sourceDestCheck:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe AttributeBooleanValue
sourceDestCheck} -> Maybe AttributeBooleanValue
sourceDestCheck) (\s :: ModifyNetworkInterfaceAttribute
s@ModifyNetworkInterfaceAttribute' {} Maybe AttributeBooleanValue
a -> ModifyNetworkInterfaceAttribute
s {$sel:sourceDestCheck:ModifyNetworkInterfaceAttribute' :: Maybe AttributeBooleanValue
sourceDestCheck = Maybe AttributeBooleanValue
a} :: ModifyNetworkInterfaceAttribute)

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

instance
  Core.AWSRequest
    ModifyNetworkInterfaceAttribute
  where
  type
    AWSResponse ModifyNetworkInterfaceAttribute =
      ModifyNetworkInterfaceAttributeResponse
  request :: (Service -> Service)
-> ModifyNetworkInterfaceAttribute
-> Request ModifyNetworkInterfaceAttribute
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 ModifyNetworkInterfaceAttribute
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse ModifyNetworkInterfaceAttribute)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      ModifyNetworkInterfaceAttributeResponse
ModifyNetworkInterfaceAttributeResponse'

instance
  Prelude.Hashable
    ModifyNetworkInterfaceAttribute
  where
  hashWithSalt :: Int -> ModifyNetworkInterfaceAttribute -> Int
hashWithSalt
    Int
_salt
    ModifyNetworkInterfaceAttribute' {Maybe Bool
Maybe [Text]
Maybe AttributeBooleanValue
Maybe AttributeValue
Maybe EnaSrdSpecification
Maybe NetworkInterfaceAttachmentChanges
Text
networkInterfaceId :: Text
sourceDestCheck :: Maybe AttributeBooleanValue
groups :: Maybe [Text]
enaSrdSpecification :: Maybe EnaSrdSpecification
dryRun :: Maybe Bool
description :: Maybe AttributeValue
attachment :: Maybe NetworkInterfaceAttachmentChanges
$sel:networkInterfaceId:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Text
$sel:sourceDestCheck:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe AttributeBooleanValue
$sel:groups:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe [Text]
$sel:enaSrdSpecification:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe EnaSrdSpecification
$sel:dryRun:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe Bool
$sel:description:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe AttributeValue
$sel:attachment:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute
-> Maybe NetworkInterfaceAttachmentChanges
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NetworkInterfaceAttachmentChanges
attachment
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AttributeValue
description
        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 [Text]
groups
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AttributeBooleanValue
sourceDestCheck
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
networkInterfaceId

instance
  Prelude.NFData
    ModifyNetworkInterfaceAttribute
  where
  rnf :: ModifyNetworkInterfaceAttribute -> ()
rnf ModifyNetworkInterfaceAttribute' {Maybe Bool
Maybe [Text]
Maybe AttributeBooleanValue
Maybe AttributeValue
Maybe EnaSrdSpecification
Maybe NetworkInterfaceAttachmentChanges
Text
networkInterfaceId :: Text
sourceDestCheck :: Maybe AttributeBooleanValue
groups :: Maybe [Text]
enaSrdSpecification :: Maybe EnaSrdSpecification
dryRun :: Maybe Bool
description :: Maybe AttributeValue
attachment :: Maybe NetworkInterfaceAttachmentChanges
$sel:networkInterfaceId:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Text
$sel:sourceDestCheck:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe AttributeBooleanValue
$sel:groups:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe [Text]
$sel:enaSrdSpecification:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe EnaSrdSpecification
$sel:dryRun:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe Bool
$sel:description:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe AttributeValue
$sel:attachment:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute
-> Maybe NetworkInterfaceAttachmentChanges
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe NetworkInterfaceAttachmentChanges
attachment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AttributeValue
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 [Text]
groups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AttributeBooleanValue
sourceDestCheck
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
networkInterfaceId

instance
  Data.ToHeaders
    ModifyNetworkInterfaceAttribute
  where
  toHeaders :: ModifyNetworkInterfaceAttribute -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery ModifyNetworkInterfaceAttribute where
  toQuery :: ModifyNetworkInterfaceAttribute -> QueryString
toQuery ModifyNetworkInterfaceAttribute' {Maybe Bool
Maybe [Text]
Maybe AttributeBooleanValue
Maybe AttributeValue
Maybe EnaSrdSpecification
Maybe NetworkInterfaceAttachmentChanges
Text
networkInterfaceId :: Text
sourceDestCheck :: Maybe AttributeBooleanValue
groups :: Maybe [Text]
enaSrdSpecification :: Maybe EnaSrdSpecification
dryRun :: Maybe Bool
description :: Maybe AttributeValue
attachment :: Maybe NetworkInterfaceAttachmentChanges
$sel:networkInterfaceId:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Text
$sel:sourceDestCheck:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe AttributeBooleanValue
$sel:groups:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe [Text]
$sel:enaSrdSpecification:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe EnaSrdSpecification
$sel:dryRun:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe Bool
$sel:description:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute -> Maybe AttributeValue
$sel:attachment:ModifyNetworkInterfaceAttribute' :: ModifyNetworkInterfaceAttribute
-> Maybe NetworkInterfaceAttachmentChanges
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"ModifyNetworkInterfaceAttribute" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"Attachment" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe NetworkInterfaceAttachmentChanges
attachment,
        ByteString
"Description" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe AttributeValue
description,
        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,
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"SecurityGroupId"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
groups
          ),
        ByteString
"SourceDestCheck" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe AttributeBooleanValue
sourceDestCheck,
        ByteString
"NetworkInterfaceId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
networkInterfaceId
      ]

-- | /See:/ 'newModifyNetworkInterfaceAttributeResponse' smart constructor.
data ModifyNetworkInterfaceAttributeResponse = ModifyNetworkInterfaceAttributeResponse'
  {
  }
  deriving (ModifyNetworkInterfaceAttributeResponse
-> ModifyNetworkInterfaceAttributeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifyNetworkInterfaceAttributeResponse
-> ModifyNetworkInterfaceAttributeResponse -> Bool
$c/= :: ModifyNetworkInterfaceAttributeResponse
-> ModifyNetworkInterfaceAttributeResponse -> Bool
== :: ModifyNetworkInterfaceAttributeResponse
-> ModifyNetworkInterfaceAttributeResponse -> Bool
$c== :: ModifyNetworkInterfaceAttributeResponse
-> ModifyNetworkInterfaceAttributeResponse -> Bool
Prelude.Eq, ReadPrec [ModifyNetworkInterfaceAttributeResponse]
ReadPrec ModifyNetworkInterfaceAttributeResponse
Int -> ReadS ModifyNetworkInterfaceAttributeResponse
ReadS [ModifyNetworkInterfaceAttributeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifyNetworkInterfaceAttributeResponse]
$creadListPrec :: ReadPrec [ModifyNetworkInterfaceAttributeResponse]
readPrec :: ReadPrec ModifyNetworkInterfaceAttributeResponse
$creadPrec :: ReadPrec ModifyNetworkInterfaceAttributeResponse
readList :: ReadS [ModifyNetworkInterfaceAttributeResponse]
$creadList :: ReadS [ModifyNetworkInterfaceAttributeResponse]
readsPrec :: Int -> ReadS ModifyNetworkInterfaceAttributeResponse
$creadsPrec :: Int -> ReadS ModifyNetworkInterfaceAttributeResponse
Prelude.Read, Int -> ModifyNetworkInterfaceAttributeResponse -> ShowS
[ModifyNetworkInterfaceAttributeResponse] -> ShowS
ModifyNetworkInterfaceAttributeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifyNetworkInterfaceAttributeResponse] -> ShowS
$cshowList :: [ModifyNetworkInterfaceAttributeResponse] -> ShowS
show :: ModifyNetworkInterfaceAttributeResponse -> String
$cshow :: ModifyNetworkInterfaceAttributeResponse -> String
showsPrec :: Int -> ModifyNetworkInterfaceAttributeResponse -> ShowS
$cshowsPrec :: Int -> ModifyNetworkInterfaceAttributeResponse -> ShowS
Prelude.Show, forall x.
Rep ModifyNetworkInterfaceAttributeResponse x
-> ModifyNetworkInterfaceAttributeResponse
forall x.
ModifyNetworkInterfaceAttributeResponse
-> Rep ModifyNetworkInterfaceAttributeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ModifyNetworkInterfaceAttributeResponse x
-> ModifyNetworkInterfaceAttributeResponse
$cfrom :: forall x.
ModifyNetworkInterfaceAttributeResponse
-> Rep ModifyNetworkInterfaceAttributeResponse x
Prelude.Generic)

-- |
-- Create a value of 'ModifyNetworkInterfaceAttributeResponse' 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.
newModifyNetworkInterfaceAttributeResponse ::
  ModifyNetworkInterfaceAttributeResponse
newModifyNetworkInterfaceAttributeResponse :: ModifyNetworkInterfaceAttributeResponse
newModifyNetworkInterfaceAttributeResponse =
  ModifyNetworkInterfaceAttributeResponse
ModifyNetworkInterfaceAttributeResponse'

instance
  Prelude.NFData
    ModifyNetworkInterfaceAttributeResponse
  where
  rnf :: ModifyNetworkInterfaceAttributeResponse -> ()
rnf ModifyNetworkInterfaceAttributeResponse
_ = ()