{-# 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.CreateConstraint
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a constraint.
--
-- A delegated admin is authorized to invoke this command.
module Amazonka.ServiceCatalog.CreateConstraint
  ( -- * Creating a Request
    CreateConstraint (..),
    newCreateConstraint,

    -- * Request Lenses
    createConstraint_acceptLanguage,
    createConstraint_description,
    createConstraint_portfolioId,
    createConstraint_productId,
    createConstraint_parameters,
    createConstraint_type,
    createConstraint_idempotencyToken,

    -- * Destructuring the Response
    CreateConstraintResponse (..),
    newCreateConstraintResponse,

    -- * Response Lenses
    createConstraintResponse_constraintDetail,
    createConstraintResponse_constraintParameters,
    createConstraintResponse_status,
    createConstraintResponse_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:/ 'newCreateConstraint' smart constructor.
data CreateConstraint = CreateConstraint'
  { -- | The language code.
    --
    -- -   @en@ - English (default)
    --
    -- -   @jp@ - Japanese
    --
    -- -   @zh@ - Chinese
    CreateConstraint -> Maybe Text
acceptLanguage :: Prelude.Maybe Prelude.Text,
    -- | The description of the constraint.
    CreateConstraint -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The portfolio identifier.
    CreateConstraint -> Text
portfolioId :: Prelude.Text,
    -- | The product identifier.
    CreateConstraint -> Text
productId :: 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>.
    CreateConstraint -> Text
parameters :: Prelude.Text,
    -- | The type of constraint.
    --
    -- -   @LAUNCH@
    --
    -- -   @NOTIFICATION@
    --
    -- -   @RESOURCE_UPDATE@
    --
    -- -   @STACKSET@
    --
    -- -   @TEMPLATE@
    CreateConstraint -> Text
type' :: Prelude.Text,
    -- | A unique identifier that you provide to ensure idempotency. If multiple
    -- requests differ only by the idempotency token, the same response is
    -- returned for each repeated request.
    CreateConstraint -> Text
idempotencyToken :: Prelude.Text
  }
  deriving (CreateConstraint -> CreateConstraint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateConstraint -> CreateConstraint -> Bool
$c/= :: CreateConstraint -> CreateConstraint -> Bool
== :: CreateConstraint -> CreateConstraint -> Bool
$c== :: CreateConstraint -> CreateConstraint -> Bool
Prelude.Eq, ReadPrec [CreateConstraint]
ReadPrec CreateConstraint
Int -> ReadS CreateConstraint
ReadS [CreateConstraint]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateConstraint]
$creadListPrec :: ReadPrec [CreateConstraint]
readPrec :: ReadPrec CreateConstraint
$creadPrec :: ReadPrec CreateConstraint
readList :: ReadS [CreateConstraint]
$creadList :: ReadS [CreateConstraint]
readsPrec :: Int -> ReadS CreateConstraint
$creadsPrec :: Int -> ReadS CreateConstraint
Prelude.Read, Int -> CreateConstraint -> ShowS
[CreateConstraint] -> ShowS
CreateConstraint -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateConstraint] -> ShowS
$cshowList :: [CreateConstraint] -> ShowS
show :: CreateConstraint -> String
$cshow :: CreateConstraint -> String
showsPrec :: Int -> CreateConstraint -> ShowS
$cshowsPrec :: Int -> CreateConstraint -> ShowS
Prelude.Show, forall x. Rep CreateConstraint x -> CreateConstraint
forall x. CreateConstraint -> Rep CreateConstraint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateConstraint x -> CreateConstraint
$cfrom :: forall x. CreateConstraint -> Rep CreateConstraint x
Prelude.Generic)

-- |
-- Create a value of 'CreateConstraint' 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', 'createConstraint_acceptLanguage' - The language code.
--
-- -   @en@ - English (default)
--
-- -   @jp@ - Japanese
--
-- -   @zh@ - Chinese
--
-- 'description', 'createConstraint_description' - The description of the constraint.
--
-- 'portfolioId', 'createConstraint_portfolioId' - The portfolio identifier.
--
-- 'productId', 'createConstraint_productId' - The product identifier.
--
-- 'parameters', 'createConstraint_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>.
--
-- 'type'', 'createConstraint_type' - The type of constraint.
--
-- -   @LAUNCH@
--
-- -   @NOTIFICATION@
--
-- -   @RESOURCE_UPDATE@
--
-- -   @STACKSET@
--
-- -   @TEMPLATE@
--
-- 'idempotencyToken', 'createConstraint_idempotencyToken' - A unique identifier that you provide to ensure idempotency. If multiple
-- requests differ only by the idempotency token, the same response is
-- returned for each repeated request.
newCreateConstraint ::
  -- | 'portfolioId'
  Prelude.Text ->
  -- | 'productId'
  Prelude.Text ->
  -- | 'parameters'
  Prelude.Text ->
  -- | 'type''
  Prelude.Text ->
  -- | 'idempotencyToken'
  Prelude.Text ->
  CreateConstraint
newCreateConstraint :: Text -> Text -> Text -> Text -> Text -> CreateConstraint
newCreateConstraint
  Text
pPortfolioId_
  Text
pProductId_
  Text
pParameters_
  Text
pType_
  Text
pIdempotencyToken_ =
    CreateConstraint'
      { $sel:acceptLanguage:CreateConstraint' :: Maybe Text
acceptLanguage = forall a. Maybe a
Prelude.Nothing,
        $sel:description:CreateConstraint' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:portfolioId:CreateConstraint' :: Text
portfolioId = Text
pPortfolioId_,
        $sel:productId:CreateConstraint' :: Text
productId = Text
pProductId_,
        $sel:parameters:CreateConstraint' :: Text
parameters = Text
pParameters_,
        $sel:type':CreateConstraint' :: Text
type' = Text
pType_,
        $sel:idempotencyToken:CreateConstraint' :: Text
idempotencyToken = Text
pIdempotencyToken_
      }

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

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

-- | The portfolio identifier.
createConstraint_portfolioId :: Lens.Lens' CreateConstraint Prelude.Text
createConstraint_portfolioId :: Lens' CreateConstraint Text
createConstraint_portfolioId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConstraint' {Text
portfolioId :: Text
$sel:portfolioId:CreateConstraint' :: CreateConstraint -> Text
portfolioId} -> Text
portfolioId) (\s :: CreateConstraint
s@CreateConstraint' {} Text
a -> CreateConstraint
s {$sel:portfolioId:CreateConstraint' :: Text
portfolioId = Text
a} :: CreateConstraint)

-- | The product identifier.
createConstraint_productId :: Lens.Lens' CreateConstraint Prelude.Text
createConstraint_productId :: Lens' CreateConstraint Text
createConstraint_productId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConstraint' {Text
productId :: Text
$sel:productId:CreateConstraint' :: CreateConstraint -> Text
productId} -> Text
productId) (\s :: CreateConstraint
s@CreateConstraint' {} Text
a -> CreateConstraint
s {$sel:productId:CreateConstraint' :: Text
productId = Text
a} :: CreateConstraint)

-- | 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>.
createConstraint_parameters :: Lens.Lens' CreateConstraint Prelude.Text
createConstraint_parameters :: Lens' CreateConstraint Text
createConstraint_parameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConstraint' {Text
parameters :: Text
$sel:parameters:CreateConstraint' :: CreateConstraint -> Text
parameters} -> Text
parameters) (\s :: CreateConstraint
s@CreateConstraint' {} Text
a -> CreateConstraint
s {$sel:parameters:CreateConstraint' :: Text
parameters = Text
a} :: CreateConstraint)

-- | The type of constraint.
--
-- -   @LAUNCH@
--
-- -   @NOTIFICATION@
--
-- -   @RESOURCE_UPDATE@
--
-- -   @STACKSET@
--
-- -   @TEMPLATE@
createConstraint_type :: Lens.Lens' CreateConstraint Prelude.Text
createConstraint_type :: Lens' CreateConstraint Text
createConstraint_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConstraint' {Text
type' :: Text
$sel:type':CreateConstraint' :: CreateConstraint -> Text
type'} -> Text
type') (\s :: CreateConstraint
s@CreateConstraint' {} Text
a -> CreateConstraint
s {$sel:type':CreateConstraint' :: Text
type' = Text
a} :: CreateConstraint)

-- | A unique identifier that you provide to ensure idempotency. If multiple
-- requests differ only by the idempotency token, the same response is
-- returned for each repeated request.
createConstraint_idempotencyToken :: Lens.Lens' CreateConstraint Prelude.Text
createConstraint_idempotencyToken :: Lens' CreateConstraint Text
createConstraint_idempotencyToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConstraint' {Text
idempotencyToken :: Text
$sel:idempotencyToken:CreateConstraint' :: CreateConstraint -> Text
idempotencyToken} -> Text
idempotencyToken) (\s :: CreateConstraint
s@CreateConstraint' {} Text
a -> CreateConstraint
s {$sel:idempotencyToken:CreateConstraint' :: Text
idempotencyToken = Text
a} :: CreateConstraint)

instance Core.AWSRequest CreateConstraint where
  type
    AWSResponse CreateConstraint =
      CreateConstraintResponse
  request :: (Service -> Service)
-> CreateConstraint -> Request CreateConstraint
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 CreateConstraint
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateConstraint)))
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
-> CreateConstraintResponse
CreateConstraintResponse'
            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 CreateConstraint where
  hashWithSalt :: Int -> CreateConstraint -> Int
hashWithSalt Int
_salt CreateConstraint' {Maybe Text
Text
idempotencyToken :: Text
type' :: Text
parameters :: Text
productId :: Text
portfolioId :: Text
description :: Maybe Text
acceptLanguage :: Maybe Text
$sel:idempotencyToken:CreateConstraint' :: CreateConstraint -> Text
$sel:type':CreateConstraint' :: CreateConstraint -> Text
$sel:parameters:CreateConstraint' :: CreateConstraint -> Text
$sel:productId:CreateConstraint' :: CreateConstraint -> Text
$sel:portfolioId:CreateConstraint' :: CreateConstraint -> Text
$sel:description:CreateConstraint' :: CreateConstraint -> Maybe Text
$sel:acceptLanguage:CreateConstraint' :: CreateConstraint -> 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` Text
portfolioId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
productId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
parameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
idempotencyToken

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

instance Data.ToHeaders CreateConstraint where
  toHeaders :: CreateConstraint -> 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.CreateConstraint" ::
                          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 CreateConstraint where
  toJSON :: CreateConstraint -> Value
toJSON CreateConstraint' {Maybe Text
Text
idempotencyToken :: Text
type' :: Text
parameters :: Text
productId :: Text
portfolioId :: Text
description :: Maybe Text
acceptLanguage :: Maybe Text
$sel:idempotencyToken:CreateConstraint' :: CreateConstraint -> Text
$sel:type':CreateConstraint' :: CreateConstraint -> Text
$sel:parameters:CreateConstraint' :: CreateConstraint -> Text
$sel:productId:CreateConstraint' :: CreateConstraint -> Text
$sel:portfolioId:CreateConstraint' :: CreateConstraint -> Text
$sel:description:CreateConstraint' :: CreateConstraint -> Maybe Text
$sel:acceptLanguage:CreateConstraint' :: CreateConstraint -> 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,
            forall a. a -> Maybe a
Prelude.Just (Key
"PortfolioId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
portfolioId),
            forall a. a -> Maybe a
Prelude.Just (Key
"ProductId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
productId),
            forall a. a -> Maybe a
Prelude.Just (Key
"Parameters" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
parameters),
            forall a. a -> Maybe a
Prelude.Just (Key
"Type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
type'),
            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 CreateConstraint where
  toPath :: CreateConstraint -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'CreateConstraintResponse' 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', 'createConstraintResponse_constraintDetail' - Information about the constraint.
--
-- 'constraintParameters', 'createConstraintResponse_constraintParameters' - The constraint parameters.
--
-- 'status', 'createConstraintResponse_status' - The status of the current request.
--
-- 'httpStatus', 'createConstraintResponse_httpStatus' - The response's http status code.
newCreateConstraintResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateConstraintResponse
newCreateConstraintResponse :: Int -> CreateConstraintResponse
newCreateConstraintResponse Int
pHttpStatus_ =
  CreateConstraintResponse'
    { $sel:constraintDetail:CreateConstraintResponse' :: Maybe ConstraintDetail
constraintDetail =
        forall a. Maybe a
Prelude.Nothing,
      $sel:constraintParameters:CreateConstraintResponse' :: Maybe Text
constraintParameters = forall a. Maybe a
Prelude.Nothing,
      $sel:status:CreateConstraintResponse' :: Maybe RequestStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateConstraintResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

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

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

instance Prelude.NFData CreateConstraintResponse where
  rnf :: CreateConstraintResponse -> ()
rnf CreateConstraintResponse' {Int
Maybe Text
Maybe ConstraintDetail
Maybe RequestStatus
httpStatus :: Int
status :: Maybe RequestStatus
constraintParameters :: Maybe Text
constraintDetail :: Maybe ConstraintDetail
$sel:httpStatus:CreateConstraintResponse' :: CreateConstraintResponse -> Int
$sel:status:CreateConstraintResponse' :: CreateConstraintResponse -> Maybe RequestStatus
$sel:constraintParameters:CreateConstraintResponse' :: CreateConstraintResponse -> Maybe Text
$sel:constraintDetail:CreateConstraintResponse' :: CreateConstraintResponse -> 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