{-# 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.DeleteNetworkInterface
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes the specified network interface. You must detach the network
-- interface before you can delete it.
module Amazonka.EC2.DeleteNetworkInterface
  ( -- * Creating a Request
    DeleteNetworkInterface (..),
    newDeleteNetworkInterface,

    -- * Request Lenses
    deleteNetworkInterface_dryRun,
    deleteNetworkInterface_networkInterfaceId,

    -- * Destructuring the Response
    DeleteNetworkInterfaceResponse (..),
    newDeleteNetworkInterfaceResponse,
  )
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 DeleteNetworkInterface.
--
-- /See:/ 'newDeleteNetworkInterface' smart constructor.
data DeleteNetworkInterface = DeleteNetworkInterface'
  { -- | 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@.
    DeleteNetworkInterface -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the network interface.
    DeleteNetworkInterface -> Text
networkInterfaceId :: Prelude.Text
  }
  deriving (DeleteNetworkInterface -> DeleteNetworkInterface -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteNetworkInterface -> DeleteNetworkInterface -> Bool
$c/= :: DeleteNetworkInterface -> DeleteNetworkInterface -> Bool
== :: DeleteNetworkInterface -> DeleteNetworkInterface -> Bool
$c== :: DeleteNetworkInterface -> DeleteNetworkInterface -> Bool
Prelude.Eq, ReadPrec [DeleteNetworkInterface]
ReadPrec DeleteNetworkInterface
Int -> ReadS DeleteNetworkInterface
ReadS [DeleteNetworkInterface]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteNetworkInterface]
$creadListPrec :: ReadPrec [DeleteNetworkInterface]
readPrec :: ReadPrec DeleteNetworkInterface
$creadPrec :: ReadPrec DeleteNetworkInterface
readList :: ReadS [DeleteNetworkInterface]
$creadList :: ReadS [DeleteNetworkInterface]
readsPrec :: Int -> ReadS DeleteNetworkInterface
$creadsPrec :: Int -> ReadS DeleteNetworkInterface
Prelude.Read, Int -> DeleteNetworkInterface -> ShowS
[DeleteNetworkInterface] -> ShowS
DeleteNetworkInterface -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteNetworkInterface] -> ShowS
$cshowList :: [DeleteNetworkInterface] -> ShowS
show :: DeleteNetworkInterface -> String
$cshow :: DeleteNetworkInterface -> String
showsPrec :: Int -> DeleteNetworkInterface -> ShowS
$cshowsPrec :: Int -> DeleteNetworkInterface -> ShowS
Prelude.Show, forall x. Rep DeleteNetworkInterface x -> DeleteNetworkInterface
forall x. DeleteNetworkInterface -> Rep DeleteNetworkInterface x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteNetworkInterface x -> DeleteNetworkInterface
$cfrom :: forall x. DeleteNetworkInterface -> Rep DeleteNetworkInterface x
Prelude.Generic)

-- |
-- Create a value of 'DeleteNetworkInterface' 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', 'deleteNetworkInterface_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@.
--
-- 'networkInterfaceId', 'deleteNetworkInterface_networkInterfaceId' - The ID of the network interface.
newDeleteNetworkInterface ::
  -- | 'networkInterfaceId'
  Prelude.Text ->
  DeleteNetworkInterface
newDeleteNetworkInterface :: Text -> DeleteNetworkInterface
newDeleteNetworkInterface Text
pNetworkInterfaceId_ =
  DeleteNetworkInterface'
    { $sel:dryRun:DeleteNetworkInterface' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:networkInterfaceId:DeleteNetworkInterface' :: 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@.
deleteNetworkInterface_dryRun :: Lens.Lens' DeleteNetworkInterface (Prelude.Maybe Prelude.Bool)
deleteNetworkInterface_dryRun :: Lens' DeleteNetworkInterface (Maybe Bool)
deleteNetworkInterface_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteNetworkInterface' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DeleteNetworkInterface' :: DeleteNetworkInterface -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: DeleteNetworkInterface
s@DeleteNetworkInterface' {} Maybe Bool
a -> DeleteNetworkInterface
s {$sel:dryRun:DeleteNetworkInterface' :: Maybe Bool
dryRun = Maybe Bool
a} :: DeleteNetworkInterface)

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

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

instance Prelude.Hashable DeleteNetworkInterface where
  hashWithSalt :: Int -> DeleteNetworkInterface -> Int
hashWithSalt Int
_salt DeleteNetworkInterface' {Maybe Bool
Text
networkInterfaceId :: Text
dryRun :: Maybe Bool
$sel:networkInterfaceId:DeleteNetworkInterface' :: DeleteNetworkInterface -> Text
$sel:dryRun:DeleteNetworkInterface' :: DeleteNetworkInterface -> 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` Text
networkInterfaceId

instance Prelude.NFData DeleteNetworkInterface where
  rnf :: DeleteNetworkInterface -> ()
rnf DeleteNetworkInterface' {Maybe Bool
Text
networkInterfaceId :: Text
dryRun :: Maybe Bool
$sel:networkInterfaceId:DeleteNetworkInterface' :: DeleteNetworkInterface -> Text
$sel:dryRun:DeleteNetworkInterface' :: DeleteNetworkInterface -> 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 Text
networkInterfaceId

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

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

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

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

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

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