{-# 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.ServiceCatalog.UpdateProvisionedProductProperties
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Requests updates to the properties of the specified provisioned product.
module Amazonka.ServiceCatalog.UpdateProvisionedProductProperties
  ( -- * Creating a Request
    UpdateProvisionedProductProperties (..),
    newUpdateProvisionedProductProperties,

    -- * Request Lenses
    updateProvisionedProductProperties_acceptLanguage,
    updateProvisionedProductProperties_provisionedProductId,
    updateProvisionedProductProperties_provisionedProductProperties,
    updateProvisionedProductProperties_idempotencyToken,

    -- * Destructuring the Response
    UpdateProvisionedProductPropertiesResponse (..),
    newUpdateProvisionedProductPropertiesResponse,

    -- * Response Lenses
    updateProvisionedProductPropertiesResponse_provisionedProductId,
    updateProvisionedProductPropertiesResponse_provisionedProductProperties,
    updateProvisionedProductPropertiesResponse_recordId,
    updateProvisionedProductPropertiesResponse_status,
    updateProvisionedProductPropertiesResponse_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.ServiceCatalog.Types

-- | /See:/ 'newUpdateProvisionedProductProperties' smart constructor.
data UpdateProvisionedProductProperties = UpdateProvisionedProductProperties'
  { -- | The language code.
    --
    -- -   @en@ - English (default)
    --
    -- -   @jp@ - Japanese
    --
    -- -   @zh@ - Chinese
    UpdateProvisionedProductProperties -> Maybe Text
acceptLanguage :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the provisioned product.
    UpdateProvisionedProductProperties -> Text
provisionedProductId :: Prelude.Text,
    -- | A map that contains the provisioned product properties to be updated.
    --
    -- The @LAUNCH_ROLE@ key accepts role ARNs. This key allows an
    -- administrator to call @UpdateProvisionedProductProperties@ to update the
    -- launch role that is associated with a provisioned product. This role is
    -- used when an end user calls a provisioning operation such as
    -- @UpdateProvisionedProduct@, @TerminateProvisionedProduct@, or
    -- @ExecuteProvisionedProductServiceAction@. Only a role ARN is valid. A
    -- user ARN is invalid.
    --
    -- The @OWNER@ key accepts IAM user ARNs, IAM role ARNs, and STS
    -- assumed-role ARNs. The owner is the user that has permission to see,
    -- update, terminate, and execute service actions in the provisioned
    -- product.
    --
    -- The administrator can change the owner of a provisioned product to
    -- another IAM or STS entity within the same account. Both end user owners
    -- and administrators can see ownership history of the provisioned product
    -- using the @ListRecordHistory@ API. The new owner can describe all past
    -- records for the provisioned product using the @DescribeRecord@ API. The
    -- previous owner can no longer use @DescribeRecord@, but can still see the
    -- product\'s history from when he was an owner using @ListRecordHistory@.
    --
    -- If a provisioned product ownership is assigned to an end user, they can
    -- see and perform any action through the API or Service Catalog console
    -- such as update, terminate, and execute service actions. If an end user
    -- provisions a product and the owner is updated to someone else, they will
    -- no longer be able to see or perform any actions through API or the
    -- Service Catalog console on that provisioned product.
    UpdateProvisionedProductProperties -> HashMap PropertyKey Text
provisionedProductProperties :: Prelude.HashMap PropertyKey Prelude.Text,
    -- | The idempotency token that uniquely identifies the provisioning product
    -- update request.
    UpdateProvisionedProductProperties -> Text
idempotencyToken :: Prelude.Text
  }
  deriving (UpdateProvisionedProductProperties
-> UpdateProvisionedProductProperties -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateProvisionedProductProperties
-> UpdateProvisionedProductProperties -> Bool
$c/= :: UpdateProvisionedProductProperties
-> UpdateProvisionedProductProperties -> Bool
== :: UpdateProvisionedProductProperties
-> UpdateProvisionedProductProperties -> Bool
$c== :: UpdateProvisionedProductProperties
-> UpdateProvisionedProductProperties -> Bool
Prelude.Eq, ReadPrec [UpdateProvisionedProductProperties]
ReadPrec UpdateProvisionedProductProperties
Int -> ReadS UpdateProvisionedProductProperties
ReadS [UpdateProvisionedProductProperties]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateProvisionedProductProperties]
$creadListPrec :: ReadPrec [UpdateProvisionedProductProperties]
readPrec :: ReadPrec UpdateProvisionedProductProperties
$creadPrec :: ReadPrec UpdateProvisionedProductProperties
readList :: ReadS [UpdateProvisionedProductProperties]
$creadList :: ReadS [UpdateProvisionedProductProperties]
readsPrec :: Int -> ReadS UpdateProvisionedProductProperties
$creadsPrec :: Int -> ReadS UpdateProvisionedProductProperties
Prelude.Read, Int -> UpdateProvisionedProductProperties -> ShowS
[UpdateProvisionedProductProperties] -> ShowS
UpdateProvisionedProductProperties -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateProvisionedProductProperties] -> ShowS
$cshowList :: [UpdateProvisionedProductProperties] -> ShowS
show :: UpdateProvisionedProductProperties -> String
$cshow :: UpdateProvisionedProductProperties -> String
showsPrec :: Int -> UpdateProvisionedProductProperties -> ShowS
$cshowsPrec :: Int -> UpdateProvisionedProductProperties -> ShowS
Prelude.Show, forall x.
Rep UpdateProvisionedProductProperties x
-> UpdateProvisionedProductProperties
forall x.
UpdateProvisionedProductProperties
-> Rep UpdateProvisionedProductProperties x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateProvisionedProductProperties x
-> UpdateProvisionedProductProperties
$cfrom :: forall x.
UpdateProvisionedProductProperties
-> Rep UpdateProvisionedProductProperties x
Prelude.Generic)

-- |
-- Create a value of 'UpdateProvisionedProductProperties' 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:
--
-- 'acceptLanguage', 'updateProvisionedProductProperties_acceptLanguage' - The language code.
--
-- -   @en@ - English (default)
--
-- -   @jp@ - Japanese
--
-- -   @zh@ - Chinese
--
-- 'provisionedProductId', 'updateProvisionedProductProperties_provisionedProductId' - The identifier of the provisioned product.
--
-- 'provisionedProductProperties', 'updateProvisionedProductProperties_provisionedProductProperties' - A map that contains the provisioned product properties to be updated.
--
-- The @LAUNCH_ROLE@ key accepts role ARNs. This key allows an
-- administrator to call @UpdateProvisionedProductProperties@ to update the
-- launch role that is associated with a provisioned product. This role is
-- used when an end user calls a provisioning operation such as
-- @UpdateProvisionedProduct@, @TerminateProvisionedProduct@, or
-- @ExecuteProvisionedProductServiceAction@. Only a role ARN is valid. A
-- user ARN is invalid.
--
-- The @OWNER@ key accepts IAM user ARNs, IAM role ARNs, and STS
-- assumed-role ARNs. The owner is the user that has permission to see,
-- update, terminate, and execute service actions in the provisioned
-- product.
--
-- The administrator can change the owner of a provisioned product to
-- another IAM or STS entity within the same account. Both end user owners
-- and administrators can see ownership history of the provisioned product
-- using the @ListRecordHistory@ API. The new owner can describe all past
-- records for the provisioned product using the @DescribeRecord@ API. The
-- previous owner can no longer use @DescribeRecord@, but can still see the
-- product\'s history from when he was an owner using @ListRecordHistory@.
--
-- If a provisioned product ownership is assigned to an end user, they can
-- see and perform any action through the API or Service Catalog console
-- such as update, terminate, and execute service actions. If an end user
-- provisions a product and the owner is updated to someone else, they will
-- no longer be able to see or perform any actions through API or the
-- Service Catalog console on that provisioned product.
--
-- 'idempotencyToken', 'updateProvisionedProductProperties_idempotencyToken' - The idempotency token that uniquely identifies the provisioning product
-- update request.
newUpdateProvisionedProductProperties ::
  -- | 'provisionedProductId'
  Prelude.Text ->
  -- | 'idempotencyToken'
  Prelude.Text ->
  UpdateProvisionedProductProperties
newUpdateProvisionedProductProperties :: Text -> Text -> UpdateProvisionedProductProperties
newUpdateProvisionedProductProperties
  Text
pProvisionedProductId_
  Text
pIdempotencyToken_ =
    UpdateProvisionedProductProperties'
      { $sel:acceptLanguage:UpdateProvisionedProductProperties' :: Maybe Text
acceptLanguage =
          forall a. Maybe a
Prelude.Nothing,
        $sel:provisionedProductId:UpdateProvisionedProductProperties' :: Text
provisionedProductId =
          Text
pProvisionedProductId_,
        $sel:provisionedProductProperties:UpdateProvisionedProductProperties' :: HashMap PropertyKey Text
provisionedProductProperties =
          forall a. Monoid a => a
Prelude.mempty,
        $sel:idempotencyToken:UpdateProvisionedProductProperties' :: Text
idempotencyToken = Text
pIdempotencyToken_
      }

-- | The language code.
--
-- -   @en@ - English (default)
--
-- -   @jp@ - Japanese
--
-- -   @zh@ - Chinese
updateProvisionedProductProperties_acceptLanguage :: Lens.Lens' UpdateProvisionedProductProperties (Prelude.Maybe Prelude.Text)
updateProvisionedProductProperties_acceptLanguage :: Lens' UpdateProvisionedProductProperties (Maybe Text)
updateProvisionedProductProperties_acceptLanguage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProvisionedProductProperties' {Maybe Text
acceptLanguage :: Maybe Text
$sel:acceptLanguage:UpdateProvisionedProductProperties' :: UpdateProvisionedProductProperties -> Maybe Text
acceptLanguage} -> Maybe Text
acceptLanguage) (\s :: UpdateProvisionedProductProperties
s@UpdateProvisionedProductProperties' {} Maybe Text
a -> UpdateProvisionedProductProperties
s {$sel:acceptLanguage:UpdateProvisionedProductProperties' :: Maybe Text
acceptLanguage = Maybe Text
a} :: UpdateProvisionedProductProperties)

-- | The identifier of the provisioned product.
updateProvisionedProductProperties_provisionedProductId :: Lens.Lens' UpdateProvisionedProductProperties Prelude.Text
updateProvisionedProductProperties_provisionedProductId :: Lens' UpdateProvisionedProductProperties Text
updateProvisionedProductProperties_provisionedProductId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProvisionedProductProperties' {Text
provisionedProductId :: Text
$sel:provisionedProductId:UpdateProvisionedProductProperties' :: UpdateProvisionedProductProperties -> Text
provisionedProductId} -> Text
provisionedProductId) (\s :: UpdateProvisionedProductProperties
s@UpdateProvisionedProductProperties' {} Text
a -> UpdateProvisionedProductProperties
s {$sel:provisionedProductId:UpdateProvisionedProductProperties' :: Text
provisionedProductId = Text
a} :: UpdateProvisionedProductProperties)

-- | A map that contains the provisioned product properties to be updated.
--
-- The @LAUNCH_ROLE@ key accepts role ARNs. This key allows an
-- administrator to call @UpdateProvisionedProductProperties@ to update the
-- launch role that is associated with a provisioned product. This role is
-- used when an end user calls a provisioning operation such as
-- @UpdateProvisionedProduct@, @TerminateProvisionedProduct@, or
-- @ExecuteProvisionedProductServiceAction@. Only a role ARN is valid. A
-- user ARN is invalid.
--
-- The @OWNER@ key accepts IAM user ARNs, IAM role ARNs, and STS
-- assumed-role ARNs. The owner is the user that has permission to see,
-- update, terminate, and execute service actions in the provisioned
-- product.
--
-- The administrator can change the owner of a provisioned product to
-- another IAM or STS entity within the same account. Both end user owners
-- and administrators can see ownership history of the provisioned product
-- using the @ListRecordHistory@ API. The new owner can describe all past
-- records for the provisioned product using the @DescribeRecord@ API. The
-- previous owner can no longer use @DescribeRecord@, but can still see the
-- product\'s history from when he was an owner using @ListRecordHistory@.
--
-- If a provisioned product ownership is assigned to an end user, they can
-- see and perform any action through the API or Service Catalog console
-- such as update, terminate, and execute service actions. If an end user
-- provisions a product and the owner is updated to someone else, they will
-- no longer be able to see or perform any actions through API or the
-- Service Catalog console on that provisioned product.
updateProvisionedProductProperties_provisionedProductProperties :: Lens.Lens' UpdateProvisionedProductProperties (Prelude.HashMap PropertyKey Prelude.Text)
updateProvisionedProductProperties_provisionedProductProperties :: Lens' UpdateProvisionedProductProperties (HashMap PropertyKey Text)
updateProvisionedProductProperties_provisionedProductProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProvisionedProductProperties' {HashMap PropertyKey Text
provisionedProductProperties :: HashMap PropertyKey Text
$sel:provisionedProductProperties:UpdateProvisionedProductProperties' :: UpdateProvisionedProductProperties -> HashMap PropertyKey Text
provisionedProductProperties} -> HashMap PropertyKey Text
provisionedProductProperties) (\s :: UpdateProvisionedProductProperties
s@UpdateProvisionedProductProperties' {} HashMap PropertyKey Text
a -> UpdateProvisionedProductProperties
s {$sel:provisionedProductProperties:UpdateProvisionedProductProperties' :: HashMap PropertyKey Text
provisionedProductProperties = HashMap PropertyKey Text
a} :: UpdateProvisionedProductProperties) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The idempotency token that uniquely identifies the provisioning product
-- update request.
updateProvisionedProductProperties_idempotencyToken :: Lens.Lens' UpdateProvisionedProductProperties Prelude.Text
updateProvisionedProductProperties_idempotencyToken :: Lens' UpdateProvisionedProductProperties Text
updateProvisionedProductProperties_idempotencyToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProvisionedProductProperties' {Text
idempotencyToken :: Text
$sel:idempotencyToken:UpdateProvisionedProductProperties' :: UpdateProvisionedProductProperties -> Text
idempotencyToken} -> Text
idempotencyToken) (\s :: UpdateProvisionedProductProperties
s@UpdateProvisionedProductProperties' {} Text
a -> UpdateProvisionedProductProperties
s {$sel:idempotencyToken:UpdateProvisionedProductProperties' :: Text
idempotencyToken = Text
a} :: UpdateProvisionedProductProperties)

instance
  Core.AWSRequest
    UpdateProvisionedProductProperties
  where
  type
    AWSResponse UpdateProvisionedProductProperties =
      UpdateProvisionedProductPropertiesResponse
  request :: (Service -> Service)
-> UpdateProvisionedProductProperties
-> Request UpdateProvisionedProductProperties
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 UpdateProvisionedProductProperties
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse UpdateProvisionedProductProperties)))
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 (HashMap PropertyKey Text)
-> Maybe Text
-> Maybe RecordStatus
-> Int
-> UpdateProvisionedProductPropertiesResponse
UpdateProvisionedProductPropertiesResponse'
            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
"ProvisionedProductId")
            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
"ProvisionedProductProperties"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            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
"RecordId")
            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
"Status")
            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
    UpdateProvisionedProductProperties
  where
  hashWithSalt :: Int -> UpdateProvisionedProductProperties -> Int
hashWithSalt
    Int
_salt
    UpdateProvisionedProductProperties' {Maybe Text
Text
HashMap PropertyKey Text
idempotencyToken :: Text
provisionedProductProperties :: HashMap PropertyKey Text
provisionedProductId :: Text
acceptLanguage :: Maybe Text
$sel:idempotencyToken:UpdateProvisionedProductProperties' :: UpdateProvisionedProductProperties -> Text
$sel:provisionedProductProperties:UpdateProvisionedProductProperties' :: UpdateProvisionedProductProperties -> HashMap PropertyKey Text
$sel:provisionedProductId:UpdateProvisionedProductProperties' :: UpdateProvisionedProductProperties -> Text
$sel:acceptLanguage:UpdateProvisionedProductProperties' :: UpdateProvisionedProductProperties -> Maybe Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
acceptLanguage
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
provisionedProductId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` HashMap PropertyKey Text
provisionedProductProperties
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
idempotencyToken

instance
  Prelude.NFData
    UpdateProvisionedProductProperties
  where
  rnf :: UpdateProvisionedProductProperties -> ()
rnf UpdateProvisionedProductProperties' {Maybe Text
Text
HashMap PropertyKey Text
idempotencyToken :: Text
provisionedProductProperties :: HashMap PropertyKey Text
provisionedProductId :: Text
acceptLanguage :: Maybe Text
$sel:idempotencyToken:UpdateProvisionedProductProperties' :: UpdateProvisionedProductProperties -> Text
$sel:provisionedProductProperties:UpdateProvisionedProductProperties' :: UpdateProvisionedProductProperties -> HashMap PropertyKey Text
$sel:provisionedProductId:UpdateProvisionedProductProperties' :: UpdateProvisionedProductProperties -> Text
$sel:acceptLanguage:UpdateProvisionedProductProperties' :: UpdateProvisionedProductProperties -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
acceptLanguage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
provisionedProductId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf HashMap PropertyKey Text
provisionedProductProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
idempotencyToken

instance
  Data.ToHeaders
    UpdateProvisionedProductProperties
  where
  toHeaders :: UpdateProvisionedProductProperties -> 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
"AWS242ServiceCatalogService.UpdateProvisionedProductProperties" ::
                          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
    UpdateProvisionedProductProperties
  where
  toJSON :: UpdateProvisionedProductProperties -> Value
toJSON UpdateProvisionedProductProperties' {Maybe Text
Text
HashMap PropertyKey Text
idempotencyToken :: Text
provisionedProductProperties :: HashMap PropertyKey Text
provisionedProductId :: Text
acceptLanguage :: Maybe Text
$sel:idempotencyToken:UpdateProvisionedProductProperties' :: UpdateProvisionedProductProperties -> Text
$sel:provisionedProductProperties:UpdateProvisionedProductProperties' :: UpdateProvisionedProductProperties -> HashMap PropertyKey Text
$sel:provisionedProductId:UpdateProvisionedProductProperties' :: UpdateProvisionedProductProperties -> Text
$sel:acceptLanguage:UpdateProvisionedProductProperties' :: UpdateProvisionedProductProperties -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AcceptLanguage" 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
acceptLanguage,
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"ProvisionedProductId"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
provisionedProductId
              ),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"ProvisionedProductProperties"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= HashMap PropertyKey Text
provisionedProductProperties
              ),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"IdempotencyToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
idempotencyToken)
          ]
      )

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

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

-- | /See:/ 'newUpdateProvisionedProductPropertiesResponse' smart constructor.
data UpdateProvisionedProductPropertiesResponse = UpdateProvisionedProductPropertiesResponse'
  { -- | The provisioned product identifier.
    UpdateProvisionedProductPropertiesResponse -> Maybe Text
provisionedProductId :: Prelude.Maybe Prelude.Text,
    -- | A map that contains the properties updated.
    UpdateProvisionedProductPropertiesResponse
-> Maybe (HashMap PropertyKey Text)
provisionedProductProperties :: Prelude.Maybe (Prelude.HashMap PropertyKey Prelude.Text),
    -- | The identifier of the record.
    UpdateProvisionedProductPropertiesResponse -> Maybe Text
recordId :: Prelude.Maybe Prelude.Text,
    -- | The status of the request.
    UpdateProvisionedProductPropertiesResponse -> Maybe RecordStatus
status :: Prelude.Maybe RecordStatus,
    -- | The response's http status code.
    UpdateProvisionedProductPropertiesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateProvisionedProductPropertiesResponse
-> UpdateProvisionedProductPropertiesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateProvisionedProductPropertiesResponse
-> UpdateProvisionedProductPropertiesResponse -> Bool
$c/= :: UpdateProvisionedProductPropertiesResponse
-> UpdateProvisionedProductPropertiesResponse -> Bool
== :: UpdateProvisionedProductPropertiesResponse
-> UpdateProvisionedProductPropertiesResponse -> Bool
$c== :: UpdateProvisionedProductPropertiesResponse
-> UpdateProvisionedProductPropertiesResponse -> Bool
Prelude.Eq, ReadPrec [UpdateProvisionedProductPropertiesResponse]
ReadPrec UpdateProvisionedProductPropertiesResponse
Int -> ReadS UpdateProvisionedProductPropertiesResponse
ReadS [UpdateProvisionedProductPropertiesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateProvisionedProductPropertiesResponse]
$creadListPrec :: ReadPrec [UpdateProvisionedProductPropertiesResponse]
readPrec :: ReadPrec UpdateProvisionedProductPropertiesResponse
$creadPrec :: ReadPrec UpdateProvisionedProductPropertiesResponse
readList :: ReadS [UpdateProvisionedProductPropertiesResponse]
$creadList :: ReadS [UpdateProvisionedProductPropertiesResponse]
readsPrec :: Int -> ReadS UpdateProvisionedProductPropertiesResponse
$creadsPrec :: Int -> ReadS UpdateProvisionedProductPropertiesResponse
Prelude.Read, Int -> UpdateProvisionedProductPropertiesResponse -> ShowS
[UpdateProvisionedProductPropertiesResponse] -> ShowS
UpdateProvisionedProductPropertiesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateProvisionedProductPropertiesResponse] -> ShowS
$cshowList :: [UpdateProvisionedProductPropertiesResponse] -> ShowS
show :: UpdateProvisionedProductPropertiesResponse -> String
$cshow :: UpdateProvisionedProductPropertiesResponse -> String
showsPrec :: Int -> UpdateProvisionedProductPropertiesResponse -> ShowS
$cshowsPrec :: Int -> UpdateProvisionedProductPropertiesResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateProvisionedProductPropertiesResponse x
-> UpdateProvisionedProductPropertiesResponse
forall x.
UpdateProvisionedProductPropertiesResponse
-> Rep UpdateProvisionedProductPropertiesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateProvisionedProductPropertiesResponse x
-> UpdateProvisionedProductPropertiesResponse
$cfrom :: forall x.
UpdateProvisionedProductPropertiesResponse
-> Rep UpdateProvisionedProductPropertiesResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateProvisionedProductPropertiesResponse' 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:
--
-- 'provisionedProductId', 'updateProvisionedProductPropertiesResponse_provisionedProductId' - The provisioned product identifier.
--
-- 'provisionedProductProperties', 'updateProvisionedProductPropertiesResponse_provisionedProductProperties' - A map that contains the properties updated.
--
-- 'recordId', 'updateProvisionedProductPropertiesResponse_recordId' - The identifier of the record.
--
-- 'status', 'updateProvisionedProductPropertiesResponse_status' - The status of the request.
--
-- 'httpStatus', 'updateProvisionedProductPropertiesResponse_httpStatus' - The response's http status code.
newUpdateProvisionedProductPropertiesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateProvisionedProductPropertiesResponse
newUpdateProvisionedProductPropertiesResponse :: Int -> UpdateProvisionedProductPropertiesResponse
newUpdateProvisionedProductPropertiesResponse
  Int
pHttpStatus_ =
    UpdateProvisionedProductPropertiesResponse'
      { $sel:provisionedProductId:UpdateProvisionedProductPropertiesResponse' :: Maybe Text
provisionedProductId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:provisionedProductProperties:UpdateProvisionedProductPropertiesResponse' :: Maybe (HashMap PropertyKey Text)
provisionedProductProperties =
          forall a. Maybe a
Prelude.Nothing,
        $sel:recordId:UpdateProvisionedProductPropertiesResponse' :: Maybe Text
recordId = forall a. Maybe a
Prelude.Nothing,
        $sel:status:UpdateProvisionedProductPropertiesResponse' :: Maybe RecordStatus
status = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:UpdateProvisionedProductPropertiesResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The provisioned product identifier.
updateProvisionedProductPropertiesResponse_provisionedProductId :: Lens.Lens' UpdateProvisionedProductPropertiesResponse (Prelude.Maybe Prelude.Text)
updateProvisionedProductPropertiesResponse_provisionedProductId :: Lens' UpdateProvisionedProductPropertiesResponse (Maybe Text)
updateProvisionedProductPropertiesResponse_provisionedProductId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProvisionedProductPropertiesResponse' {Maybe Text
provisionedProductId :: Maybe Text
$sel:provisionedProductId:UpdateProvisionedProductPropertiesResponse' :: UpdateProvisionedProductPropertiesResponse -> Maybe Text
provisionedProductId} -> Maybe Text
provisionedProductId) (\s :: UpdateProvisionedProductPropertiesResponse
s@UpdateProvisionedProductPropertiesResponse' {} Maybe Text
a -> UpdateProvisionedProductPropertiesResponse
s {$sel:provisionedProductId:UpdateProvisionedProductPropertiesResponse' :: Maybe Text
provisionedProductId = Maybe Text
a} :: UpdateProvisionedProductPropertiesResponse)

-- | A map that contains the properties updated.
updateProvisionedProductPropertiesResponse_provisionedProductProperties :: Lens.Lens' UpdateProvisionedProductPropertiesResponse (Prelude.Maybe (Prelude.HashMap PropertyKey Prelude.Text))
updateProvisionedProductPropertiesResponse_provisionedProductProperties :: Lens'
  UpdateProvisionedProductPropertiesResponse
  (Maybe (HashMap PropertyKey Text))
updateProvisionedProductPropertiesResponse_provisionedProductProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProvisionedProductPropertiesResponse' {Maybe (HashMap PropertyKey Text)
provisionedProductProperties :: Maybe (HashMap PropertyKey Text)
$sel:provisionedProductProperties:UpdateProvisionedProductPropertiesResponse' :: UpdateProvisionedProductPropertiesResponse
-> Maybe (HashMap PropertyKey Text)
provisionedProductProperties} -> Maybe (HashMap PropertyKey Text)
provisionedProductProperties) (\s :: UpdateProvisionedProductPropertiesResponse
s@UpdateProvisionedProductPropertiesResponse' {} Maybe (HashMap PropertyKey Text)
a -> UpdateProvisionedProductPropertiesResponse
s {$sel:provisionedProductProperties:UpdateProvisionedProductPropertiesResponse' :: Maybe (HashMap PropertyKey Text)
provisionedProductProperties = Maybe (HashMap PropertyKey Text)
a} :: UpdateProvisionedProductPropertiesResponse) 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 identifier of the record.
updateProvisionedProductPropertiesResponse_recordId :: Lens.Lens' UpdateProvisionedProductPropertiesResponse (Prelude.Maybe Prelude.Text)
updateProvisionedProductPropertiesResponse_recordId :: Lens' UpdateProvisionedProductPropertiesResponse (Maybe Text)
updateProvisionedProductPropertiesResponse_recordId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProvisionedProductPropertiesResponse' {Maybe Text
recordId :: Maybe Text
$sel:recordId:UpdateProvisionedProductPropertiesResponse' :: UpdateProvisionedProductPropertiesResponse -> Maybe Text
recordId} -> Maybe Text
recordId) (\s :: UpdateProvisionedProductPropertiesResponse
s@UpdateProvisionedProductPropertiesResponse' {} Maybe Text
a -> UpdateProvisionedProductPropertiesResponse
s {$sel:recordId:UpdateProvisionedProductPropertiesResponse' :: Maybe Text
recordId = Maybe Text
a} :: UpdateProvisionedProductPropertiesResponse)

-- | The status of the request.
updateProvisionedProductPropertiesResponse_status :: Lens.Lens' UpdateProvisionedProductPropertiesResponse (Prelude.Maybe RecordStatus)
updateProvisionedProductPropertiesResponse_status :: Lens'
  UpdateProvisionedProductPropertiesResponse (Maybe RecordStatus)
updateProvisionedProductPropertiesResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProvisionedProductPropertiesResponse' {Maybe RecordStatus
status :: Maybe RecordStatus
$sel:status:UpdateProvisionedProductPropertiesResponse' :: UpdateProvisionedProductPropertiesResponse -> Maybe RecordStatus
status} -> Maybe RecordStatus
status) (\s :: UpdateProvisionedProductPropertiesResponse
s@UpdateProvisionedProductPropertiesResponse' {} Maybe RecordStatus
a -> UpdateProvisionedProductPropertiesResponse
s {$sel:status:UpdateProvisionedProductPropertiesResponse' :: Maybe RecordStatus
status = Maybe RecordStatus
a} :: UpdateProvisionedProductPropertiesResponse)

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

instance
  Prelude.NFData
    UpdateProvisionedProductPropertiesResponse
  where
  rnf :: UpdateProvisionedProductPropertiesResponse -> ()
rnf UpdateProvisionedProductPropertiesResponse' {Int
Maybe Text
Maybe (HashMap PropertyKey Text)
Maybe RecordStatus
httpStatus :: Int
status :: Maybe RecordStatus
recordId :: Maybe Text
provisionedProductProperties :: Maybe (HashMap PropertyKey Text)
provisionedProductId :: Maybe Text
$sel:httpStatus:UpdateProvisionedProductPropertiesResponse' :: UpdateProvisionedProductPropertiesResponse -> Int
$sel:status:UpdateProvisionedProductPropertiesResponse' :: UpdateProvisionedProductPropertiesResponse -> Maybe RecordStatus
$sel:recordId:UpdateProvisionedProductPropertiesResponse' :: UpdateProvisionedProductPropertiesResponse -> Maybe Text
$sel:provisionedProductProperties:UpdateProvisionedProductPropertiesResponse' :: UpdateProvisionedProductPropertiesResponse
-> Maybe (HashMap PropertyKey Text)
$sel:provisionedProductId:UpdateProvisionedProductPropertiesResponse' :: UpdateProvisionedProductPropertiesResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
provisionedProductId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap PropertyKey Text)
provisionedProductProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
recordId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RecordStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus