{-# 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.DeleteRoute
-- 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 from the specified route table.
module Amazonka.EC2.DeleteRoute
  ( -- * Creating a Request
    DeleteRoute (..),
    newDeleteRoute,

    -- * Request Lenses
    deleteRoute_destinationCidrBlock,
    deleteRoute_destinationIpv6CidrBlock,
    deleteRoute_destinationPrefixListId,
    deleteRoute_dryRun,
    deleteRoute_routeTableId,

    -- * Destructuring the Response
    DeleteRouteResponse (..),
    newDeleteRouteResponse,
  )
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:/ 'newDeleteRoute' smart constructor.
data DeleteRoute = DeleteRoute'
  { -- | The IPv4 CIDR range for the route. The value you specify must match the
    -- CIDR for the route exactly.
    DeleteRoute -> Maybe Text
destinationCidrBlock :: Prelude.Maybe Prelude.Text,
    -- | The IPv6 CIDR range for the route. The value you specify must match the
    -- CIDR for the route exactly.
    DeleteRoute -> Maybe Text
destinationIpv6CidrBlock :: Prelude.Maybe Prelude.Text,
    -- | The ID of the prefix list for the route.
    DeleteRoute -> Maybe Text
destinationPrefixListId :: Prelude.Maybe Prelude.Text,
    -- | 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@.
    DeleteRoute -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the route table.
    DeleteRoute -> Text
routeTableId :: Prelude.Text
  }
  deriving (DeleteRoute -> DeleteRoute -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteRoute -> DeleteRoute -> Bool
$c/= :: DeleteRoute -> DeleteRoute -> Bool
== :: DeleteRoute -> DeleteRoute -> Bool
$c== :: DeleteRoute -> DeleteRoute -> Bool
Prelude.Eq, ReadPrec [DeleteRoute]
ReadPrec DeleteRoute
Int -> ReadS DeleteRoute
ReadS [DeleteRoute]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteRoute]
$creadListPrec :: ReadPrec [DeleteRoute]
readPrec :: ReadPrec DeleteRoute
$creadPrec :: ReadPrec DeleteRoute
readList :: ReadS [DeleteRoute]
$creadList :: ReadS [DeleteRoute]
readsPrec :: Int -> ReadS DeleteRoute
$creadsPrec :: Int -> ReadS DeleteRoute
Prelude.Read, Int -> DeleteRoute -> ShowS
[DeleteRoute] -> ShowS
DeleteRoute -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteRoute] -> ShowS
$cshowList :: [DeleteRoute] -> ShowS
show :: DeleteRoute -> String
$cshow :: DeleteRoute -> String
showsPrec :: Int -> DeleteRoute -> ShowS
$cshowsPrec :: Int -> DeleteRoute -> ShowS
Prelude.Show, forall x. Rep DeleteRoute x -> DeleteRoute
forall x. DeleteRoute -> Rep DeleteRoute x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteRoute x -> DeleteRoute
$cfrom :: forall x. DeleteRoute -> Rep DeleteRoute x
Prelude.Generic)

-- |
-- Create a value of 'DeleteRoute' 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:
--
-- 'destinationCidrBlock', 'deleteRoute_destinationCidrBlock' - The IPv4 CIDR range for the route. The value you specify must match the
-- CIDR for the route exactly.
--
-- 'destinationIpv6CidrBlock', 'deleteRoute_destinationIpv6CidrBlock' - The IPv6 CIDR range for the route. The value you specify must match the
-- CIDR for the route exactly.
--
-- 'destinationPrefixListId', 'deleteRoute_destinationPrefixListId' - The ID of the prefix list for the route.
--
-- 'dryRun', 'deleteRoute_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', 'deleteRoute_routeTableId' - The ID of the route table.
newDeleteRoute ::
  -- | 'routeTableId'
  Prelude.Text ->
  DeleteRoute
newDeleteRoute :: Text -> DeleteRoute
newDeleteRoute Text
pRouteTableId_ =
  DeleteRoute'
    { $sel:destinationCidrBlock:DeleteRoute' :: Maybe Text
destinationCidrBlock =
        forall a. Maybe a
Prelude.Nothing,
      $sel:destinationIpv6CidrBlock:DeleteRoute' :: Maybe Text
destinationIpv6CidrBlock = forall a. Maybe a
Prelude.Nothing,
      $sel:destinationPrefixListId:DeleteRoute' :: Maybe Text
destinationPrefixListId = forall a. Maybe a
Prelude.Nothing,
      $sel:dryRun:DeleteRoute' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:routeTableId:DeleteRoute' :: Text
routeTableId = Text
pRouteTableId_
    }

-- | The IPv4 CIDR range for the route. The value you specify must match the
-- CIDR for the route exactly.
deleteRoute_destinationCidrBlock :: Lens.Lens' DeleteRoute (Prelude.Maybe Prelude.Text)
deleteRoute_destinationCidrBlock :: Lens' DeleteRoute (Maybe Text)
deleteRoute_destinationCidrBlock = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRoute' {Maybe Text
destinationCidrBlock :: Maybe Text
$sel:destinationCidrBlock:DeleteRoute' :: DeleteRoute -> Maybe Text
destinationCidrBlock} -> Maybe Text
destinationCidrBlock) (\s :: DeleteRoute
s@DeleteRoute' {} Maybe Text
a -> DeleteRoute
s {$sel:destinationCidrBlock:DeleteRoute' :: Maybe Text
destinationCidrBlock = Maybe Text
a} :: DeleteRoute)

-- | The IPv6 CIDR range for the route. The value you specify must match the
-- CIDR for the route exactly.
deleteRoute_destinationIpv6CidrBlock :: Lens.Lens' DeleteRoute (Prelude.Maybe Prelude.Text)
deleteRoute_destinationIpv6CidrBlock :: Lens' DeleteRoute (Maybe Text)
deleteRoute_destinationIpv6CidrBlock = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRoute' {Maybe Text
destinationIpv6CidrBlock :: Maybe Text
$sel:destinationIpv6CidrBlock:DeleteRoute' :: DeleteRoute -> Maybe Text
destinationIpv6CidrBlock} -> Maybe Text
destinationIpv6CidrBlock) (\s :: DeleteRoute
s@DeleteRoute' {} Maybe Text
a -> DeleteRoute
s {$sel:destinationIpv6CidrBlock:DeleteRoute' :: Maybe Text
destinationIpv6CidrBlock = Maybe Text
a} :: DeleteRoute)

-- | The ID of the prefix list for the route.
deleteRoute_destinationPrefixListId :: Lens.Lens' DeleteRoute (Prelude.Maybe Prelude.Text)
deleteRoute_destinationPrefixListId :: Lens' DeleteRoute (Maybe Text)
deleteRoute_destinationPrefixListId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRoute' {Maybe Text
destinationPrefixListId :: Maybe Text
$sel:destinationPrefixListId:DeleteRoute' :: DeleteRoute -> Maybe Text
destinationPrefixListId} -> Maybe Text
destinationPrefixListId) (\s :: DeleteRoute
s@DeleteRoute' {} Maybe Text
a -> DeleteRoute
s {$sel:destinationPrefixListId:DeleteRoute' :: Maybe Text
destinationPrefixListId = Maybe Text
a} :: DeleteRoute)

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

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

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

instance Prelude.Hashable DeleteRoute where
  hashWithSalt :: Int -> DeleteRoute -> Int
hashWithSalt Int
_salt DeleteRoute' {Maybe Bool
Maybe Text
Text
routeTableId :: Text
dryRun :: Maybe Bool
destinationPrefixListId :: Maybe Text
destinationIpv6CidrBlock :: Maybe Text
destinationCidrBlock :: Maybe Text
$sel:routeTableId:DeleteRoute' :: DeleteRoute -> Text
$sel:dryRun:DeleteRoute' :: DeleteRoute -> Maybe Bool
$sel:destinationPrefixListId:DeleteRoute' :: DeleteRoute -> Maybe Text
$sel:destinationIpv6CidrBlock:DeleteRoute' :: DeleteRoute -> Maybe Text
$sel:destinationCidrBlock:DeleteRoute' :: DeleteRoute -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
destinationCidrBlock
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
destinationIpv6CidrBlock
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
destinationPrefixListId
      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 DeleteRoute where
  rnf :: DeleteRoute -> ()
rnf DeleteRoute' {Maybe Bool
Maybe Text
Text
routeTableId :: Text
dryRun :: Maybe Bool
destinationPrefixListId :: Maybe Text
destinationIpv6CidrBlock :: Maybe Text
destinationCidrBlock :: Maybe Text
$sel:routeTableId:DeleteRoute' :: DeleteRoute -> Text
$sel:dryRun:DeleteRoute' :: DeleteRoute -> Maybe Bool
$sel:destinationPrefixListId:DeleteRoute' :: DeleteRoute -> Maybe Text
$sel:destinationIpv6CidrBlock:DeleteRoute' :: DeleteRoute -> Maybe Text
$sel:destinationCidrBlock:DeleteRoute' :: DeleteRoute -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
destinationCidrBlock
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
destinationIpv6CidrBlock
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
destinationPrefixListId
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 DeleteRoute where
  toHeaders :: DeleteRoute -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery DeleteRoute where
  toQuery :: DeleteRoute -> QueryString
toQuery DeleteRoute' {Maybe Bool
Maybe Text
Text
routeTableId :: Text
dryRun :: Maybe Bool
destinationPrefixListId :: Maybe Text
destinationIpv6CidrBlock :: Maybe Text
destinationCidrBlock :: Maybe Text
$sel:routeTableId:DeleteRoute' :: DeleteRoute -> Text
$sel:dryRun:DeleteRoute' :: DeleteRoute -> Maybe Bool
$sel:destinationPrefixListId:DeleteRoute' :: DeleteRoute -> Maybe Text
$sel:destinationIpv6CidrBlock:DeleteRoute' :: DeleteRoute -> Maybe Text
$sel:destinationCidrBlock:DeleteRoute' :: DeleteRoute -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DeleteRoute" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DestinationCidrBlock" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
destinationCidrBlock,
        ByteString
"DestinationIpv6CidrBlock"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
destinationIpv6CidrBlock,
        ByteString
"DestinationPrefixListId"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
destinationPrefixListId,
        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:/ 'newDeleteRouteResponse' smart constructor.
data DeleteRouteResponse = DeleteRouteResponse'
  {
  }
  deriving (DeleteRouteResponse -> DeleteRouteResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteRouteResponse -> DeleteRouteResponse -> Bool
$c/= :: DeleteRouteResponse -> DeleteRouteResponse -> Bool
== :: DeleteRouteResponse -> DeleteRouteResponse -> Bool
$c== :: DeleteRouteResponse -> DeleteRouteResponse -> Bool
Prelude.Eq, ReadPrec [DeleteRouteResponse]
ReadPrec DeleteRouteResponse
Int -> ReadS DeleteRouteResponse
ReadS [DeleteRouteResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteRouteResponse]
$creadListPrec :: ReadPrec [DeleteRouteResponse]
readPrec :: ReadPrec DeleteRouteResponse
$creadPrec :: ReadPrec DeleteRouteResponse
readList :: ReadS [DeleteRouteResponse]
$creadList :: ReadS [DeleteRouteResponse]
readsPrec :: Int -> ReadS DeleteRouteResponse
$creadsPrec :: Int -> ReadS DeleteRouteResponse
Prelude.Read, Int -> DeleteRouteResponse -> ShowS
[DeleteRouteResponse] -> ShowS
DeleteRouteResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteRouteResponse] -> ShowS
$cshowList :: [DeleteRouteResponse] -> ShowS
show :: DeleteRouteResponse -> String
$cshow :: DeleteRouteResponse -> String
showsPrec :: Int -> DeleteRouteResponse -> ShowS
$cshowsPrec :: Int -> DeleteRouteResponse -> ShowS
Prelude.Show, forall x. Rep DeleteRouteResponse x -> DeleteRouteResponse
forall x. DeleteRouteResponse -> Rep DeleteRouteResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteRouteResponse x -> DeleteRouteResponse
$cfrom :: forall x. DeleteRouteResponse -> Rep DeleteRouteResponse x
Prelude.Generic)

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

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