{-# 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.IoT.UpdateAuthorizer
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates an authorizer.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions UpdateAuthorizer>
-- action.
module Amazonka.IoT.UpdateAuthorizer
  ( -- * Creating a Request
    UpdateAuthorizer (..),
    newUpdateAuthorizer,

    -- * Request Lenses
    updateAuthorizer_authorizerFunctionArn,
    updateAuthorizer_enableCachingForHttp,
    updateAuthorizer_status,
    updateAuthorizer_tokenKeyName,
    updateAuthorizer_tokenSigningPublicKeys,
    updateAuthorizer_authorizerName,

    -- * Destructuring the Response
    UpdateAuthorizerResponse (..),
    newUpdateAuthorizerResponse,

    -- * Response Lenses
    updateAuthorizerResponse_authorizerArn,
    updateAuthorizerResponse_authorizerName,
    updateAuthorizerResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateAuthorizer' smart constructor.
data UpdateAuthorizer = UpdateAuthorizer'
  { -- | The ARN of the authorizer\'s Lambda function.
    UpdateAuthorizer -> Maybe Text
authorizerFunctionArn :: Prelude.Maybe Prelude.Text,
    -- | When @true@, the result from the authorizer’s Lambda function is cached
    -- for the time specified in @refreshAfterInSeconds@. The cached result is
    -- used while the device reuses the same HTTP connection.
    UpdateAuthorizer -> Maybe Bool
enableCachingForHttp :: Prelude.Maybe Prelude.Bool,
    -- | The status of the update authorizer request.
    UpdateAuthorizer -> Maybe AuthorizerStatus
status :: Prelude.Maybe AuthorizerStatus,
    -- | The key used to extract the token from the HTTP headers.
    UpdateAuthorizer -> Maybe Text
tokenKeyName :: Prelude.Maybe Prelude.Text,
    -- | The public keys used to verify the token signature.
    UpdateAuthorizer -> Maybe (HashMap Text Text)
tokenSigningPublicKeys :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The authorizer name.
    UpdateAuthorizer -> Text
authorizerName :: Prelude.Text
  }
  deriving (UpdateAuthorizer -> UpdateAuthorizer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateAuthorizer -> UpdateAuthorizer -> Bool
$c/= :: UpdateAuthorizer -> UpdateAuthorizer -> Bool
== :: UpdateAuthorizer -> UpdateAuthorizer -> Bool
$c== :: UpdateAuthorizer -> UpdateAuthorizer -> Bool
Prelude.Eq, ReadPrec [UpdateAuthorizer]
ReadPrec UpdateAuthorizer
Int -> ReadS UpdateAuthorizer
ReadS [UpdateAuthorizer]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateAuthorizer]
$creadListPrec :: ReadPrec [UpdateAuthorizer]
readPrec :: ReadPrec UpdateAuthorizer
$creadPrec :: ReadPrec UpdateAuthorizer
readList :: ReadS [UpdateAuthorizer]
$creadList :: ReadS [UpdateAuthorizer]
readsPrec :: Int -> ReadS UpdateAuthorizer
$creadsPrec :: Int -> ReadS UpdateAuthorizer
Prelude.Read, Int -> UpdateAuthorizer -> ShowS
[UpdateAuthorizer] -> ShowS
UpdateAuthorizer -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateAuthorizer] -> ShowS
$cshowList :: [UpdateAuthorizer] -> ShowS
show :: UpdateAuthorizer -> String
$cshow :: UpdateAuthorizer -> String
showsPrec :: Int -> UpdateAuthorizer -> ShowS
$cshowsPrec :: Int -> UpdateAuthorizer -> ShowS
Prelude.Show, forall x. Rep UpdateAuthorizer x -> UpdateAuthorizer
forall x. UpdateAuthorizer -> Rep UpdateAuthorizer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateAuthorizer x -> UpdateAuthorizer
$cfrom :: forall x. UpdateAuthorizer -> Rep UpdateAuthorizer x
Prelude.Generic)

-- |
-- Create a value of 'UpdateAuthorizer' 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:
--
-- 'authorizerFunctionArn', 'updateAuthorizer_authorizerFunctionArn' - The ARN of the authorizer\'s Lambda function.
--
-- 'enableCachingForHttp', 'updateAuthorizer_enableCachingForHttp' - When @true@, the result from the authorizer’s Lambda function is cached
-- for the time specified in @refreshAfterInSeconds@. The cached result is
-- used while the device reuses the same HTTP connection.
--
-- 'status', 'updateAuthorizer_status' - The status of the update authorizer request.
--
-- 'tokenKeyName', 'updateAuthorizer_tokenKeyName' - The key used to extract the token from the HTTP headers.
--
-- 'tokenSigningPublicKeys', 'updateAuthorizer_tokenSigningPublicKeys' - The public keys used to verify the token signature.
--
-- 'authorizerName', 'updateAuthorizer_authorizerName' - The authorizer name.
newUpdateAuthorizer ::
  -- | 'authorizerName'
  Prelude.Text ->
  UpdateAuthorizer
newUpdateAuthorizer :: Text -> UpdateAuthorizer
newUpdateAuthorizer Text
pAuthorizerName_ =
  UpdateAuthorizer'
    { $sel:authorizerFunctionArn:UpdateAuthorizer' :: Maybe Text
authorizerFunctionArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:enableCachingForHttp:UpdateAuthorizer' :: Maybe Bool
enableCachingForHttp = forall a. Maybe a
Prelude.Nothing,
      $sel:status:UpdateAuthorizer' :: Maybe AuthorizerStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:tokenKeyName:UpdateAuthorizer' :: Maybe Text
tokenKeyName = forall a. Maybe a
Prelude.Nothing,
      $sel:tokenSigningPublicKeys:UpdateAuthorizer' :: Maybe (HashMap Text Text)
tokenSigningPublicKeys = forall a. Maybe a
Prelude.Nothing,
      $sel:authorizerName:UpdateAuthorizer' :: Text
authorizerName = Text
pAuthorizerName_
    }

-- | The ARN of the authorizer\'s Lambda function.
updateAuthorizer_authorizerFunctionArn :: Lens.Lens' UpdateAuthorizer (Prelude.Maybe Prelude.Text)
updateAuthorizer_authorizerFunctionArn :: Lens' UpdateAuthorizer (Maybe Text)
updateAuthorizer_authorizerFunctionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAuthorizer' {Maybe Text
authorizerFunctionArn :: Maybe Text
$sel:authorizerFunctionArn:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe Text
authorizerFunctionArn} -> Maybe Text
authorizerFunctionArn) (\s :: UpdateAuthorizer
s@UpdateAuthorizer' {} Maybe Text
a -> UpdateAuthorizer
s {$sel:authorizerFunctionArn:UpdateAuthorizer' :: Maybe Text
authorizerFunctionArn = Maybe Text
a} :: UpdateAuthorizer)

-- | When @true@, the result from the authorizer’s Lambda function is cached
-- for the time specified in @refreshAfterInSeconds@. The cached result is
-- used while the device reuses the same HTTP connection.
updateAuthorizer_enableCachingForHttp :: Lens.Lens' UpdateAuthorizer (Prelude.Maybe Prelude.Bool)
updateAuthorizer_enableCachingForHttp :: Lens' UpdateAuthorizer (Maybe Bool)
updateAuthorizer_enableCachingForHttp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAuthorizer' {Maybe Bool
enableCachingForHttp :: Maybe Bool
$sel:enableCachingForHttp:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe Bool
enableCachingForHttp} -> Maybe Bool
enableCachingForHttp) (\s :: UpdateAuthorizer
s@UpdateAuthorizer' {} Maybe Bool
a -> UpdateAuthorizer
s {$sel:enableCachingForHttp:UpdateAuthorizer' :: Maybe Bool
enableCachingForHttp = Maybe Bool
a} :: UpdateAuthorizer)

-- | The status of the update authorizer request.
updateAuthorizer_status :: Lens.Lens' UpdateAuthorizer (Prelude.Maybe AuthorizerStatus)
updateAuthorizer_status :: Lens' UpdateAuthorizer (Maybe AuthorizerStatus)
updateAuthorizer_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAuthorizer' {Maybe AuthorizerStatus
status :: Maybe AuthorizerStatus
$sel:status:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe AuthorizerStatus
status} -> Maybe AuthorizerStatus
status) (\s :: UpdateAuthorizer
s@UpdateAuthorizer' {} Maybe AuthorizerStatus
a -> UpdateAuthorizer
s {$sel:status:UpdateAuthorizer' :: Maybe AuthorizerStatus
status = Maybe AuthorizerStatus
a} :: UpdateAuthorizer)

-- | The key used to extract the token from the HTTP headers.
updateAuthorizer_tokenKeyName :: Lens.Lens' UpdateAuthorizer (Prelude.Maybe Prelude.Text)
updateAuthorizer_tokenKeyName :: Lens' UpdateAuthorizer (Maybe Text)
updateAuthorizer_tokenKeyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAuthorizer' {Maybe Text
tokenKeyName :: Maybe Text
$sel:tokenKeyName:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe Text
tokenKeyName} -> Maybe Text
tokenKeyName) (\s :: UpdateAuthorizer
s@UpdateAuthorizer' {} Maybe Text
a -> UpdateAuthorizer
s {$sel:tokenKeyName:UpdateAuthorizer' :: Maybe Text
tokenKeyName = Maybe Text
a} :: UpdateAuthorizer)

-- | The public keys used to verify the token signature.
updateAuthorizer_tokenSigningPublicKeys :: Lens.Lens' UpdateAuthorizer (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
updateAuthorizer_tokenSigningPublicKeys :: Lens' UpdateAuthorizer (Maybe (HashMap Text Text))
updateAuthorizer_tokenSigningPublicKeys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAuthorizer' {Maybe (HashMap Text Text)
tokenSigningPublicKeys :: Maybe (HashMap Text Text)
$sel:tokenSigningPublicKeys:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe (HashMap Text Text)
tokenSigningPublicKeys} -> Maybe (HashMap Text Text)
tokenSigningPublicKeys) (\s :: UpdateAuthorizer
s@UpdateAuthorizer' {} Maybe (HashMap Text Text)
a -> UpdateAuthorizer
s {$sel:tokenSigningPublicKeys:UpdateAuthorizer' :: Maybe (HashMap Text Text)
tokenSigningPublicKeys = Maybe (HashMap Text Text)
a} :: UpdateAuthorizer) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The authorizer name.
updateAuthorizer_authorizerName :: Lens.Lens' UpdateAuthorizer Prelude.Text
updateAuthorizer_authorizerName :: Lens' UpdateAuthorizer Text
updateAuthorizer_authorizerName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAuthorizer' {Text
authorizerName :: Text
$sel:authorizerName:UpdateAuthorizer' :: UpdateAuthorizer -> Text
authorizerName} -> Text
authorizerName) (\s :: UpdateAuthorizer
s@UpdateAuthorizer' {} Text
a -> UpdateAuthorizer
s {$sel:authorizerName:UpdateAuthorizer' :: Text
authorizerName = Text
a} :: UpdateAuthorizer)

instance Core.AWSRequest UpdateAuthorizer where
  type
    AWSResponse UpdateAuthorizer =
      UpdateAuthorizerResponse
  request :: (Service -> Service)
-> UpdateAuthorizer -> Request UpdateAuthorizer
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateAuthorizer
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateAuthorizer)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Maybe Text -> Int -> UpdateAuthorizerResponse
UpdateAuthorizerResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"authorizerArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"authorizerName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable UpdateAuthorizer where
  hashWithSalt :: Int -> UpdateAuthorizer -> Int
hashWithSalt Int
_salt UpdateAuthorizer' {Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Maybe AuthorizerStatus
Text
authorizerName :: Text
tokenSigningPublicKeys :: Maybe (HashMap Text Text)
tokenKeyName :: Maybe Text
status :: Maybe AuthorizerStatus
enableCachingForHttp :: Maybe Bool
authorizerFunctionArn :: Maybe Text
$sel:authorizerName:UpdateAuthorizer' :: UpdateAuthorizer -> Text
$sel:tokenSigningPublicKeys:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe (HashMap Text Text)
$sel:tokenKeyName:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe Text
$sel:status:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe AuthorizerStatus
$sel:enableCachingForHttp:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe Bool
$sel:authorizerFunctionArn:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
authorizerFunctionArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
enableCachingForHttp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AuthorizerStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
tokenKeyName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tokenSigningPublicKeys
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
authorizerName

instance Prelude.NFData UpdateAuthorizer where
  rnf :: UpdateAuthorizer -> ()
rnf UpdateAuthorizer' {Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Maybe AuthorizerStatus
Text
authorizerName :: Text
tokenSigningPublicKeys :: Maybe (HashMap Text Text)
tokenKeyName :: Maybe Text
status :: Maybe AuthorizerStatus
enableCachingForHttp :: Maybe Bool
authorizerFunctionArn :: Maybe Text
$sel:authorizerName:UpdateAuthorizer' :: UpdateAuthorizer -> Text
$sel:tokenSigningPublicKeys:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe (HashMap Text Text)
$sel:tokenKeyName:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe Text
$sel:status:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe AuthorizerStatus
$sel:enableCachingForHttp:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe Bool
$sel:authorizerFunctionArn:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
authorizerFunctionArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enableCachingForHttp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AuthorizerStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
tokenKeyName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tokenSigningPublicKeys
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
authorizerName

instance Data.ToHeaders UpdateAuthorizer where
  toHeaders :: UpdateAuthorizer -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON UpdateAuthorizer where
  toJSON :: UpdateAuthorizer -> Value
toJSON UpdateAuthorizer' {Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Maybe AuthorizerStatus
Text
authorizerName :: Text
tokenSigningPublicKeys :: Maybe (HashMap Text Text)
tokenKeyName :: Maybe Text
status :: Maybe AuthorizerStatus
enableCachingForHttp :: Maybe Bool
authorizerFunctionArn :: Maybe Text
$sel:authorizerName:UpdateAuthorizer' :: UpdateAuthorizer -> Text
$sel:tokenSigningPublicKeys:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe (HashMap Text Text)
$sel:tokenKeyName:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe Text
$sel:status:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe AuthorizerStatus
$sel:enableCachingForHttp:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe Bool
$sel:authorizerFunctionArn:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"authorizerFunctionArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
authorizerFunctionArn,
            (Key
"enableCachingForHttp" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
enableCachingForHttp,
            (Key
"status" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AuthorizerStatus
status,
            (Key
"tokenKeyName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
tokenKeyName,
            (Key
"tokenSigningPublicKeys" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
tokenSigningPublicKeys
          ]
      )

instance Data.ToPath UpdateAuthorizer where
  toPath :: UpdateAuthorizer -> ByteString
toPath UpdateAuthorizer' {Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Maybe AuthorizerStatus
Text
authorizerName :: Text
tokenSigningPublicKeys :: Maybe (HashMap Text Text)
tokenKeyName :: Maybe Text
status :: Maybe AuthorizerStatus
enableCachingForHttp :: Maybe Bool
authorizerFunctionArn :: Maybe Text
$sel:authorizerName:UpdateAuthorizer' :: UpdateAuthorizer -> Text
$sel:tokenSigningPublicKeys:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe (HashMap Text Text)
$sel:tokenKeyName:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe Text
$sel:status:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe AuthorizerStatus
$sel:enableCachingForHttp:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe Bool
$sel:authorizerFunctionArn:UpdateAuthorizer' :: UpdateAuthorizer -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/authorizer/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
authorizerName]

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

-- | /See:/ 'newUpdateAuthorizerResponse' smart constructor.
data UpdateAuthorizerResponse = UpdateAuthorizerResponse'
  { -- | The authorizer ARN.
    UpdateAuthorizerResponse -> Maybe Text
authorizerArn :: Prelude.Maybe Prelude.Text,
    -- | The authorizer name.
    UpdateAuthorizerResponse -> Maybe Text
authorizerName :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateAuthorizerResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateAuthorizerResponse -> UpdateAuthorizerResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateAuthorizerResponse -> UpdateAuthorizerResponse -> Bool
$c/= :: UpdateAuthorizerResponse -> UpdateAuthorizerResponse -> Bool
== :: UpdateAuthorizerResponse -> UpdateAuthorizerResponse -> Bool
$c== :: UpdateAuthorizerResponse -> UpdateAuthorizerResponse -> Bool
Prelude.Eq, ReadPrec [UpdateAuthorizerResponse]
ReadPrec UpdateAuthorizerResponse
Int -> ReadS UpdateAuthorizerResponse
ReadS [UpdateAuthorizerResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateAuthorizerResponse]
$creadListPrec :: ReadPrec [UpdateAuthorizerResponse]
readPrec :: ReadPrec UpdateAuthorizerResponse
$creadPrec :: ReadPrec UpdateAuthorizerResponse
readList :: ReadS [UpdateAuthorizerResponse]
$creadList :: ReadS [UpdateAuthorizerResponse]
readsPrec :: Int -> ReadS UpdateAuthorizerResponse
$creadsPrec :: Int -> ReadS UpdateAuthorizerResponse
Prelude.Read, Int -> UpdateAuthorizerResponse -> ShowS
[UpdateAuthorizerResponse] -> ShowS
UpdateAuthorizerResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateAuthorizerResponse] -> ShowS
$cshowList :: [UpdateAuthorizerResponse] -> ShowS
show :: UpdateAuthorizerResponse -> String
$cshow :: UpdateAuthorizerResponse -> String
showsPrec :: Int -> UpdateAuthorizerResponse -> ShowS
$cshowsPrec :: Int -> UpdateAuthorizerResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateAuthorizerResponse x -> UpdateAuthorizerResponse
forall x.
UpdateAuthorizerResponse -> Rep UpdateAuthorizerResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateAuthorizerResponse x -> UpdateAuthorizerResponse
$cfrom :: forall x.
UpdateAuthorizerResponse -> Rep UpdateAuthorizerResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateAuthorizerResponse' 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:
--
-- 'authorizerArn', 'updateAuthorizerResponse_authorizerArn' - The authorizer ARN.
--
-- 'authorizerName', 'updateAuthorizerResponse_authorizerName' - The authorizer name.
--
-- 'httpStatus', 'updateAuthorizerResponse_httpStatus' - The response's http status code.
newUpdateAuthorizerResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateAuthorizerResponse
newUpdateAuthorizerResponse :: Int -> UpdateAuthorizerResponse
newUpdateAuthorizerResponse Int
pHttpStatus_ =
  UpdateAuthorizerResponse'
    { $sel:authorizerArn:UpdateAuthorizerResponse' :: Maybe Text
authorizerArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:authorizerName:UpdateAuthorizerResponse' :: Maybe Text
authorizerName = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateAuthorizerResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The authorizer ARN.
updateAuthorizerResponse_authorizerArn :: Lens.Lens' UpdateAuthorizerResponse (Prelude.Maybe Prelude.Text)
updateAuthorizerResponse_authorizerArn :: Lens' UpdateAuthorizerResponse (Maybe Text)
updateAuthorizerResponse_authorizerArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAuthorizerResponse' {Maybe Text
authorizerArn :: Maybe Text
$sel:authorizerArn:UpdateAuthorizerResponse' :: UpdateAuthorizerResponse -> Maybe Text
authorizerArn} -> Maybe Text
authorizerArn) (\s :: UpdateAuthorizerResponse
s@UpdateAuthorizerResponse' {} Maybe Text
a -> UpdateAuthorizerResponse
s {$sel:authorizerArn:UpdateAuthorizerResponse' :: Maybe Text
authorizerArn = Maybe Text
a} :: UpdateAuthorizerResponse)

-- | The authorizer name.
updateAuthorizerResponse_authorizerName :: Lens.Lens' UpdateAuthorizerResponse (Prelude.Maybe Prelude.Text)
updateAuthorizerResponse_authorizerName :: Lens' UpdateAuthorizerResponse (Maybe Text)
updateAuthorizerResponse_authorizerName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAuthorizerResponse' {Maybe Text
authorizerName :: Maybe Text
$sel:authorizerName:UpdateAuthorizerResponse' :: UpdateAuthorizerResponse -> Maybe Text
authorizerName} -> Maybe Text
authorizerName) (\s :: UpdateAuthorizerResponse
s@UpdateAuthorizerResponse' {} Maybe Text
a -> UpdateAuthorizerResponse
s {$sel:authorizerName:UpdateAuthorizerResponse' :: Maybe Text
authorizerName = Maybe Text
a} :: UpdateAuthorizerResponse)

-- | The response's http status code.
updateAuthorizerResponse_httpStatus :: Lens.Lens' UpdateAuthorizerResponse Prelude.Int
updateAuthorizerResponse_httpStatus :: Lens' UpdateAuthorizerResponse Int
updateAuthorizerResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateAuthorizerResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateAuthorizerResponse' :: UpdateAuthorizerResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateAuthorizerResponse
s@UpdateAuthorizerResponse' {} Int
a -> UpdateAuthorizerResponse
s {$sel:httpStatus:UpdateAuthorizerResponse' :: Int
httpStatus = Int
a} :: UpdateAuthorizerResponse)

instance Prelude.NFData UpdateAuthorizerResponse where
  rnf :: UpdateAuthorizerResponse -> ()
rnf UpdateAuthorizerResponse' {Int
Maybe Text
httpStatus :: Int
authorizerName :: Maybe Text
authorizerArn :: Maybe Text
$sel:httpStatus:UpdateAuthorizerResponse' :: UpdateAuthorizerResponse -> Int
$sel:authorizerName:UpdateAuthorizerResponse' :: UpdateAuthorizerResponse -> Maybe Text
$sel:authorizerArn:UpdateAuthorizerResponse' :: UpdateAuthorizerResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
authorizerArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
authorizerName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus