{-# 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.DetachInternetGateway
-- 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 an internet gateway from a VPC, disabling connectivity between
-- the internet and the VPC. The VPC must not contain any running instances
-- with Elastic IP addresses or public IPv4 addresses.
module Amazonka.EC2.DetachInternetGateway
  ( -- * Creating a Request
    DetachInternetGateway (..),
    newDetachInternetGateway,

    -- * Request Lenses
    detachInternetGateway_dryRun,
    detachInternetGateway_internetGatewayId,
    detachInternetGateway_vpcId,

    -- * Destructuring the Response
    DetachInternetGatewayResponse (..),
    newDetachInternetGatewayResponse,
  )
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

-- | /See:/ 'newDetachInternetGateway' smart constructor.
data DetachInternetGateway = DetachInternetGateway'
  { -- | 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@.
    DetachInternetGateway -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the internet gateway.
    DetachInternetGateway -> Text
internetGatewayId :: Prelude.Text,
    -- | The ID of the VPC.
    DetachInternetGateway -> Text
vpcId :: Prelude.Text
  }
  deriving (DetachInternetGateway -> DetachInternetGateway -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DetachInternetGateway -> DetachInternetGateway -> Bool
$c/= :: DetachInternetGateway -> DetachInternetGateway -> Bool
== :: DetachInternetGateway -> DetachInternetGateway -> Bool
$c== :: DetachInternetGateway -> DetachInternetGateway -> Bool
Prelude.Eq, ReadPrec [DetachInternetGateway]
ReadPrec DetachInternetGateway
Int -> ReadS DetachInternetGateway
ReadS [DetachInternetGateway]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DetachInternetGateway]
$creadListPrec :: ReadPrec [DetachInternetGateway]
readPrec :: ReadPrec DetachInternetGateway
$creadPrec :: ReadPrec DetachInternetGateway
readList :: ReadS [DetachInternetGateway]
$creadList :: ReadS [DetachInternetGateway]
readsPrec :: Int -> ReadS DetachInternetGateway
$creadsPrec :: Int -> ReadS DetachInternetGateway
Prelude.Read, Int -> DetachInternetGateway -> ShowS
[DetachInternetGateway] -> ShowS
DetachInternetGateway -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DetachInternetGateway] -> ShowS
$cshowList :: [DetachInternetGateway] -> ShowS
show :: DetachInternetGateway -> String
$cshow :: DetachInternetGateway -> String
showsPrec :: Int -> DetachInternetGateway -> ShowS
$cshowsPrec :: Int -> DetachInternetGateway -> ShowS
Prelude.Show, forall x. Rep DetachInternetGateway x -> DetachInternetGateway
forall x. DetachInternetGateway -> Rep DetachInternetGateway x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DetachInternetGateway x -> DetachInternetGateway
$cfrom :: forall x. DetachInternetGateway -> Rep DetachInternetGateway x
Prelude.Generic)

-- |
-- Create a value of 'DetachInternetGateway' 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', 'detachInternetGateway_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@.
--
-- 'internetGatewayId', 'detachInternetGateway_internetGatewayId' - The ID of the internet gateway.
--
-- 'vpcId', 'detachInternetGateway_vpcId' - The ID of the VPC.
newDetachInternetGateway ::
  -- | 'internetGatewayId'
  Prelude.Text ->
  -- | 'vpcId'
  Prelude.Text ->
  DetachInternetGateway
newDetachInternetGateway :: Text -> Text -> DetachInternetGateway
newDetachInternetGateway Text
pInternetGatewayId_ Text
pVpcId_ =
  DetachInternetGateway'
    { $sel:dryRun:DetachInternetGateway' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:internetGatewayId:DetachInternetGateway' :: Text
internetGatewayId = Text
pInternetGatewayId_,
      $sel:vpcId:DetachInternetGateway' :: Text
vpcId = Text
pVpcId_
    }

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

-- | The ID of the internet gateway.
detachInternetGateway_internetGatewayId :: Lens.Lens' DetachInternetGateway Prelude.Text
detachInternetGateway_internetGatewayId :: Lens' DetachInternetGateway Text
detachInternetGateway_internetGatewayId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachInternetGateway' {Text
internetGatewayId :: Text
$sel:internetGatewayId:DetachInternetGateway' :: DetachInternetGateway -> Text
internetGatewayId} -> Text
internetGatewayId) (\s :: DetachInternetGateway
s@DetachInternetGateway' {} Text
a -> DetachInternetGateway
s {$sel:internetGatewayId:DetachInternetGateway' :: Text
internetGatewayId = Text
a} :: DetachInternetGateway)

-- | The ID of the VPC.
detachInternetGateway_vpcId :: Lens.Lens' DetachInternetGateway Prelude.Text
detachInternetGateway_vpcId :: Lens' DetachInternetGateway Text
detachInternetGateway_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachInternetGateway' {Text
vpcId :: Text
$sel:vpcId:DetachInternetGateway' :: DetachInternetGateway -> Text
vpcId} -> Text
vpcId) (\s :: DetachInternetGateway
s@DetachInternetGateway' {} Text
a -> DetachInternetGateway
s {$sel:vpcId:DetachInternetGateway' :: Text
vpcId = Text
a} :: DetachInternetGateway)

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

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

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

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

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

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

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

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

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