{-# 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.DeleteRouteTable
-- 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 route table. You must disassociate the route table
-- from any subnets before you can delete it. You can\'t delete the main
-- route table.
module Amazonka.EC2.DeleteRouteTable
  ( -- * Creating a Request
    DeleteRouteTable (..),
    newDeleteRouteTable,

    -- * Request Lenses
    deleteRouteTable_dryRun,
    deleteRouteTable_routeTableId,

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

-- |
-- Create a value of 'DeleteRouteTable' 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', 'deleteRouteTable_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@.
--
-- 'routeTableId', 'deleteRouteTable_routeTableId' - The ID of the route table.
newDeleteRouteTable ::
  -- | 'routeTableId'
  Prelude.Text ->
  DeleteRouteTable
newDeleteRouteTable :: Text -> DeleteRouteTable
newDeleteRouteTable Text
pRouteTableId_ =
  DeleteRouteTable'
    { $sel:dryRun:DeleteRouteTable' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:routeTableId:DeleteRouteTable' :: 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@.
deleteRouteTable_dryRun :: Lens.Lens' DeleteRouteTable (Prelude.Maybe Prelude.Bool)
deleteRouteTable_dryRun :: Lens' DeleteRouteTable (Maybe Bool)
deleteRouteTable_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRouteTable' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DeleteRouteTable' :: DeleteRouteTable -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: DeleteRouteTable
s@DeleteRouteTable' {} Maybe Bool
a -> DeleteRouteTable
s {$sel:dryRun:DeleteRouteTable' :: Maybe Bool
dryRun = Maybe Bool
a} :: DeleteRouteTable)

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

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

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

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

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

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

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

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

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

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