{-# 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.FlushStageAuthorizersCache
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Flushes all authorizer cache entries on a stage.
module Amazonka.APIGateway.FlushStageAuthorizersCache
  ( -- * Creating a Request
    FlushStageAuthorizersCache (..),
    newFlushStageAuthorizersCache,

    -- * Request Lenses
    flushStageAuthorizersCache_restApiId,
    flushStageAuthorizersCache_stageName,

    -- * Destructuring the Response
    FlushStageAuthorizersCacheResponse (..),
    newFlushStageAuthorizersCacheResponse,
  )
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

-- | Request to flush authorizer cache entries on a specified stage.
--
-- /See:/ 'newFlushStageAuthorizersCache' smart constructor.
data FlushStageAuthorizersCache = FlushStageAuthorizersCache'
  { -- | The string identifier of the associated RestApi.
    FlushStageAuthorizersCache -> Text
restApiId :: Prelude.Text,
    -- | The name of the stage to flush.
    FlushStageAuthorizersCache -> Text
stageName :: Prelude.Text
  }
  deriving (FlushStageAuthorizersCache -> FlushStageAuthorizersCache -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FlushStageAuthorizersCache -> FlushStageAuthorizersCache -> Bool
$c/= :: FlushStageAuthorizersCache -> FlushStageAuthorizersCache -> Bool
== :: FlushStageAuthorizersCache -> FlushStageAuthorizersCache -> Bool
$c== :: FlushStageAuthorizersCache -> FlushStageAuthorizersCache -> Bool
Prelude.Eq, ReadPrec [FlushStageAuthorizersCache]
ReadPrec FlushStageAuthorizersCache
Int -> ReadS FlushStageAuthorizersCache
ReadS [FlushStageAuthorizersCache]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FlushStageAuthorizersCache]
$creadListPrec :: ReadPrec [FlushStageAuthorizersCache]
readPrec :: ReadPrec FlushStageAuthorizersCache
$creadPrec :: ReadPrec FlushStageAuthorizersCache
readList :: ReadS [FlushStageAuthorizersCache]
$creadList :: ReadS [FlushStageAuthorizersCache]
readsPrec :: Int -> ReadS FlushStageAuthorizersCache
$creadsPrec :: Int -> ReadS FlushStageAuthorizersCache
Prelude.Read, Int -> FlushStageAuthorizersCache -> ShowS
[FlushStageAuthorizersCache] -> ShowS
FlushStageAuthorizersCache -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FlushStageAuthorizersCache] -> ShowS
$cshowList :: [FlushStageAuthorizersCache] -> ShowS
show :: FlushStageAuthorizersCache -> String
$cshow :: FlushStageAuthorizersCache -> String
showsPrec :: Int -> FlushStageAuthorizersCache -> ShowS
$cshowsPrec :: Int -> FlushStageAuthorizersCache -> ShowS
Prelude.Show, forall x.
Rep FlushStageAuthorizersCache x -> FlushStageAuthorizersCache
forall x.
FlushStageAuthorizersCache -> Rep FlushStageAuthorizersCache x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep FlushStageAuthorizersCache x -> FlushStageAuthorizersCache
$cfrom :: forall x.
FlushStageAuthorizersCache -> Rep FlushStageAuthorizersCache x
Prelude.Generic)

-- |
-- Create a value of 'FlushStageAuthorizersCache' 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', 'flushStageAuthorizersCache_restApiId' - The string identifier of the associated RestApi.
--
-- 'stageName', 'flushStageAuthorizersCache_stageName' - The name of the stage to flush.
newFlushStageAuthorizersCache ::
  -- | 'restApiId'
  Prelude.Text ->
  -- | 'stageName'
  Prelude.Text ->
  FlushStageAuthorizersCache
newFlushStageAuthorizersCache :: Text -> Text -> FlushStageAuthorizersCache
newFlushStageAuthorizersCache Text
pRestApiId_ Text
pStageName_ =
  FlushStageAuthorizersCache'
    { $sel:restApiId:FlushStageAuthorizersCache' :: Text
restApiId =
        Text
pRestApiId_,
      $sel:stageName:FlushStageAuthorizersCache' :: Text
stageName = Text
pStageName_
    }

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

-- | The name of the stage to flush.
flushStageAuthorizersCache_stageName :: Lens.Lens' FlushStageAuthorizersCache Prelude.Text
flushStageAuthorizersCache_stageName :: Lens' FlushStageAuthorizersCache Text
flushStageAuthorizersCache_stageName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FlushStageAuthorizersCache' {Text
stageName :: Text
$sel:stageName:FlushStageAuthorizersCache' :: FlushStageAuthorizersCache -> Text
stageName} -> Text
stageName) (\s :: FlushStageAuthorizersCache
s@FlushStageAuthorizersCache' {} Text
a -> FlushStageAuthorizersCache
s {$sel:stageName:FlushStageAuthorizersCache' :: Text
stageName = Text
a} :: FlushStageAuthorizersCache)

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

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

instance Prelude.NFData FlushStageAuthorizersCache where
  rnf :: FlushStageAuthorizersCache -> ()
rnf FlushStageAuthorizersCache' {Text
stageName :: Text
restApiId :: Text
$sel:stageName:FlushStageAuthorizersCache' :: FlushStageAuthorizersCache -> Text
$sel:restApiId:FlushStageAuthorizersCache' :: FlushStageAuthorizersCache -> 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 Text
stageName

instance Data.ToHeaders FlushStageAuthorizersCache where
  toHeaders :: FlushStageAuthorizersCache -> [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 FlushStageAuthorizersCache where
  toPath :: FlushStageAuthorizersCache -> ByteString
toPath FlushStageAuthorizersCache' {Text
stageName :: Text
restApiId :: Text
$sel:stageName:FlushStageAuthorizersCache' :: FlushStageAuthorizersCache -> Text
$sel:restApiId:FlushStageAuthorizersCache' :: FlushStageAuthorizersCache -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/restapis/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
restApiId,
        ByteString
"/stages/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
stageName,
        ByteString
"/cache/authorizers"
      ]

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

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

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

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