{-# 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.WorkSpaces.ModifyCertificateBasedAuthProperties
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Modifies the properties of the certificate-based authentication you want
-- to use with your WorkSpaces.
module Amazonka.WorkSpaces.ModifyCertificateBasedAuthProperties
  ( -- * Creating a Request
    ModifyCertificateBasedAuthProperties (..),
    newModifyCertificateBasedAuthProperties,

    -- * Request Lenses
    modifyCertificateBasedAuthProperties_certificateBasedAuthProperties,
    modifyCertificateBasedAuthProperties_propertiesToDelete,
    modifyCertificateBasedAuthProperties_resourceId,

    -- * Destructuring the Response
    ModifyCertificateBasedAuthPropertiesResponse (..),
    newModifyCertificateBasedAuthPropertiesResponse,

    -- * Response Lenses
    modifyCertificateBasedAuthPropertiesResponse_httpStatus,
  )
where

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
import Amazonka.WorkSpaces.Types

-- | /See:/ 'newModifyCertificateBasedAuthProperties' smart constructor.
data ModifyCertificateBasedAuthProperties = ModifyCertificateBasedAuthProperties'
  { -- | The properties of the certificate-based authentication.
    ModifyCertificateBasedAuthProperties
-> Maybe CertificateBasedAuthProperties
certificateBasedAuthProperties :: Prelude.Maybe CertificateBasedAuthProperties,
    -- | The properties of the certificate-based authentication you want to
    -- delete.
    ModifyCertificateBasedAuthProperties
-> Maybe [DeletableCertificateBasedAuthProperty]
propertiesToDelete :: Prelude.Maybe [DeletableCertificateBasedAuthProperty],
    -- | The resource identifiers, in the form of directory IDs.
    ModifyCertificateBasedAuthProperties -> Text
resourceId :: Prelude.Text
  }
  deriving (ModifyCertificateBasedAuthProperties
-> ModifyCertificateBasedAuthProperties -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifyCertificateBasedAuthProperties
-> ModifyCertificateBasedAuthProperties -> Bool
$c/= :: ModifyCertificateBasedAuthProperties
-> ModifyCertificateBasedAuthProperties -> Bool
== :: ModifyCertificateBasedAuthProperties
-> ModifyCertificateBasedAuthProperties -> Bool
$c== :: ModifyCertificateBasedAuthProperties
-> ModifyCertificateBasedAuthProperties -> Bool
Prelude.Eq, ReadPrec [ModifyCertificateBasedAuthProperties]
ReadPrec ModifyCertificateBasedAuthProperties
Int -> ReadS ModifyCertificateBasedAuthProperties
ReadS [ModifyCertificateBasedAuthProperties]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifyCertificateBasedAuthProperties]
$creadListPrec :: ReadPrec [ModifyCertificateBasedAuthProperties]
readPrec :: ReadPrec ModifyCertificateBasedAuthProperties
$creadPrec :: ReadPrec ModifyCertificateBasedAuthProperties
readList :: ReadS [ModifyCertificateBasedAuthProperties]
$creadList :: ReadS [ModifyCertificateBasedAuthProperties]
readsPrec :: Int -> ReadS ModifyCertificateBasedAuthProperties
$creadsPrec :: Int -> ReadS ModifyCertificateBasedAuthProperties
Prelude.Read, Int -> ModifyCertificateBasedAuthProperties -> ShowS
[ModifyCertificateBasedAuthProperties] -> ShowS
ModifyCertificateBasedAuthProperties -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifyCertificateBasedAuthProperties] -> ShowS
$cshowList :: [ModifyCertificateBasedAuthProperties] -> ShowS
show :: ModifyCertificateBasedAuthProperties -> String
$cshow :: ModifyCertificateBasedAuthProperties -> String
showsPrec :: Int -> ModifyCertificateBasedAuthProperties -> ShowS
$cshowsPrec :: Int -> ModifyCertificateBasedAuthProperties -> ShowS
Prelude.Show, forall x.
Rep ModifyCertificateBasedAuthProperties x
-> ModifyCertificateBasedAuthProperties
forall x.
ModifyCertificateBasedAuthProperties
-> Rep ModifyCertificateBasedAuthProperties x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ModifyCertificateBasedAuthProperties x
-> ModifyCertificateBasedAuthProperties
$cfrom :: forall x.
ModifyCertificateBasedAuthProperties
-> Rep ModifyCertificateBasedAuthProperties x
Prelude.Generic)

-- |
-- Create a value of 'ModifyCertificateBasedAuthProperties' 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:
--
-- 'certificateBasedAuthProperties', 'modifyCertificateBasedAuthProperties_certificateBasedAuthProperties' - The properties of the certificate-based authentication.
--
-- 'propertiesToDelete', 'modifyCertificateBasedAuthProperties_propertiesToDelete' - The properties of the certificate-based authentication you want to
-- delete.
--
-- 'resourceId', 'modifyCertificateBasedAuthProperties_resourceId' - The resource identifiers, in the form of directory IDs.
newModifyCertificateBasedAuthProperties ::
  -- | 'resourceId'
  Prelude.Text ->
  ModifyCertificateBasedAuthProperties
newModifyCertificateBasedAuthProperties :: Text -> ModifyCertificateBasedAuthProperties
newModifyCertificateBasedAuthProperties Text
pResourceId_ =
  ModifyCertificateBasedAuthProperties'
    { $sel:certificateBasedAuthProperties:ModifyCertificateBasedAuthProperties' :: Maybe CertificateBasedAuthProperties
certificateBasedAuthProperties =
        forall a. Maybe a
Prelude.Nothing,
      $sel:propertiesToDelete:ModifyCertificateBasedAuthProperties' :: Maybe [DeletableCertificateBasedAuthProperty]
propertiesToDelete = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceId:ModifyCertificateBasedAuthProperties' :: Text
resourceId = Text
pResourceId_
    }

-- | The properties of the certificate-based authentication.
modifyCertificateBasedAuthProperties_certificateBasedAuthProperties :: Lens.Lens' ModifyCertificateBasedAuthProperties (Prelude.Maybe CertificateBasedAuthProperties)
modifyCertificateBasedAuthProperties_certificateBasedAuthProperties :: Lens'
  ModifyCertificateBasedAuthProperties
  (Maybe CertificateBasedAuthProperties)
modifyCertificateBasedAuthProperties_certificateBasedAuthProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyCertificateBasedAuthProperties' {Maybe CertificateBasedAuthProperties
certificateBasedAuthProperties :: Maybe CertificateBasedAuthProperties
$sel:certificateBasedAuthProperties:ModifyCertificateBasedAuthProperties' :: ModifyCertificateBasedAuthProperties
-> Maybe CertificateBasedAuthProperties
certificateBasedAuthProperties} -> Maybe CertificateBasedAuthProperties
certificateBasedAuthProperties) (\s :: ModifyCertificateBasedAuthProperties
s@ModifyCertificateBasedAuthProperties' {} Maybe CertificateBasedAuthProperties
a -> ModifyCertificateBasedAuthProperties
s {$sel:certificateBasedAuthProperties:ModifyCertificateBasedAuthProperties' :: Maybe CertificateBasedAuthProperties
certificateBasedAuthProperties = Maybe CertificateBasedAuthProperties
a} :: ModifyCertificateBasedAuthProperties)

-- | The properties of the certificate-based authentication you want to
-- delete.
modifyCertificateBasedAuthProperties_propertiesToDelete :: Lens.Lens' ModifyCertificateBasedAuthProperties (Prelude.Maybe [DeletableCertificateBasedAuthProperty])
modifyCertificateBasedAuthProperties_propertiesToDelete :: Lens'
  ModifyCertificateBasedAuthProperties
  (Maybe [DeletableCertificateBasedAuthProperty])
modifyCertificateBasedAuthProperties_propertiesToDelete = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyCertificateBasedAuthProperties' {Maybe [DeletableCertificateBasedAuthProperty]
propertiesToDelete :: Maybe [DeletableCertificateBasedAuthProperty]
$sel:propertiesToDelete:ModifyCertificateBasedAuthProperties' :: ModifyCertificateBasedAuthProperties
-> Maybe [DeletableCertificateBasedAuthProperty]
propertiesToDelete} -> Maybe [DeletableCertificateBasedAuthProperty]
propertiesToDelete) (\s :: ModifyCertificateBasedAuthProperties
s@ModifyCertificateBasedAuthProperties' {} Maybe [DeletableCertificateBasedAuthProperty]
a -> ModifyCertificateBasedAuthProperties
s {$sel:propertiesToDelete:ModifyCertificateBasedAuthProperties' :: Maybe [DeletableCertificateBasedAuthProperty]
propertiesToDelete = Maybe [DeletableCertificateBasedAuthProperty]
a} :: ModifyCertificateBasedAuthProperties) 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 resource identifiers, in the form of directory IDs.
modifyCertificateBasedAuthProperties_resourceId :: Lens.Lens' ModifyCertificateBasedAuthProperties Prelude.Text
modifyCertificateBasedAuthProperties_resourceId :: Lens' ModifyCertificateBasedAuthProperties Text
modifyCertificateBasedAuthProperties_resourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyCertificateBasedAuthProperties' {Text
resourceId :: Text
$sel:resourceId:ModifyCertificateBasedAuthProperties' :: ModifyCertificateBasedAuthProperties -> Text
resourceId} -> Text
resourceId) (\s :: ModifyCertificateBasedAuthProperties
s@ModifyCertificateBasedAuthProperties' {} Text
a -> ModifyCertificateBasedAuthProperties
s {$sel:resourceId:ModifyCertificateBasedAuthProperties' :: Text
resourceId = Text
a} :: ModifyCertificateBasedAuthProperties)

instance
  Core.AWSRequest
    ModifyCertificateBasedAuthProperties
  where
  type
    AWSResponse ModifyCertificateBasedAuthProperties =
      ModifyCertificateBasedAuthPropertiesResponse
  request :: (Service -> Service)
-> ModifyCertificateBasedAuthProperties
-> Request ModifyCertificateBasedAuthProperties
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ModifyCertificateBasedAuthProperties
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse ModifyCertificateBasedAuthProperties)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> ModifyCertificateBasedAuthPropertiesResponse
ModifyCertificateBasedAuthPropertiesResponse'
            forall (f :: * -> *) a b. Functor 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
    ModifyCertificateBasedAuthProperties
  where
  hashWithSalt :: Int -> ModifyCertificateBasedAuthProperties -> Int
hashWithSalt
    Int
_salt
    ModifyCertificateBasedAuthProperties' {Maybe [DeletableCertificateBasedAuthProperty]
Maybe CertificateBasedAuthProperties
Text
resourceId :: Text
propertiesToDelete :: Maybe [DeletableCertificateBasedAuthProperty]
certificateBasedAuthProperties :: Maybe CertificateBasedAuthProperties
$sel:resourceId:ModifyCertificateBasedAuthProperties' :: ModifyCertificateBasedAuthProperties -> Text
$sel:propertiesToDelete:ModifyCertificateBasedAuthProperties' :: ModifyCertificateBasedAuthProperties
-> Maybe [DeletableCertificateBasedAuthProperty]
$sel:certificateBasedAuthProperties:ModifyCertificateBasedAuthProperties' :: ModifyCertificateBasedAuthProperties
-> Maybe CertificateBasedAuthProperties
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CertificateBasedAuthProperties
certificateBasedAuthProperties
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [DeletableCertificateBasedAuthProperty]
propertiesToDelete
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceId

instance
  Prelude.NFData
    ModifyCertificateBasedAuthProperties
  where
  rnf :: ModifyCertificateBasedAuthProperties -> ()
rnf ModifyCertificateBasedAuthProperties' {Maybe [DeletableCertificateBasedAuthProperty]
Maybe CertificateBasedAuthProperties
Text
resourceId :: Text
propertiesToDelete :: Maybe [DeletableCertificateBasedAuthProperty]
certificateBasedAuthProperties :: Maybe CertificateBasedAuthProperties
$sel:resourceId:ModifyCertificateBasedAuthProperties' :: ModifyCertificateBasedAuthProperties -> Text
$sel:propertiesToDelete:ModifyCertificateBasedAuthProperties' :: ModifyCertificateBasedAuthProperties
-> Maybe [DeletableCertificateBasedAuthProperty]
$sel:certificateBasedAuthProperties:ModifyCertificateBasedAuthProperties' :: ModifyCertificateBasedAuthProperties
-> Maybe CertificateBasedAuthProperties
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CertificateBasedAuthProperties
certificateBasedAuthProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [DeletableCertificateBasedAuthProperty]
propertiesToDelete
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
resourceId

instance
  Data.ToHeaders
    ModifyCertificateBasedAuthProperties
  where
  toHeaders :: ModifyCertificateBasedAuthProperties -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"WorkspacesService.ModifyCertificateBasedAuthProperties" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance
  Data.ToJSON
    ModifyCertificateBasedAuthProperties
  where
  toJSON :: ModifyCertificateBasedAuthProperties -> Value
toJSON ModifyCertificateBasedAuthProperties' {Maybe [DeletableCertificateBasedAuthProperty]
Maybe CertificateBasedAuthProperties
Text
resourceId :: Text
propertiesToDelete :: Maybe [DeletableCertificateBasedAuthProperty]
certificateBasedAuthProperties :: Maybe CertificateBasedAuthProperties
$sel:resourceId:ModifyCertificateBasedAuthProperties' :: ModifyCertificateBasedAuthProperties -> Text
$sel:propertiesToDelete:ModifyCertificateBasedAuthProperties' :: ModifyCertificateBasedAuthProperties
-> Maybe [DeletableCertificateBasedAuthProperty]
$sel:certificateBasedAuthProperties:ModifyCertificateBasedAuthProperties' :: ModifyCertificateBasedAuthProperties
-> Maybe CertificateBasedAuthProperties
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"CertificateBasedAuthProperties" 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 CertificateBasedAuthProperties
certificateBasedAuthProperties,
            (Key
"PropertiesToDelete" 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 [DeletableCertificateBasedAuthProperty]
propertiesToDelete,
            forall a. a -> Maybe a
Prelude.Just (Key
"ResourceId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
resourceId)
          ]
      )

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

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

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

-- |
-- Create a value of 'ModifyCertificateBasedAuthPropertiesResponse' 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:
--
-- 'httpStatus', 'modifyCertificateBasedAuthPropertiesResponse_httpStatus' - The response's http status code.
newModifyCertificateBasedAuthPropertiesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ModifyCertificateBasedAuthPropertiesResponse
newModifyCertificateBasedAuthPropertiesResponse :: Int -> ModifyCertificateBasedAuthPropertiesResponse
newModifyCertificateBasedAuthPropertiesResponse
  Int
pHttpStatus_ =
    ModifyCertificateBasedAuthPropertiesResponse'
      { $sel:httpStatus:ModifyCertificateBasedAuthPropertiesResponse' :: Int
httpStatus =
          Int
pHttpStatus_
      }

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

instance
  Prelude.NFData
    ModifyCertificateBasedAuthPropertiesResponse
  where
  rnf :: ModifyCertificateBasedAuthPropertiesResponse -> ()
rnf ModifyCertificateBasedAuthPropertiesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ModifyCertificateBasedAuthPropertiesResponse' :: ModifyCertificateBasedAuthPropertiesResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus