{-# 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.AttachVpnGateway
-- 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 a virtual private gateway to a VPC. You can attach one virtual
-- private gateway to one VPC at a time.
--
-- For more information, see
-- <https://docs.aws.amazon.com/vpn/latest/s2svpn/VPC_VPN.html Amazon Web Services Site-to-Site VPN>
-- in the /Amazon Web Services Site-to-Site VPN User Guide/.
module Amazonka.EC2.AttachVpnGateway
  ( -- * Creating a Request
    AttachVpnGateway (..),
    newAttachVpnGateway,

    -- * Request Lenses
    attachVpnGateway_dryRun,
    attachVpnGateway_vpcId,
    attachVpnGateway_vpnGatewayId,

    -- * Destructuring the Response
    AttachVpnGatewayResponse (..),
    newAttachVpnGatewayResponse,

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

-- |
-- Create a value of 'AttachVpnGateway' 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', 'attachVpnGateway_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@.
--
-- 'vpcId', 'attachVpnGateway_vpcId' - The ID of the VPC.
--
-- 'vpnGatewayId', 'attachVpnGateway_vpnGatewayId' - The ID of the virtual private gateway.
newAttachVpnGateway ::
  -- | 'vpcId'
  Prelude.Text ->
  -- | 'vpnGatewayId'
  Prelude.Text ->
  AttachVpnGateway
newAttachVpnGateway :: Text -> Text -> AttachVpnGateway
newAttachVpnGateway Text
pVpcId_ Text
pVpnGatewayId_ =
  AttachVpnGateway'
    { $sel:dryRun:AttachVpnGateway' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:AttachVpnGateway' :: Text
vpcId = Text
pVpcId_,
      $sel:vpnGatewayId:AttachVpnGateway' :: Text
vpnGatewayId = Text
pVpnGatewayId_
    }

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

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

-- | The ID of the virtual private gateway.
attachVpnGateway_vpnGatewayId :: Lens.Lens' AttachVpnGateway Prelude.Text
attachVpnGateway_vpnGatewayId :: Lens' AttachVpnGateway Text
attachVpnGateway_vpnGatewayId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachVpnGateway' {Text
vpnGatewayId :: Text
$sel:vpnGatewayId:AttachVpnGateway' :: AttachVpnGateway -> Text
vpnGatewayId} -> Text
vpnGatewayId) (\s :: AttachVpnGateway
s@AttachVpnGateway' {} Text
a -> AttachVpnGateway
s {$sel:vpnGatewayId:AttachVpnGateway' :: Text
vpnGatewayId = Text
a} :: AttachVpnGateway)

instance Core.AWSRequest AttachVpnGateway where
  type
    AWSResponse AttachVpnGateway =
      AttachVpnGatewayResponse
  request :: (Service -> Service)
-> AttachVpnGateway -> Request AttachVpnGateway
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 AttachVpnGateway
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse AttachVpnGateway)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe VpcAttachment -> Int -> AttachVpnGatewayResponse
AttachVpnGatewayResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"attachment")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

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

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

instance Data.ToHeaders AttachVpnGateway where
  toHeaders :: AttachVpnGateway -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

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

-- | Contains the output of AttachVpnGateway.
--
-- /See:/ 'newAttachVpnGatewayResponse' smart constructor.
data AttachVpnGatewayResponse = AttachVpnGatewayResponse'
  { -- | Information about the attachment.
    AttachVpnGatewayResponse -> Maybe VpcAttachment
vpcAttachment :: Prelude.Maybe VpcAttachment,
    -- | The response's http status code.
    AttachVpnGatewayResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (AttachVpnGatewayResponse -> AttachVpnGatewayResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachVpnGatewayResponse -> AttachVpnGatewayResponse -> Bool
$c/= :: AttachVpnGatewayResponse -> AttachVpnGatewayResponse -> Bool
== :: AttachVpnGatewayResponse -> AttachVpnGatewayResponse -> Bool
$c== :: AttachVpnGatewayResponse -> AttachVpnGatewayResponse -> Bool
Prelude.Eq, ReadPrec [AttachVpnGatewayResponse]
ReadPrec AttachVpnGatewayResponse
Int -> ReadS AttachVpnGatewayResponse
ReadS [AttachVpnGatewayResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttachVpnGatewayResponse]
$creadListPrec :: ReadPrec [AttachVpnGatewayResponse]
readPrec :: ReadPrec AttachVpnGatewayResponse
$creadPrec :: ReadPrec AttachVpnGatewayResponse
readList :: ReadS [AttachVpnGatewayResponse]
$creadList :: ReadS [AttachVpnGatewayResponse]
readsPrec :: Int -> ReadS AttachVpnGatewayResponse
$creadsPrec :: Int -> ReadS AttachVpnGatewayResponse
Prelude.Read, Int -> AttachVpnGatewayResponse -> ShowS
[AttachVpnGatewayResponse] -> ShowS
AttachVpnGatewayResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachVpnGatewayResponse] -> ShowS
$cshowList :: [AttachVpnGatewayResponse] -> ShowS
show :: AttachVpnGatewayResponse -> String
$cshow :: AttachVpnGatewayResponse -> String
showsPrec :: Int -> AttachVpnGatewayResponse -> ShowS
$cshowsPrec :: Int -> AttachVpnGatewayResponse -> ShowS
Prelude.Show, forall x.
Rep AttachVpnGatewayResponse x -> AttachVpnGatewayResponse
forall x.
AttachVpnGatewayResponse -> Rep AttachVpnGatewayResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AttachVpnGatewayResponse x -> AttachVpnGatewayResponse
$cfrom :: forall x.
AttachVpnGatewayResponse -> Rep AttachVpnGatewayResponse x
Prelude.Generic)

-- |
-- Create a value of 'AttachVpnGatewayResponse' 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:
--
-- 'vpcAttachment', 'attachVpnGatewayResponse_vpcAttachment' - Information about the attachment.
--
-- 'httpStatus', 'attachVpnGatewayResponse_httpStatus' - The response's http status code.
newAttachVpnGatewayResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AttachVpnGatewayResponse
newAttachVpnGatewayResponse :: Int -> AttachVpnGatewayResponse
newAttachVpnGatewayResponse Int
pHttpStatus_ =
  AttachVpnGatewayResponse'
    { $sel:vpcAttachment:AttachVpnGatewayResponse' :: Maybe VpcAttachment
vpcAttachment =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:AttachVpnGatewayResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the attachment.
attachVpnGatewayResponse_vpcAttachment :: Lens.Lens' AttachVpnGatewayResponse (Prelude.Maybe VpcAttachment)
attachVpnGatewayResponse_vpcAttachment :: Lens' AttachVpnGatewayResponse (Maybe VpcAttachment)
attachVpnGatewayResponse_vpcAttachment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachVpnGatewayResponse' {Maybe VpcAttachment
vpcAttachment :: Maybe VpcAttachment
$sel:vpcAttachment:AttachVpnGatewayResponse' :: AttachVpnGatewayResponse -> Maybe VpcAttachment
vpcAttachment} -> Maybe VpcAttachment
vpcAttachment) (\s :: AttachVpnGatewayResponse
s@AttachVpnGatewayResponse' {} Maybe VpcAttachment
a -> AttachVpnGatewayResponse
s {$sel:vpcAttachment:AttachVpnGatewayResponse' :: Maybe VpcAttachment
vpcAttachment = Maybe VpcAttachment
a} :: AttachVpnGatewayResponse)

-- | The response's http status code.
attachVpnGatewayResponse_httpStatus :: Lens.Lens' AttachVpnGatewayResponse Prelude.Int
attachVpnGatewayResponse_httpStatus :: Lens' AttachVpnGatewayResponse Int
attachVpnGatewayResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachVpnGatewayResponse' {Int
httpStatus :: Int
$sel:httpStatus:AttachVpnGatewayResponse' :: AttachVpnGatewayResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: AttachVpnGatewayResponse
s@AttachVpnGatewayResponse' {} Int
a -> AttachVpnGatewayResponse
s {$sel:httpStatus:AttachVpnGatewayResponse' :: Int
httpStatus = Int
a} :: AttachVpnGatewayResponse)

instance Prelude.NFData AttachVpnGatewayResponse where
  rnf :: AttachVpnGatewayResponse -> ()
rnf AttachVpnGatewayResponse' {Int
Maybe VpcAttachment
httpStatus :: Int
vpcAttachment :: Maybe VpcAttachment
$sel:httpStatus:AttachVpnGatewayResponse' :: AttachVpnGatewayResponse -> Int
$sel:vpcAttachment:AttachVpnGatewayResponse' :: AttachVpnGatewayResponse -> Maybe VpcAttachment
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe VpcAttachment
vpcAttachment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus