{-# 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.UpdateConstraint
-- 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 the specified constraint.
module Amazonka.ServiceCatalog.UpdateConstraint
  ( -- * Creating a Request
    UpdateConstraint (..),
    newUpdateConstraint,

    -- * Request Lenses
    updateConstraint_acceptLanguage,
    updateConstraint_description,
    updateConstraint_parameters,
    updateConstraint_id,

    -- * Destructuring the Response
    UpdateConstraintResponse (..),
    newUpdateConstraintResponse,

    -- * Response Lenses
    updateConstraintResponse_constraintDetail,
    updateConstraintResponse_constraintParameters,
    updateConstraintResponse_status,
    updateConstraintResponse_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:/ 'newUpdateConstraint' smart constructor.
data UpdateConstraint = UpdateConstraint'
  { -- | The language code.
    --
    -- -   @en@ - English (default)
    --
    -- -   @jp@ - Japanese
    --
    -- -   @zh@ - Chinese
    UpdateConstraint -> Maybe Text
acceptLanguage :: Prelude.Maybe Prelude.Text,
    -- | The updated description of the constraint.
    UpdateConstraint -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The constraint parameters, in JSON format. The syntax depends on the
    -- constraint type as follows:
    --
    -- [LAUNCH]
    --     You are required to specify either the @RoleArn@ or the
    --     @LocalRoleName@ but can\'t use both.
    --
    --     Specify the @RoleArn@ property as follows:
    --
    --     @{\"RoleArn\" : \"arn:aws:iam::123456789012:role\/LaunchRole\"}@
    --
    --     Specify the @LocalRoleName@ property as follows:
    --
    --     @{\"LocalRoleName\": \"SCBasicLaunchRole\"}@
    --
    --     If you specify the @LocalRoleName@ property, when an account uses
    --     the launch constraint, the IAM role with that name in the account
    --     will be used. This allows launch-role constraints to be
    --     account-agnostic so the administrator can create fewer resources per
    --     shared account.
    --
    --     The given role name must exist in the account used to create the
    --     launch constraint and the account of the user who launches a product
    --     with this launch constraint.
    --
    --     You cannot have both a @LAUNCH@ and a @STACKSET@ constraint.
    --
    --     You also cannot have more than one @LAUNCH@ constraint on a product
    --     and portfolio.
    --
    -- [NOTIFICATION]
    --     Specify the @NotificationArns@ property as follows:
    --
    --     @{\"NotificationArns\" : [\"arn:aws:sns:us-east-1:123456789012:Topic\"]}@
    --
    -- [RESOURCE_UPDATE]
    --     Specify the @TagUpdatesOnProvisionedProduct@ property as follows:
    --
    --     @{\"Version\":\"2.0\",\"Properties\":{\"TagUpdateOnProvisionedProduct\":\"String\"}}@
    --
    --     The @TagUpdatesOnProvisionedProduct@ property accepts a string value
    --     of @ALLOWED@ or @NOT_ALLOWED@.
    --
    -- [STACKSET]
    --     Specify the @Parameters@ property as follows:
    --
    --     @{\"Version\": \"String\", \"Properties\": {\"AccountList\": [ \"String\" ], \"RegionList\": [ \"String\" ], \"AdminRole\": \"String\", \"ExecutionRole\": \"String\"}}@
    --
    --     You cannot have both a @LAUNCH@ and a @STACKSET@ constraint.
    --
    --     You also cannot have more than one @STACKSET@ constraint on a
    --     product and portfolio.
    --
    --     Products with a @STACKSET@ constraint will launch an CloudFormation
    --     stack set.
    --
    -- [TEMPLATE]
    --     Specify the @Rules@ property. For more information, see
    --     <http://docs.aws.amazon.com/servicecatalog/latest/adminguide/reference-template_constraint_rules.html Template Constraint Rules>.
    UpdateConstraint -> Maybe Text
parameters :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the constraint.
    UpdateConstraint -> Text
id :: Prelude.Text
  }
  deriving (UpdateConstraint -> UpdateConstraint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateConstraint -> UpdateConstraint -> Bool
$c/= :: UpdateConstraint -> UpdateConstraint -> Bool
== :: UpdateConstraint -> UpdateConstraint -> Bool
$c== :: UpdateConstraint -> UpdateConstraint -> Bool
Prelude.Eq, ReadPrec [UpdateConstraint]
ReadPrec UpdateConstraint
Int -> ReadS UpdateConstraint
ReadS [UpdateConstraint]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateConstraint]
$creadListPrec :: ReadPrec [UpdateConstraint]
readPrec :: ReadPrec UpdateConstraint
$creadPrec :: ReadPrec UpdateConstraint
readList :: ReadS [UpdateConstraint]
$creadList :: ReadS [UpdateConstraint]
readsPrec :: Int -> ReadS UpdateConstraint
$creadsPrec :: Int -> ReadS UpdateConstraint
Prelude.Read, Int -> UpdateConstraint -> ShowS
[UpdateConstraint] -> ShowS
UpdateConstraint -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateConstraint] -> ShowS
$cshowList :: [UpdateConstraint] -> ShowS
show :: UpdateConstraint -> String
$cshow :: UpdateConstraint -> String
showsPrec :: Int -> UpdateConstraint -> ShowS
$cshowsPrec :: Int -> UpdateConstraint -> ShowS
Prelude.Show, forall x. Rep UpdateConstraint x -> UpdateConstraint
forall x. UpdateConstraint -> Rep UpdateConstraint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateConstraint x -> UpdateConstraint
$cfrom :: forall x. UpdateConstraint -> Rep UpdateConstraint x
Prelude.Generic)

-- |
-- Create a value of 'UpdateConstraint' 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', 'updateConstraint_acceptLanguage' - The language code.
--
-- -   @en@ - English (default)
--
-- -   @jp@ - Japanese
--
-- -   @zh@ - Chinese
--
-- 'description', 'updateConstraint_description' - The updated description of the constraint.
--
-- 'parameters', 'updateConstraint_parameters' - The constraint parameters, in JSON format. The syntax depends on the
-- constraint type as follows:
--
-- [LAUNCH]
--     You are required to specify either the @RoleArn@ or the
--     @LocalRoleName@ but can\'t use both.
--
--     Specify the @RoleArn@ property as follows:
--
--     @{\"RoleArn\" : \"arn:aws:iam::123456789012:role\/LaunchRole\"}@
--
--     Specify the @LocalRoleName@ property as follows:
--
--     @{\"LocalRoleName\": \"SCBasicLaunchRole\"}@
--
--     If you specify the @LocalRoleName@ property, when an account uses
--     the launch constraint, the IAM role with that name in the account
--     will be used. This allows launch-role constraints to be
--     account-agnostic so the administrator can create fewer resources per
--     shared account.
--
--     The given role name must exist in the account used to create the
--     launch constraint and the account of the user who launches a product
--     with this launch constraint.
--
--     You cannot have both a @LAUNCH@ and a @STACKSET@ constraint.
--
--     You also cannot have more than one @LAUNCH@ constraint on a product
--     and portfolio.
--
-- [NOTIFICATION]
--     Specify the @NotificationArns@ property as follows:
--
--     @{\"NotificationArns\" : [\"arn:aws:sns:us-east-1:123456789012:Topic\"]}@
--
-- [RESOURCE_UPDATE]
--     Specify the @TagUpdatesOnProvisionedProduct@ property as follows:
--
--     @{\"Version\":\"2.0\",\"Properties\":{\"TagUpdateOnProvisionedProduct\":\"String\"}}@
--
--     The @TagUpdatesOnProvisionedProduct@ property accepts a string value
--     of @ALLOWED@ or @NOT_ALLOWED@.
--
-- [STACKSET]
--     Specify the @Parameters@ property as follows:
--
--     @{\"Version\": \"String\", \"Properties\": {\"AccountList\": [ \"String\" ], \"RegionList\": [ \"String\" ], \"AdminRole\": \"String\", \"ExecutionRole\": \"String\"}}@
--
--     You cannot have both a @LAUNCH@ and a @STACKSET@ constraint.
--
--     You also cannot have more than one @STACKSET@ constraint on a
--     product and portfolio.
--
--     Products with a @STACKSET@ constraint will launch an CloudFormation
--     stack set.
--
-- [TEMPLATE]
--     Specify the @Rules@ property. For more information, see
--     <http://docs.aws.amazon.com/servicecatalog/latest/adminguide/reference-template_constraint_rules.html Template Constraint Rules>.
--
-- 'id', 'updateConstraint_id' - The identifier of the constraint.
newUpdateConstraint ::
  -- | 'id'
  Prelude.Text ->
  UpdateConstraint
newUpdateConstraint :: Text -> UpdateConstraint
newUpdateConstraint Text
pId_ =
  UpdateConstraint'
    { $sel:acceptLanguage:UpdateConstraint' :: Maybe Text
acceptLanguage = forall a. Maybe a
Prelude.Nothing,
      $sel:description:UpdateConstraint' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:parameters:UpdateConstraint' :: Maybe Text
parameters = forall a. Maybe a
Prelude.Nothing,
      $sel:id:UpdateConstraint' :: Text
id = Text
pId_
    }

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

-- | The updated description of the constraint.
updateConstraint_description :: Lens.Lens' UpdateConstraint (Prelude.Maybe Prelude.Text)
updateConstraint_description :: Lens' UpdateConstraint (Maybe Text)
updateConstraint_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConstraint' {Maybe Text
description :: Maybe Text
$sel:description:UpdateConstraint' :: UpdateConstraint -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateConstraint
s@UpdateConstraint' {} Maybe Text
a -> UpdateConstraint
s {$sel:description:UpdateConstraint' :: Maybe Text
description = Maybe Text
a} :: UpdateConstraint)

-- | The constraint parameters, in JSON format. The syntax depends on the
-- constraint type as follows:
--
-- [LAUNCH]
--     You are required to specify either the @RoleArn@ or the
--     @LocalRoleName@ but can\'t use both.
--
--     Specify the @RoleArn@ property as follows:
--
--     @{\"RoleArn\" : \"arn:aws:iam::123456789012:role\/LaunchRole\"}@
--
--     Specify the @LocalRoleName@ property as follows:
--
--     @{\"LocalRoleName\": \"SCBasicLaunchRole\"}@
--
--     If you specify the @LocalRoleName@ property, when an account uses
--     the launch constraint, the IAM role with that name in the account
--     will be used. This allows launch-role constraints to be
--     account-agnostic so the administrator can create fewer resources per
--     shared account.
--
--     The given role name must exist in the account used to create the
--     launch constraint and the account of the user who launches a product
--     with this launch constraint.
--
--     You cannot have both a @LAUNCH@ and a @STACKSET@ constraint.
--
--     You also cannot have more than one @LAUNCH@ constraint on a product
--     and portfolio.
--
-- [NOTIFICATION]
--     Specify the @NotificationArns@ property as follows:
--
--     @{\"NotificationArns\" : [\"arn:aws:sns:us-east-1:123456789012:Topic\"]}@
--
-- [RESOURCE_UPDATE]
--     Specify the @TagUpdatesOnProvisionedProduct@ property as follows:
--
--     @{\"Version\":\"2.0\",\"Properties\":{\"TagUpdateOnProvisionedProduct\":\"String\"}}@
--
--     The @TagUpdatesOnProvisionedProduct@ property accepts a string value
--     of @ALLOWED@ or @NOT_ALLOWED@.
--
-- [STACKSET]
--     Specify the @Parameters@ property as follows:
--
--     @{\"Version\": \"String\", \"Properties\": {\"AccountList\": [ \"String\" ], \"RegionList\": [ \"String\" ], \"AdminRole\": \"String\", \"ExecutionRole\": \"String\"}}@
--
--     You cannot have both a @LAUNCH@ and a @STACKSET@ constraint.
--
--     You also cannot have more than one @STACKSET@ constraint on a
--     product and portfolio.
--
--     Products with a @STACKSET@ constraint will launch an CloudFormation
--     stack set.
--
-- [TEMPLATE]
--     Specify the @Rules@ property. For more information, see
--     <http://docs.aws.amazon.com/servicecatalog/latest/adminguide/reference-template_constraint_rules.html Template Constraint Rules>.
updateConstraint_parameters :: Lens.Lens' UpdateConstraint (Prelude.Maybe Prelude.Text)
updateConstraint_parameters :: Lens' UpdateConstraint (Maybe Text)
updateConstraint_parameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConstraint' {Maybe Text
parameters :: Maybe Text
$sel:parameters:UpdateConstraint' :: UpdateConstraint -> Maybe Text
parameters} -> Maybe Text
parameters) (\s :: UpdateConstraint
s@UpdateConstraint' {} Maybe Text
a -> UpdateConstraint
s {$sel:parameters:UpdateConstraint' :: Maybe Text
parameters = Maybe Text
a} :: UpdateConstraint)

-- | The identifier of the constraint.
updateConstraint_id :: Lens.Lens' UpdateConstraint Prelude.Text
updateConstraint_id :: Lens' UpdateConstraint Text
updateConstraint_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConstraint' {Text
id :: Text
$sel:id:UpdateConstraint' :: UpdateConstraint -> Text
id} -> Text
id) (\s :: UpdateConstraint
s@UpdateConstraint' {} Text
a -> UpdateConstraint
s {$sel:id:UpdateConstraint' :: Text
id = Text
a} :: UpdateConstraint)

instance Core.AWSRequest UpdateConstraint where
  type
    AWSResponse UpdateConstraint =
      UpdateConstraintResponse
  request :: (Service -> Service)
-> UpdateConstraint -> Request UpdateConstraint
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 UpdateConstraint
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateConstraint)))
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 ConstraintDetail
-> Maybe Text
-> Maybe RequestStatus
-> Int
-> UpdateConstraintResponse
UpdateConstraintResponse'
            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
"ConstraintDetail")
            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
"ConstraintParameters")
            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 UpdateConstraint where
  hashWithSalt :: Int -> UpdateConstraint -> Int
hashWithSalt Int
_salt UpdateConstraint' {Maybe Text
Text
id :: Text
parameters :: Maybe Text
description :: Maybe Text
acceptLanguage :: Maybe Text
$sel:id:UpdateConstraint' :: UpdateConstraint -> Text
$sel:parameters:UpdateConstraint' :: UpdateConstraint -> Maybe Text
$sel:description:UpdateConstraint' :: UpdateConstraint -> Maybe Text
$sel:acceptLanguage:UpdateConstraint' :: UpdateConstraint -> 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` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
parameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance Prelude.NFData UpdateConstraint where
  rnf :: UpdateConstraint -> ()
rnf UpdateConstraint' {Maybe Text
Text
id :: Text
parameters :: Maybe Text
description :: Maybe Text
acceptLanguage :: Maybe Text
$sel:id:UpdateConstraint' :: UpdateConstraint -> Text
$sel:parameters:UpdateConstraint' :: UpdateConstraint -> Maybe Text
$sel:description:UpdateConstraint' :: UpdateConstraint -> Maybe Text
$sel:acceptLanguage:UpdateConstraint' :: UpdateConstraint -> 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 Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
parameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id

instance Data.ToHeaders UpdateConstraint where
  toHeaders :: UpdateConstraint -> 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.UpdateConstraint" ::
                          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 UpdateConstraint where
  toJSON :: UpdateConstraint -> Value
toJSON UpdateConstraint' {Maybe Text
Text
id :: Text
parameters :: Maybe Text
description :: Maybe Text
acceptLanguage :: Maybe Text
$sel:id:UpdateConstraint' :: UpdateConstraint -> Text
$sel:parameters:UpdateConstraint' :: UpdateConstraint -> Maybe Text
$sel:description:UpdateConstraint' :: UpdateConstraint -> Maybe Text
$sel:acceptLanguage:UpdateConstraint' :: UpdateConstraint -> 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,
            (Key
"Description" 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
description,
            (Key
"Parameters" 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
parameters,
            forall a. a -> Maybe a
Prelude.Just (Key
"Id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
id)
          ]
      )

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

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

-- | /See:/ 'newUpdateConstraintResponse' smart constructor.
data UpdateConstraintResponse = UpdateConstraintResponse'
  { -- | Information about the constraint.
    UpdateConstraintResponse -> Maybe ConstraintDetail
constraintDetail :: Prelude.Maybe ConstraintDetail,
    -- | The constraint parameters.
    UpdateConstraintResponse -> Maybe Text
constraintParameters :: Prelude.Maybe Prelude.Text,
    -- | The status of the current request.
    UpdateConstraintResponse -> Maybe RequestStatus
status :: Prelude.Maybe RequestStatus,
    -- | The response's http status code.
    UpdateConstraintResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateConstraintResponse -> UpdateConstraintResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateConstraintResponse -> UpdateConstraintResponse -> Bool
$c/= :: UpdateConstraintResponse -> UpdateConstraintResponse -> Bool
== :: UpdateConstraintResponse -> UpdateConstraintResponse -> Bool
$c== :: UpdateConstraintResponse -> UpdateConstraintResponse -> Bool
Prelude.Eq, ReadPrec [UpdateConstraintResponse]
ReadPrec UpdateConstraintResponse
Int -> ReadS UpdateConstraintResponse
ReadS [UpdateConstraintResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateConstraintResponse]
$creadListPrec :: ReadPrec [UpdateConstraintResponse]
readPrec :: ReadPrec UpdateConstraintResponse
$creadPrec :: ReadPrec UpdateConstraintResponse
readList :: ReadS [UpdateConstraintResponse]
$creadList :: ReadS [UpdateConstraintResponse]
readsPrec :: Int -> ReadS UpdateConstraintResponse
$creadsPrec :: Int -> ReadS UpdateConstraintResponse
Prelude.Read, Int -> UpdateConstraintResponse -> ShowS
[UpdateConstraintResponse] -> ShowS
UpdateConstraintResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateConstraintResponse] -> ShowS
$cshowList :: [UpdateConstraintResponse] -> ShowS
show :: UpdateConstraintResponse -> String
$cshow :: UpdateConstraintResponse -> String
showsPrec :: Int -> UpdateConstraintResponse -> ShowS
$cshowsPrec :: Int -> UpdateConstraintResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateConstraintResponse x -> UpdateConstraintResponse
forall x.
UpdateConstraintResponse -> Rep UpdateConstraintResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateConstraintResponse x -> UpdateConstraintResponse
$cfrom :: forall x.
UpdateConstraintResponse -> Rep UpdateConstraintResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateConstraintResponse' 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:
--
-- 'constraintDetail', 'updateConstraintResponse_constraintDetail' - Information about the constraint.
--
-- 'constraintParameters', 'updateConstraintResponse_constraintParameters' - The constraint parameters.
--
-- 'status', 'updateConstraintResponse_status' - The status of the current request.
--
-- 'httpStatus', 'updateConstraintResponse_httpStatus' - The response's http status code.
newUpdateConstraintResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateConstraintResponse
newUpdateConstraintResponse :: Int -> UpdateConstraintResponse
newUpdateConstraintResponse Int
pHttpStatus_ =
  UpdateConstraintResponse'
    { $sel:constraintDetail:UpdateConstraintResponse' :: Maybe ConstraintDetail
constraintDetail =
        forall a. Maybe a
Prelude.Nothing,
      $sel:constraintParameters:UpdateConstraintResponse' :: Maybe Text
constraintParameters = forall a. Maybe a
Prelude.Nothing,
      $sel:status:UpdateConstraintResponse' :: Maybe RequestStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateConstraintResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the constraint.
updateConstraintResponse_constraintDetail :: Lens.Lens' UpdateConstraintResponse (Prelude.Maybe ConstraintDetail)
updateConstraintResponse_constraintDetail :: Lens' UpdateConstraintResponse (Maybe ConstraintDetail)
updateConstraintResponse_constraintDetail = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConstraintResponse' {Maybe ConstraintDetail
constraintDetail :: Maybe ConstraintDetail
$sel:constraintDetail:UpdateConstraintResponse' :: UpdateConstraintResponse -> Maybe ConstraintDetail
constraintDetail} -> Maybe ConstraintDetail
constraintDetail) (\s :: UpdateConstraintResponse
s@UpdateConstraintResponse' {} Maybe ConstraintDetail
a -> UpdateConstraintResponse
s {$sel:constraintDetail:UpdateConstraintResponse' :: Maybe ConstraintDetail
constraintDetail = Maybe ConstraintDetail
a} :: UpdateConstraintResponse)

-- | The constraint parameters.
updateConstraintResponse_constraintParameters :: Lens.Lens' UpdateConstraintResponse (Prelude.Maybe Prelude.Text)
updateConstraintResponse_constraintParameters :: Lens' UpdateConstraintResponse (Maybe Text)
updateConstraintResponse_constraintParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateConstraintResponse' {Maybe Text
constraintParameters :: Maybe Text
$sel:constraintParameters:UpdateConstraintResponse' :: UpdateConstraintResponse -> Maybe Text
constraintParameters} -> Maybe Text
constraintParameters) (\s :: UpdateConstraintResponse
s@UpdateConstraintResponse' {} Maybe Text
a -> UpdateConstraintResponse
s {$sel:constraintParameters:UpdateConstraintResponse' :: Maybe Text
constraintParameters = Maybe Text
a} :: UpdateConstraintResponse)

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

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

instance Prelude.NFData UpdateConstraintResponse where
  rnf :: UpdateConstraintResponse -> ()
rnf UpdateConstraintResponse' {Int
Maybe Text
Maybe ConstraintDetail
Maybe RequestStatus
httpStatus :: Int
status :: Maybe RequestStatus
constraintParameters :: Maybe Text
constraintDetail :: Maybe ConstraintDetail
$sel:httpStatus:UpdateConstraintResponse' :: UpdateConstraintResponse -> Int
$sel:status:UpdateConstraintResponse' :: UpdateConstraintResponse -> Maybe RequestStatus
$sel:constraintParameters:UpdateConstraintResponse' :: UpdateConstraintResponse -> Maybe Text
$sel:constraintDetail:UpdateConstraintResponse' :: UpdateConstraintResponse -> Maybe ConstraintDetail
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ConstraintDetail
constraintDetail
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
constraintParameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RequestStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus