{-# 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.AttachInternetGateway
-- 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 an internet gateway or a virtual private gateway to a VPC,
-- enabling connectivity between the internet and the VPC. For more
-- information about your VPC and internet gateway, see the
-- <https://docs.aws.amazon.com/vpc/latest/userguide/ Amazon Virtual Private Cloud User Guide>.
module Amazonka.EC2.AttachInternetGateway
  ( -- * Creating a Request
    AttachInternetGateway (..),
    newAttachInternetGateway,

    -- * Request Lenses
    attachInternetGateway_dryRun,
    attachInternetGateway_internetGatewayId,
    attachInternetGateway_vpcId,

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

-- |
-- Create a value of 'AttachInternetGateway' 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', 'attachInternetGateway_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', 'attachInternetGateway_internetGatewayId' - The ID of the internet gateway.
--
-- 'vpcId', 'attachInternetGateway_vpcId' - The ID of the VPC.
newAttachInternetGateway ::
  -- | 'internetGatewayId'
  Prelude.Text ->
  -- | 'vpcId'
  Prelude.Text ->
  AttachInternetGateway
newAttachInternetGateway :: Text -> Text -> AttachInternetGateway
newAttachInternetGateway Text
pInternetGatewayId_ Text
pVpcId_ =
  AttachInternetGateway'
    { $sel:dryRun:AttachInternetGateway' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:internetGatewayId:AttachInternetGateway' :: Text
internetGatewayId = Text
pInternetGatewayId_,
      $sel:vpcId:AttachInternetGateway' :: 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@.
attachInternetGateway_dryRun :: Lens.Lens' AttachInternetGateway (Prelude.Maybe Prelude.Bool)
attachInternetGateway_dryRun :: Lens' AttachInternetGateway (Maybe Bool)
attachInternetGateway_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachInternetGateway' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:AttachInternetGateway' :: AttachInternetGateway -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: AttachInternetGateway
s@AttachInternetGateway' {} Maybe Bool
a -> AttachInternetGateway
s {$sel:dryRun:AttachInternetGateway' :: Maybe Bool
dryRun = Maybe Bool
a} :: AttachInternetGateway)

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

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

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

instance Prelude.Hashable AttachInternetGateway where
  hashWithSalt :: Int -> AttachInternetGateway -> Int
hashWithSalt Int
_salt AttachInternetGateway' {Maybe Bool
Text
vpcId :: Text
internetGatewayId :: Text
dryRun :: Maybe Bool
$sel:vpcId:AttachInternetGateway' :: AttachInternetGateway -> Text
$sel:internetGatewayId:AttachInternetGateway' :: AttachInternetGateway -> Text
$sel:dryRun:AttachInternetGateway' :: AttachInternetGateway -> 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 AttachInternetGateway where
  rnf :: AttachInternetGateway -> ()
rnf AttachInternetGateway' {Maybe Bool
Text
vpcId :: Text
internetGatewayId :: Text
dryRun :: Maybe Bool
$sel:vpcId:AttachInternetGateway' :: AttachInternetGateway -> Text
$sel:internetGatewayId:AttachInternetGateway' :: AttachInternetGateway -> Text
$sel:dryRun:AttachInternetGateway' :: AttachInternetGateway -> 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 AttachInternetGateway where
  toHeaders :: AttachInternetGateway -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery AttachInternetGateway where
  toQuery :: AttachInternetGateway -> QueryString
toQuery AttachInternetGateway' {Maybe Bool
Text
vpcId :: Text
internetGatewayId :: Text
dryRun :: Maybe Bool
$sel:vpcId:AttachInternetGateway' :: AttachInternetGateway -> Text
$sel:internetGatewayId:AttachInternetGateway' :: AttachInternetGateway -> Text
$sel:dryRun:AttachInternetGateway' :: AttachInternetGateway -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"AttachInternetGateway" :: 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:/ 'newAttachInternetGatewayResponse' smart constructor.
data AttachInternetGatewayResponse = AttachInternetGatewayResponse'
  {
  }
  deriving (AttachInternetGatewayResponse
-> AttachInternetGatewayResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachInternetGatewayResponse
-> AttachInternetGatewayResponse -> Bool
$c/= :: AttachInternetGatewayResponse
-> AttachInternetGatewayResponse -> Bool
== :: AttachInternetGatewayResponse
-> AttachInternetGatewayResponse -> Bool
$c== :: AttachInternetGatewayResponse
-> AttachInternetGatewayResponse -> Bool
Prelude.Eq, ReadPrec [AttachInternetGatewayResponse]
ReadPrec AttachInternetGatewayResponse
Int -> ReadS AttachInternetGatewayResponse
ReadS [AttachInternetGatewayResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttachInternetGatewayResponse]
$creadListPrec :: ReadPrec [AttachInternetGatewayResponse]
readPrec :: ReadPrec AttachInternetGatewayResponse
$creadPrec :: ReadPrec AttachInternetGatewayResponse
readList :: ReadS [AttachInternetGatewayResponse]
$creadList :: ReadS [AttachInternetGatewayResponse]
readsPrec :: Int -> ReadS AttachInternetGatewayResponse
$creadsPrec :: Int -> ReadS AttachInternetGatewayResponse
Prelude.Read, Int -> AttachInternetGatewayResponse -> ShowS
[AttachInternetGatewayResponse] -> ShowS
AttachInternetGatewayResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachInternetGatewayResponse] -> ShowS
$cshowList :: [AttachInternetGatewayResponse] -> ShowS
show :: AttachInternetGatewayResponse -> String
$cshow :: AttachInternetGatewayResponse -> String
showsPrec :: Int -> AttachInternetGatewayResponse -> ShowS
$cshowsPrec :: Int -> AttachInternetGatewayResponse -> ShowS
Prelude.Show, forall x.
Rep AttachInternetGatewayResponse x
-> AttachInternetGatewayResponse
forall x.
AttachInternetGatewayResponse
-> Rep AttachInternetGatewayResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AttachInternetGatewayResponse x
-> AttachInternetGatewayResponse
$cfrom :: forall x.
AttachInternetGatewayResponse
-> Rep AttachInternetGatewayResponse x
Prelude.Generic)

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

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