{-# 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.DetachNetworkInterface
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Detaches a network interface from an instance.
module Amazonka.EC2.DetachNetworkInterface
  ( -- * Creating a Request
    DetachNetworkInterface (..),
    newDetachNetworkInterface,

    -- * Request Lenses
    detachNetworkInterface_dryRun,
    detachNetworkInterface_force,
    detachNetworkInterface_attachmentId,

    -- * Destructuring the Response
    DetachNetworkInterfaceResponse (..),
    newDetachNetworkInterfaceResponse,
  )
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 DetachNetworkInterface.
--
-- /See:/ 'newDetachNetworkInterface' smart constructor.
data DetachNetworkInterface = DetachNetworkInterface'
  { -- | 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@.
    DetachNetworkInterface -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | Specifies whether to force a detachment.
    --
    -- -   Use the @Force@ parameter only as a last resort to detach a network
    --     interface from a failed instance.
    --
    -- -   If you use the @Force@ parameter to detach a network interface, you
    --     might not be able to attach a different network interface to the
    --     same index on the instance without first stopping and starting the
    --     instance.
    --
    -- -   If you force the detachment of a network interface, the
    --     <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/ec2-instance-metadata.html instance metadata>
    --     might not get updated. This means that the attributes associated
    --     with the detached network interface might still be visible. The
    --     instance metadata will get updated when you stop and start the
    --     instance.
    DetachNetworkInterface -> Maybe Bool
force :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the attachment.
    DetachNetworkInterface -> Text
attachmentId :: Prelude.Text
  }
  deriving (DetachNetworkInterface -> DetachNetworkInterface -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DetachNetworkInterface -> DetachNetworkInterface -> Bool
$c/= :: DetachNetworkInterface -> DetachNetworkInterface -> Bool
== :: DetachNetworkInterface -> DetachNetworkInterface -> Bool
$c== :: DetachNetworkInterface -> DetachNetworkInterface -> Bool
Prelude.Eq, ReadPrec [DetachNetworkInterface]
ReadPrec DetachNetworkInterface
Int -> ReadS DetachNetworkInterface
ReadS [DetachNetworkInterface]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DetachNetworkInterface]
$creadListPrec :: ReadPrec [DetachNetworkInterface]
readPrec :: ReadPrec DetachNetworkInterface
$creadPrec :: ReadPrec DetachNetworkInterface
readList :: ReadS [DetachNetworkInterface]
$creadList :: ReadS [DetachNetworkInterface]
readsPrec :: Int -> ReadS DetachNetworkInterface
$creadsPrec :: Int -> ReadS DetachNetworkInterface
Prelude.Read, Int -> DetachNetworkInterface -> ShowS
[DetachNetworkInterface] -> ShowS
DetachNetworkInterface -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DetachNetworkInterface] -> ShowS
$cshowList :: [DetachNetworkInterface] -> ShowS
show :: DetachNetworkInterface -> String
$cshow :: DetachNetworkInterface -> String
showsPrec :: Int -> DetachNetworkInterface -> ShowS
$cshowsPrec :: Int -> DetachNetworkInterface -> ShowS
Prelude.Show, forall x. Rep DetachNetworkInterface x -> DetachNetworkInterface
forall x. DetachNetworkInterface -> Rep DetachNetworkInterface x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DetachNetworkInterface x -> DetachNetworkInterface
$cfrom :: forall x. DetachNetworkInterface -> Rep DetachNetworkInterface x
Prelude.Generic)

-- |
-- Create a value of 'DetachNetworkInterface' 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', 'detachNetworkInterface_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@.
--
-- 'force', 'detachNetworkInterface_force' - Specifies whether to force a detachment.
--
-- -   Use the @Force@ parameter only as a last resort to detach a network
--     interface from a failed instance.
--
-- -   If you use the @Force@ parameter to detach a network interface, you
--     might not be able to attach a different network interface to the
--     same index on the instance without first stopping and starting the
--     instance.
--
-- -   If you force the detachment of a network interface, the
--     <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/ec2-instance-metadata.html instance metadata>
--     might not get updated. This means that the attributes associated
--     with the detached network interface might still be visible. The
--     instance metadata will get updated when you stop and start the
--     instance.
--
-- 'attachmentId', 'detachNetworkInterface_attachmentId' - The ID of the attachment.
newDetachNetworkInterface ::
  -- | 'attachmentId'
  Prelude.Text ->
  DetachNetworkInterface
newDetachNetworkInterface :: Text -> DetachNetworkInterface
newDetachNetworkInterface Text
pAttachmentId_ =
  DetachNetworkInterface'
    { $sel:dryRun:DetachNetworkInterface' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:force:DetachNetworkInterface' :: Maybe Bool
force = forall a. Maybe a
Prelude.Nothing,
      $sel:attachmentId:DetachNetworkInterface' :: Text
attachmentId = Text
pAttachmentId_
    }

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

-- | Specifies whether to force a detachment.
--
-- -   Use the @Force@ parameter only as a last resort to detach a network
--     interface from a failed instance.
--
-- -   If you use the @Force@ parameter to detach a network interface, you
--     might not be able to attach a different network interface to the
--     same index on the instance without first stopping and starting the
--     instance.
--
-- -   If you force the detachment of a network interface, the
--     <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/ec2-instance-metadata.html instance metadata>
--     might not get updated. This means that the attributes associated
--     with the detached network interface might still be visible. The
--     instance metadata will get updated when you stop and start the
--     instance.
detachNetworkInterface_force :: Lens.Lens' DetachNetworkInterface (Prelude.Maybe Prelude.Bool)
detachNetworkInterface_force :: Lens' DetachNetworkInterface (Maybe Bool)
detachNetworkInterface_force = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachNetworkInterface' {Maybe Bool
force :: Maybe Bool
$sel:force:DetachNetworkInterface' :: DetachNetworkInterface -> Maybe Bool
force} -> Maybe Bool
force) (\s :: DetachNetworkInterface
s@DetachNetworkInterface' {} Maybe Bool
a -> DetachNetworkInterface
s {$sel:force:DetachNetworkInterface' :: Maybe Bool
force = Maybe Bool
a} :: DetachNetworkInterface)

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

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

instance Prelude.Hashable DetachNetworkInterface where
  hashWithSalt :: Int -> DetachNetworkInterface -> Int
hashWithSalt Int
_salt DetachNetworkInterface' {Maybe Bool
Text
attachmentId :: Text
force :: Maybe Bool
dryRun :: Maybe Bool
$sel:attachmentId:DetachNetworkInterface' :: DetachNetworkInterface -> Text
$sel:force:DetachNetworkInterface' :: DetachNetworkInterface -> Maybe Bool
$sel:dryRun:DetachNetworkInterface' :: DetachNetworkInterface -> 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 Bool
force
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
attachmentId

instance Prelude.NFData DetachNetworkInterface where
  rnf :: DetachNetworkInterface -> ()
rnf DetachNetworkInterface' {Maybe Bool
Text
attachmentId :: Text
force :: Maybe Bool
dryRun :: Maybe Bool
$sel:attachmentId:DetachNetworkInterface' :: DetachNetworkInterface -> Text
$sel:force:DetachNetworkInterface' :: DetachNetworkInterface -> Maybe Bool
$sel:dryRun:DetachNetworkInterface' :: DetachNetworkInterface -> 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 Bool
force
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
attachmentId

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

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

instance Data.ToQuery DetachNetworkInterface where
  toQuery :: DetachNetworkInterface -> QueryString
toQuery DetachNetworkInterface' {Maybe Bool
Text
attachmentId :: Text
force :: Maybe Bool
dryRun :: Maybe Bool
$sel:attachmentId:DetachNetworkInterface' :: DetachNetworkInterface -> Text
$sel:force:DetachNetworkInterface' :: DetachNetworkInterface -> Maybe Bool
$sel:dryRun:DetachNetworkInterface' :: DetachNetworkInterface -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DetachNetworkInterface" :: 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
"Force" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
force,
        ByteString
"AttachmentId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
attachmentId
      ]

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

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

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