{-# 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.APIGateway.DeleteGatewayResponse
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Clears any customization of a GatewayResponse of a specified response
-- type on the given RestApi and resets it with the default settings.
module Amazonka.APIGateway.DeleteGatewayResponse
  ( -- * Creating a Request
    DeleteGatewayResponse (..),
    newDeleteGatewayResponse,

    -- * Request Lenses
    deleteGatewayResponse_restApiId,
    deleteGatewayResponse_responseType,

    -- * Destructuring the Response
    DeleteGatewayResponseResponse (..),
    newDeleteGatewayResponseResponse,
  )
where

import Amazonka.APIGateway.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

-- | Clears any customization of a GatewayResponse of a specified response
-- type on the given RestApi and resets it with the default settings.
--
-- /See:/ 'newDeleteGatewayResponse' smart constructor.
data DeleteGatewayResponse = DeleteGatewayResponse'
  { -- | The string identifier of the associated RestApi.
    DeleteGatewayResponse -> Text
restApiId :: Prelude.Text,
    -- | The response type of the associated GatewayResponse.
    DeleteGatewayResponse -> GatewayResponseType
responseType :: GatewayResponseType
  }
  deriving (DeleteGatewayResponse -> DeleteGatewayResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteGatewayResponse -> DeleteGatewayResponse -> Bool
$c/= :: DeleteGatewayResponse -> DeleteGatewayResponse -> Bool
== :: DeleteGatewayResponse -> DeleteGatewayResponse -> Bool
$c== :: DeleteGatewayResponse -> DeleteGatewayResponse -> Bool
Prelude.Eq, ReadPrec [DeleteGatewayResponse]
ReadPrec DeleteGatewayResponse
Int -> ReadS DeleteGatewayResponse
ReadS [DeleteGatewayResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteGatewayResponse]
$creadListPrec :: ReadPrec [DeleteGatewayResponse]
readPrec :: ReadPrec DeleteGatewayResponse
$creadPrec :: ReadPrec DeleteGatewayResponse
readList :: ReadS [DeleteGatewayResponse]
$creadList :: ReadS [DeleteGatewayResponse]
readsPrec :: Int -> ReadS DeleteGatewayResponse
$creadsPrec :: Int -> ReadS DeleteGatewayResponse
Prelude.Read, Int -> DeleteGatewayResponse -> ShowS
[DeleteGatewayResponse] -> ShowS
DeleteGatewayResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteGatewayResponse] -> ShowS
$cshowList :: [DeleteGatewayResponse] -> ShowS
show :: DeleteGatewayResponse -> String
$cshow :: DeleteGatewayResponse -> String
showsPrec :: Int -> DeleteGatewayResponse -> ShowS
$cshowsPrec :: Int -> DeleteGatewayResponse -> ShowS
Prelude.Show, forall x. Rep DeleteGatewayResponse x -> DeleteGatewayResponse
forall x. DeleteGatewayResponse -> Rep DeleteGatewayResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteGatewayResponse x -> DeleteGatewayResponse
$cfrom :: forall x. DeleteGatewayResponse -> Rep DeleteGatewayResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteGatewayResponse' 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:
--
-- 'restApiId', 'deleteGatewayResponse_restApiId' - The string identifier of the associated RestApi.
--
-- 'responseType', 'deleteGatewayResponse_responseType' - The response type of the associated GatewayResponse.
newDeleteGatewayResponse ::
  -- | 'restApiId'
  Prelude.Text ->
  -- | 'responseType'
  GatewayResponseType ->
  DeleteGatewayResponse
newDeleteGatewayResponse :: Text -> GatewayResponseType -> DeleteGatewayResponse
newDeleteGatewayResponse Text
pRestApiId_ GatewayResponseType
pResponseType_ =
  DeleteGatewayResponse'
    { $sel:restApiId:DeleteGatewayResponse' :: Text
restApiId = Text
pRestApiId_,
      $sel:responseType:DeleteGatewayResponse' :: GatewayResponseType
responseType = GatewayResponseType
pResponseType_
    }

-- | The string identifier of the associated RestApi.
deleteGatewayResponse_restApiId :: Lens.Lens' DeleteGatewayResponse Prelude.Text
deleteGatewayResponse_restApiId :: Lens' DeleteGatewayResponse Text
deleteGatewayResponse_restApiId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGatewayResponse' {Text
restApiId :: Text
$sel:restApiId:DeleteGatewayResponse' :: DeleteGatewayResponse -> Text
restApiId} -> Text
restApiId) (\s :: DeleteGatewayResponse
s@DeleteGatewayResponse' {} Text
a -> DeleteGatewayResponse
s {$sel:restApiId:DeleteGatewayResponse' :: Text
restApiId = Text
a} :: DeleteGatewayResponse)

-- | The response type of the associated GatewayResponse.
deleteGatewayResponse_responseType :: Lens.Lens' DeleteGatewayResponse GatewayResponseType
deleteGatewayResponse_responseType :: Lens' DeleteGatewayResponse GatewayResponseType
deleteGatewayResponse_responseType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGatewayResponse' {GatewayResponseType
responseType :: GatewayResponseType
$sel:responseType:DeleteGatewayResponse' :: DeleteGatewayResponse -> GatewayResponseType
responseType} -> GatewayResponseType
responseType) (\s :: DeleteGatewayResponse
s@DeleteGatewayResponse' {} GatewayResponseType
a -> DeleteGatewayResponse
s {$sel:responseType:DeleteGatewayResponse' :: GatewayResponseType
responseType = GatewayResponseType
a} :: DeleteGatewayResponse)

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

instance Prelude.Hashable DeleteGatewayResponse where
  hashWithSalt :: Int -> DeleteGatewayResponse -> Int
hashWithSalt Int
_salt DeleteGatewayResponse' {Text
GatewayResponseType
responseType :: GatewayResponseType
restApiId :: Text
$sel:responseType:DeleteGatewayResponse' :: DeleteGatewayResponse -> GatewayResponseType
$sel:restApiId:DeleteGatewayResponse' :: DeleteGatewayResponse -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
restApiId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` GatewayResponseType
responseType

instance Prelude.NFData DeleteGatewayResponse where
  rnf :: DeleteGatewayResponse -> ()
rnf DeleteGatewayResponse' {Text
GatewayResponseType
responseType :: GatewayResponseType
restApiId :: Text
$sel:responseType:DeleteGatewayResponse' :: DeleteGatewayResponse -> GatewayResponseType
$sel:restApiId:DeleteGatewayResponse' :: DeleteGatewayResponse -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
restApiId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf GatewayResponseType
responseType

instance Data.ToHeaders DeleteGatewayResponse where
  toHeaders :: DeleteGatewayResponse -> [Header]
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Accept"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# (ByteString
"application/json" :: Prelude.ByteString)
          ]
      )

instance Data.ToPath DeleteGatewayResponse where
  toPath :: DeleteGatewayResponse -> ByteString
toPath DeleteGatewayResponse' {Text
GatewayResponseType
responseType :: GatewayResponseType
restApiId :: Text
$sel:responseType:DeleteGatewayResponse' :: DeleteGatewayResponse -> GatewayResponseType
$sel:restApiId:DeleteGatewayResponse' :: DeleteGatewayResponse -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/restapis/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
restApiId,
        ByteString
"/gatewayresponses/",
        forall a. ToByteString a => a -> ByteString
Data.toBS GatewayResponseType
responseType
      ]

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

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

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

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