{-# 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.DisableVgwRoutePropagation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Disables a virtual private gateway (VGW) from propagating routes to a
-- specified route table of a VPC.
module Amazonka.EC2.DisableVgwRoutePropagation
  ( -- * Creating a Request
    DisableVgwRoutePropagation (..),
    newDisableVgwRoutePropagation,

    -- * Request Lenses
    disableVgwRoutePropagation_dryRun,
    disableVgwRoutePropagation_gatewayId,
    disableVgwRoutePropagation_routeTableId,

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

-- |
-- Create a value of 'DisableVgwRoutePropagation' 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', 'disableVgwRoutePropagation_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@.
--
-- 'gatewayId', 'disableVgwRoutePropagation_gatewayId' - The ID of the virtual private gateway.
--
-- 'routeTableId', 'disableVgwRoutePropagation_routeTableId' - The ID of the route table.
newDisableVgwRoutePropagation ::
  -- | 'gatewayId'
  Prelude.Text ->
  -- | 'routeTableId'
  Prelude.Text ->
  DisableVgwRoutePropagation
newDisableVgwRoutePropagation :: Text -> Text -> DisableVgwRoutePropagation
newDisableVgwRoutePropagation
  Text
pGatewayId_
  Text
pRouteTableId_ =
    DisableVgwRoutePropagation'
      { $sel:dryRun:DisableVgwRoutePropagation' :: Maybe Bool
dryRun =
          forall a. Maybe a
Prelude.Nothing,
        $sel:gatewayId:DisableVgwRoutePropagation' :: Text
gatewayId = Text
pGatewayId_,
        $sel:routeTableId:DisableVgwRoutePropagation' :: Text
routeTableId = Text
pRouteTableId_
      }

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

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

-- | The ID of the route table.
disableVgwRoutePropagation_routeTableId :: Lens.Lens' DisableVgwRoutePropagation Prelude.Text
disableVgwRoutePropagation_routeTableId :: Lens' DisableVgwRoutePropagation Text
disableVgwRoutePropagation_routeTableId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisableVgwRoutePropagation' {Text
routeTableId :: Text
$sel:routeTableId:DisableVgwRoutePropagation' :: DisableVgwRoutePropagation -> Text
routeTableId} -> Text
routeTableId) (\s :: DisableVgwRoutePropagation
s@DisableVgwRoutePropagation' {} Text
a -> DisableVgwRoutePropagation
s {$sel:routeTableId:DisableVgwRoutePropagation' :: Text
routeTableId = Text
a} :: DisableVgwRoutePropagation)

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

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

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

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

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

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

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

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

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