{-# 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.LicenseManager.UpdateLicenseSpecificationsForResource
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Adds or removes the specified license configurations for the specified
-- Amazon Web Services resource.
--
-- You can update the license specifications of AMIs, instances, and hosts.
-- You cannot update the license specifications for launch templates and
-- CloudFormation templates, as they send license configurations to the
-- operation that creates the resource.
module Amazonka.LicenseManager.UpdateLicenseSpecificationsForResource
  ( -- * Creating a Request
    UpdateLicenseSpecificationsForResource (..),
    newUpdateLicenseSpecificationsForResource,

    -- * Request Lenses
    updateLicenseSpecificationsForResource_addLicenseSpecifications,
    updateLicenseSpecificationsForResource_removeLicenseSpecifications,
    updateLicenseSpecificationsForResource_resourceArn,

    -- * Destructuring the Response
    UpdateLicenseSpecificationsForResourceResponse (..),
    newUpdateLicenseSpecificationsForResourceResponse,

    -- * Response Lenses
    updateLicenseSpecificationsForResourceResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateLicenseSpecificationsForResource' smart constructor.
data UpdateLicenseSpecificationsForResource = UpdateLicenseSpecificationsForResource'
  { -- | ARNs of the license configurations to add.
    UpdateLicenseSpecificationsForResource
-> Maybe [LicenseSpecification]
addLicenseSpecifications :: Prelude.Maybe [LicenseSpecification],
    -- | ARNs of the license configurations to remove.
    UpdateLicenseSpecificationsForResource
-> Maybe [LicenseSpecification]
removeLicenseSpecifications :: Prelude.Maybe [LicenseSpecification],
    -- | Amazon Resource Name (ARN) of the Amazon Web Services resource.
    UpdateLicenseSpecificationsForResource -> Text
resourceArn :: Prelude.Text
  }
  deriving (UpdateLicenseSpecificationsForResource
-> UpdateLicenseSpecificationsForResource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateLicenseSpecificationsForResource
-> UpdateLicenseSpecificationsForResource -> Bool
$c/= :: UpdateLicenseSpecificationsForResource
-> UpdateLicenseSpecificationsForResource -> Bool
== :: UpdateLicenseSpecificationsForResource
-> UpdateLicenseSpecificationsForResource -> Bool
$c== :: UpdateLicenseSpecificationsForResource
-> UpdateLicenseSpecificationsForResource -> Bool
Prelude.Eq, ReadPrec [UpdateLicenseSpecificationsForResource]
ReadPrec UpdateLicenseSpecificationsForResource
Int -> ReadS UpdateLicenseSpecificationsForResource
ReadS [UpdateLicenseSpecificationsForResource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateLicenseSpecificationsForResource]
$creadListPrec :: ReadPrec [UpdateLicenseSpecificationsForResource]
readPrec :: ReadPrec UpdateLicenseSpecificationsForResource
$creadPrec :: ReadPrec UpdateLicenseSpecificationsForResource
readList :: ReadS [UpdateLicenseSpecificationsForResource]
$creadList :: ReadS [UpdateLicenseSpecificationsForResource]
readsPrec :: Int -> ReadS UpdateLicenseSpecificationsForResource
$creadsPrec :: Int -> ReadS UpdateLicenseSpecificationsForResource
Prelude.Read, Int -> UpdateLicenseSpecificationsForResource -> ShowS
[UpdateLicenseSpecificationsForResource] -> ShowS
UpdateLicenseSpecificationsForResource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateLicenseSpecificationsForResource] -> ShowS
$cshowList :: [UpdateLicenseSpecificationsForResource] -> ShowS
show :: UpdateLicenseSpecificationsForResource -> String
$cshow :: UpdateLicenseSpecificationsForResource -> String
showsPrec :: Int -> UpdateLicenseSpecificationsForResource -> ShowS
$cshowsPrec :: Int -> UpdateLicenseSpecificationsForResource -> ShowS
Prelude.Show, forall x.
Rep UpdateLicenseSpecificationsForResource x
-> UpdateLicenseSpecificationsForResource
forall x.
UpdateLicenseSpecificationsForResource
-> Rep UpdateLicenseSpecificationsForResource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateLicenseSpecificationsForResource x
-> UpdateLicenseSpecificationsForResource
$cfrom :: forall x.
UpdateLicenseSpecificationsForResource
-> Rep UpdateLicenseSpecificationsForResource x
Prelude.Generic)

-- |
-- Create a value of 'UpdateLicenseSpecificationsForResource' 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:
--
-- 'addLicenseSpecifications', 'updateLicenseSpecificationsForResource_addLicenseSpecifications' - ARNs of the license configurations to add.
--
-- 'removeLicenseSpecifications', 'updateLicenseSpecificationsForResource_removeLicenseSpecifications' - ARNs of the license configurations to remove.
--
-- 'resourceArn', 'updateLicenseSpecificationsForResource_resourceArn' - Amazon Resource Name (ARN) of the Amazon Web Services resource.
newUpdateLicenseSpecificationsForResource ::
  -- | 'resourceArn'
  Prelude.Text ->
  UpdateLicenseSpecificationsForResource
newUpdateLicenseSpecificationsForResource :: Text -> UpdateLicenseSpecificationsForResource
newUpdateLicenseSpecificationsForResource
  Text
pResourceArn_ =
    UpdateLicenseSpecificationsForResource'
      { $sel:addLicenseSpecifications:UpdateLicenseSpecificationsForResource' :: Maybe [LicenseSpecification]
addLicenseSpecifications =
          forall a. Maybe a
Prelude.Nothing,
        $sel:removeLicenseSpecifications:UpdateLicenseSpecificationsForResource' :: Maybe [LicenseSpecification]
removeLicenseSpecifications =
          forall a. Maybe a
Prelude.Nothing,
        $sel:resourceArn:UpdateLicenseSpecificationsForResource' :: Text
resourceArn = Text
pResourceArn_
      }

-- | ARNs of the license configurations to add.
updateLicenseSpecificationsForResource_addLicenseSpecifications :: Lens.Lens' UpdateLicenseSpecificationsForResource (Prelude.Maybe [LicenseSpecification])
updateLicenseSpecificationsForResource_addLicenseSpecifications :: Lens'
  UpdateLicenseSpecificationsForResource
  (Maybe [LicenseSpecification])
updateLicenseSpecificationsForResource_addLicenseSpecifications = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateLicenseSpecificationsForResource' {Maybe [LicenseSpecification]
addLicenseSpecifications :: Maybe [LicenseSpecification]
$sel:addLicenseSpecifications:UpdateLicenseSpecificationsForResource' :: UpdateLicenseSpecificationsForResource
-> Maybe [LicenseSpecification]
addLicenseSpecifications} -> Maybe [LicenseSpecification]
addLicenseSpecifications) (\s :: UpdateLicenseSpecificationsForResource
s@UpdateLicenseSpecificationsForResource' {} Maybe [LicenseSpecification]
a -> UpdateLicenseSpecificationsForResource
s {$sel:addLicenseSpecifications:UpdateLicenseSpecificationsForResource' :: Maybe [LicenseSpecification]
addLicenseSpecifications = Maybe [LicenseSpecification]
a} :: UpdateLicenseSpecificationsForResource) 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

-- | ARNs of the license configurations to remove.
updateLicenseSpecificationsForResource_removeLicenseSpecifications :: Lens.Lens' UpdateLicenseSpecificationsForResource (Prelude.Maybe [LicenseSpecification])
updateLicenseSpecificationsForResource_removeLicenseSpecifications :: Lens'
  UpdateLicenseSpecificationsForResource
  (Maybe [LicenseSpecification])
updateLicenseSpecificationsForResource_removeLicenseSpecifications = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateLicenseSpecificationsForResource' {Maybe [LicenseSpecification]
removeLicenseSpecifications :: Maybe [LicenseSpecification]
$sel:removeLicenseSpecifications:UpdateLicenseSpecificationsForResource' :: UpdateLicenseSpecificationsForResource
-> Maybe [LicenseSpecification]
removeLicenseSpecifications} -> Maybe [LicenseSpecification]
removeLicenseSpecifications) (\s :: UpdateLicenseSpecificationsForResource
s@UpdateLicenseSpecificationsForResource' {} Maybe [LicenseSpecification]
a -> UpdateLicenseSpecificationsForResource
s {$sel:removeLicenseSpecifications:UpdateLicenseSpecificationsForResource' :: Maybe [LicenseSpecification]
removeLicenseSpecifications = Maybe [LicenseSpecification]
a} :: UpdateLicenseSpecificationsForResource) 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

-- | Amazon Resource Name (ARN) of the Amazon Web Services resource.
updateLicenseSpecificationsForResource_resourceArn :: Lens.Lens' UpdateLicenseSpecificationsForResource Prelude.Text
updateLicenseSpecificationsForResource_resourceArn :: Lens' UpdateLicenseSpecificationsForResource Text
updateLicenseSpecificationsForResource_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateLicenseSpecificationsForResource' {Text
resourceArn :: Text
$sel:resourceArn:UpdateLicenseSpecificationsForResource' :: UpdateLicenseSpecificationsForResource -> Text
resourceArn} -> Text
resourceArn) (\s :: UpdateLicenseSpecificationsForResource
s@UpdateLicenseSpecificationsForResource' {} Text
a -> UpdateLicenseSpecificationsForResource
s {$sel:resourceArn:UpdateLicenseSpecificationsForResource' :: Text
resourceArn = Text
a} :: UpdateLicenseSpecificationsForResource)

instance
  Core.AWSRequest
    UpdateLicenseSpecificationsForResource
  where
  type
    AWSResponse
      UpdateLicenseSpecificationsForResource =
      UpdateLicenseSpecificationsForResourceResponse
  request :: (Service -> Service)
-> UpdateLicenseSpecificationsForResource
-> Request UpdateLicenseSpecificationsForResource
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 UpdateLicenseSpecificationsForResource
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse UpdateLicenseSpecificationsForResource)))
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 -> UpdateLicenseSpecificationsForResourceResponse
UpdateLicenseSpecificationsForResourceResponse'
            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
    UpdateLicenseSpecificationsForResource
  where
  hashWithSalt :: Int -> UpdateLicenseSpecificationsForResource -> Int
hashWithSalt
    Int
_salt
    UpdateLicenseSpecificationsForResource' {Maybe [LicenseSpecification]
Text
resourceArn :: Text
removeLicenseSpecifications :: Maybe [LicenseSpecification]
addLicenseSpecifications :: Maybe [LicenseSpecification]
$sel:resourceArn:UpdateLicenseSpecificationsForResource' :: UpdateLicenseSpecificationsForResource -> Text
$sel:removeLicenseSpecifications:UpdateLicenseSpecificationsForResource' :: UpdateLicenseSpecificationsForResource
-> Maybe [LicenseSpecification]
$sel:addLicenseSpecifications:UpdateLicenseSpecificationsForResource' :: UpdateLicenseSpecificationsForResource
-> Maybe [LicenseSpecification]
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [LicenseSpecification]
addLicenseSpecifications
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [LicenseSpecification]
removeLicenseSpecifications
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceArn

instance
  Prelude.NFData
    UpdateLicenseSpecificationsForResource
  where
  rnf :: UpdateLicenseSpecificationsForResource -> ()
rnf UpdateLicenseSpecificationsForResource' {Maybe [LicenseSpecification]
Text
resourceArn :: Text
removeLicenseSpecifications :: Maybe [LicenseSpecification]
addLicenseSpecifications :: Maybe [LicenseSpecification]
$sel:resourceArn:UpdateLicenseSpecificationsForResource' :: UpdateLicenseSpecificationsForResource -> Text
$sel:removeLicenseSpecifications:UpdateLicenseSpecificationsForResource' :: UpdateLicenseSpecificationsForResource
-> Maybe [LicenseSpecification]
$sel:addLicenseSpecifications:UpdateLicenseSpecificationsForResource' :: UpdateLicenseSpecificationsForResource
-> Maybe [LicenseSpecification]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [LicenseSpecification]
addLicenseSpecifications
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [LicenseSpecification]
removeLicenseSpecifications
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
resourceArn

instance
  Data.ToHeaders
    UpdateLicenseSpecificationsForResource
  where
  toHeaders :: UpdateLicenseSpecificationsForResource -> 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
"AWSLicenseManager.UpdateLicenseSpecificationsForResource" ::
                          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
    UpdateLicenseSpecificationsForResource
  where
  toJSON :: UpdateLicenseSpecificationsForResource -> Value
toJSON UpdateLicenseSpecificationsForResource' {Maybe [LicenseSpecification]
Text
resourceArn :: Text
removeLicenseSpecifications :: Maybe [LicenseSpecification]
addLicenseSpecifications :: Maybe [LicenseSpecification]
$sel:resourceArn:UpdateLicenseSpecificationsForResource' :: UpdateLicenseSpecificationsForResource -> Text
$sel:removeLicenseSpecifications:UpdateLicenseSpecificationsForResource' :: UpdateLicenseSpecificationsForResource
-> Maybe [LicenseSpecification]
$sel:addLicenseSpecifications:UpdateLicenseSpecificationsForResource' :: UpdateLicenseSpecificationsForResource
-> Maybe [LicenseSpecification]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AddLicenseSpecifications" 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 [LicenseSpecification]
addLicenseSpecifications,
            (Key
"RemoveLicenseSpecifications" 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 [LicenseSpecification]
removeLicenseSpecifications,
            forall a. a -> Maybe a
Prelude.Just (Key
"ResourceArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
resourceArn)
          ]
      )

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

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

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

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

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

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