{-# 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.ApiGatewayV2.DeleteRouteSettings
-- 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 RouteSettings for a stage.
module Amazonka.ApiGatewayV2.DeleteRouteSettings
  ( -- * Creating a Request
    DeleteRouteSettings (..),
    newDeleteRouteSettings,

    -- * Request Lenses
    deleteRouteSettings_stageName,
    deleteRouteSettings_routeKey,
    deleteRouteSettings_apiId,

    -- * Destructuring the Response
    DeleteRouteSettingsResponse (..),
    newDeleteRouteSettingsResponse,
  )
where

import Amazonka.ApiGatewayV2.Types
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDeleteRouteSettings' smart constructor.
data DeleteRouteSettings = DeleteRouteSettings'
  { -- | The stage name. Stage names can only contain alphanumeric characters,
    -- hyphens, and underscores. Maximum length is 128 characters.
    DeleteRouteSettings -> Text
stageName :: Prelude.Text,
    -- | The route key.
    DeleteRouteSettings -> Text
routeKey :: Prelude.Text,
    -- | The API identifier.
    DeleteRouteSettings -> Text
apiId :: Prelude.Text
  }
  deriving (DeleteRouteSettings -> DeleteRouteSettings -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteRouteSettings -> DeleteRouteSettings -> Bool
$c/= :: DeleteRouteSettings -> DeleteRouteSettings -> Bool
== :: DeleteRouteSettings -> DeleteRouteSettings -> Bool
$c== :: DeleteRouteSettings -> DeleteRouteSettings -> Bool
Prelude.Eq, ReadPrec [DeleteRouteSettings]
ReadPrec DeleteRouteSettings
Int -> ReadS DeleteRouteSettings
ReadS [DeleteRouteSettings]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteRouteSettings]
$creadListPrec :: ReadPrec [DeleteRouteSettings]
readPrec :: ReadPrec DeleteRouteSettings
$creadPrec :: ReadPrec DeleteRouteSettings
readList :: ReadS [DeleteRouteSettings]
$creadList :: ReadS [DeleteRouteSettings]
readsPrec :: Int -> ReadS DeleteRouteSettings
$creadsPrec :: Int -> ReadS DeleteRouteSettings
Prelude.Read, Int -> DeleteRouteSettings -> ShowS
[DeleteRouteSettings] -> ShowS
DeleteRouteSettings -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteRouteSettings] -> ShowS
$cshowList :: [DeleteRouteSettings] -> ShowS
show :: DeleteRouteSettings -> String
$cshow :: DeleteRouteSettings -> String
showsPrec :: Int -> DeleteRouteSettings -> ShowS
$cshowsPrec :: Int -> DeleteRouteSettings -> ShowS
Prelude.Show, forall x. Rep DeleteRouteSettings x -> DeleteRouteSettings
forall x. DeleteRouteSettings -> Rep DeleteRouteSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteRouteSettings x -> DeleteRouteSettings
$cfrom :: forall x. DeleteRouteSettings -> Rep DeleteRouteSettings x
Prelude.Generic)

-- |
-- Create a value of 'DeleteRouteSettings' 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:
--
-- 'stageName', 'deleteRouteSettings_stageName' - The stage name. Stage names can only contain alphanumeric characters,
-- hyphens, and underscores. Maximum length is 128 characters.
--
-- 'routeKey', 'deleteRouteSettings_routeKey' - The route key.
--
-- 'apiId', 'deleteRouteSettings_apiId' - The API identifier.
newDeleteRouteSettings ::
  -- | 'stageName'
  Prelude.Text ->
  -- | 'routeKey'
  Prelude.Text ->
  -- | 'apiId'
  Prelude.Text ->
  DeleteRouteSettings
newDeleteRouteSettings :: Text -> Text -> Text -> DeleteRouteSettings
newDeleteRouteSettings Text
pStageName_ Text
pRouteKey_ Text
pApiId_ =
  DeleteRouteSettings'
    { $sel:stageName:DeleteRouteSettings' :: Text
stageName = Text
pStageName_,
      $sel:routeKey:DeleteRouteSettings' :: Text
routeKey = Text
pRouteKey_,
      $sel:apiId:DeleteRouteSettings' :: Text
apiId = Text
pApiId_
    }

-- | The stage name. Stage names can only contain alphanumeric characters,
-- hyphens, and underscores. Maximum length is 128 characters.
deleteRouteSettings_stageName :: Lens.Lens' DeleteRouteSettings Prelude.Text
deleteRouteSettings_stageName :: Lens' DeleteRouteSettings Text
deleteRouteSettings_stageName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRouteSettings' {Text
stageName :: Text
$sel:stageName:DeleteRouteSettings' :: DeleteRouteSettings -> Text
stageName} -> Text
stageName) (\s :: DeleteRouteSettings
s@DeleteRouteSettings' {} Text
a -> DeleteRouteSettings
s {$sel:stageName:DeleteRouteSettings' :: Text
stageName = Text
a} :: DeleteRouteSettings)

-- | The route key.
deleteRouteSettings_routeKey :: Lens.Lens' DeleteRouteSettings Prelude.Text
deleteRouteSettings_routeKey :: Lens' DeleteRouteSettings Text
deleteRouteSettings_routeKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRouteSettings' {Text
routeKey :: Text
$sel:routeKey:DeleteRouteSettings' :: DeleteRouteSettings -> Text
routeKey} -> Text
routeKey) (\s :: DeleteRouteSettings
s@DeleteRouteSettings' {} Text
a -> DeleteRouteSettings
s {$sel:routeKey:DeleteRouteSettings' :: Text
routeKey = Text
a} :: DeleteRouteSettings)

-- | The API identifier.
deleteRouteSettings_apiId :: Lens.Lens' DeleteRouteSettings Prelude.Text
deleteRouteSettings_apiId :: Lens' DeleteRouteSettings Text
deleteRouteSettings_apiId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRouteSettings' {Text
apiId :: Text
$sel:apiId:DeleteRouteSettings' :: DeleteRouteSettings -> Text
apiId} -> Text
apiId) (\s :: DeleteRouteSettings
s@DeleteRouteSettings' {} Text
a -> DeleteRouteSettings
s {$sel:apiId:DeleteRouteSettings' :: Text
apiId = Text
a} :: DeleteRouteSettings)

instance Core.AWSRequest DeleteRouteSettings where
  type
    AWSResponse DeleteRouteSettings =
      DeleteRouteSettingsResponse
  request :: (Service -> Service)
-> DeleteRouteSettings -> Request DeleteRouteSettings
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteRouteSettings
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteRouteSettings)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull DeleteRouteSettingsResponse
DeleteRouteSettingsResponse'

instance Prelude.Hashable DeleteRouteSettings where
  hashWithSalt :: Int -> DeleteRouteSettings -> Int
hashWithSalt Int
_salt DeleteRouteSettings' {Text
apiId :: Text
routeKey :: Text
stageName :: Text
$sel:apiId:DeleteRouteSettings' :: DeleteRouteSettings -> Text
$sel:routeKey:DeleteRouteSettings' :: DeleteRouteSettings -> Text
$sel:stageName:DeleteRouteSettings' :: DeleteRouteSettings -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
stageName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
routeKey
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
apiId

instance Prelude.NFData DeleteRouteSettings where
  rnf :: DeleteRouteSettings -> ()
rnf DeleteRouteSettings' {Text
apiId :: Text
routeKey :: Text
stageName :: Text
$sel:apiId:DeleteRouteSettings' :: DeleteRouteSettings -> Text
$sel:routeKey:DeleteRouteSettings' :: DeleteRouteSettings -> Text
$sel:stageName:DeleteRouteSettings' :: DeleteRouteSettings -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
stageName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
routeKey
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
apiId

instance Data.ToHeaders DeleteRouteSettings where
  toHeaders :: DeleteRouteSettings -> [Header]
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath DeleteRouteSettings where
  toPath :: DeleteRouteSettings -> ByteString
toPath DeleteRouteSettings' {Text
apiId :: Text
routeKey :: Text
stageName :: Text
$sel:apiId:DeleteRouteSettings' :: DeleteRouteSettings -> Text
$sel:routeKey:DeleteRouteSettings' :: DeleteRouteSettings -> Text
$sel:stageName:DeleteRouteSettings' :: DeleteRouteSettings -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v2/apis/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
apiId,
        ByteString
"/stages/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
stageName,
        ByteString
"/routesettings/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
routeKey
      ]

instance Data.ToQuery DeleteRouteSettings where
  toQuery :: DeleteRouteSettings -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

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

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