{-# 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.BatchAssociateServiceActionWithProvisioningArtifact
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Associates multiple self-service actions with provisioning artifacts.
module Amazonka.ServiceCatalog.BatchAssociateServiceActionWithProvisioningArtifact
  ( -- * Creating a Request
    BatchAssociateServiceActionWithProvisioningArtifact (..),
    newBatchAssociateServiceActionWithProvisioningArtifact,

    -- * Request Lenses
    batchAssociateServiceActionWithProvisioningArtifact_acceptLanguage,
    batchAssociateServiceActionWithProvisioningArtifact_serviceActionAssociations,

    -- * Destructuring the Response
    BatchAssociateServiceActionWithProvisioningArtifactResponse (..),
    newBatchAssociateServiceActionWithProvisioningArtifactResponse,

    -- * Response Lenses
    batchAssociateServiceActionWithProvisioningArtifactResponse_failedServiceActionAssociations,
    batchAssociateServiceActionWithProvisioningArtifactResponse_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:/ 'newBatchAssociateServiceActionWithProvisioningArtifact' smart constructor.
data BatchAssociateServiceActionWithProvisioningArtifact = BatchAssociateServiceActionWithProvisioningArtifact'
  { -- | The language code.
    --
    -- -   @en@ - English (default)
    --
    -- -   @jp@ - Japanese
    --
    -- -   @zh@ - Chinese
    BatchAssociateServiceActionWithProvisioningArtifact -> Maybe Text
acceptLanguage :: Prelude.Maybe Prelude.Text,
    -- | One or more associations, each consisting of the Action ID, the Product
    -- ID, and the Provisioning Artifact ID.
    BatchAssociateServiceActionWithProvisioningArtifact
-> NonEmpty ServiceActionAssociation
serviceActionAssociations :: Prelude.NonEmpty ServiceActionAssociation
  }
  deriving (BatchAssociateServiceActionWithProvisioningArtifact
-> BatchAssociateServiceActionWithProvisioningArtifact -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchAssociateServiceActionWithProvisioningArtifact
-> BatchAssociateServiceActionWithProvisioningArtifact -> Bool
$c/= :: BatchAssociateServiceActionWithProvisioningArtifact
-> BatchAssociateServiceActionWithProvisioningArtifact -> Bool
== :: BatchAssociateServiceActionWithProvisioningArtifact
-> BatchAssociateServiceActionWithProvisioningArtifact -> Bool
$c== :: BatchAssociateServiceActionWithProvisioningArtifact
-> BatchAssociateServiceActionWithProvisioningArtifact -> Bool
Prelude.Eq, ReadPrec [BatchAssociateServiceActionWithProvisioningArtifact]
ReadPrec BatchAssociateServiceActionWithProvisioningArtifact
Int -> ReadS BatchAssociateServiceActionWithProvisioningArtifact
ReadS [BatchAssociateServiceActionWithProvisioningArtifact]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchAssociateServiceActionWithProvisioningArtifact]
$creadListPrec :: ReadPrec [BatchAssociateServiceActionWithProvisioningArtifact]
readPrec :: ReadPrec BatchAssociateServiceActionWithProvisioningArtifact
$creadPrec :: ReadPrec BatchAssociateServiceActionWithProvisioningArtifact
readList :: ReadS [BatchAssociateServiceActionWithProvisioningArtifact]
$creadList :: ReadS [BatchAssociateServiceActionWithProvisioningArtifact]
readsPrec :: Int -> ReadS BatchAssociateServiceActionWithProvisioningArtifact
$creadsPrec :: Int -> ReadS BatchAssociateServiceActionWithProvisioningArtifact
Prelude.Read, Int -> BatchAssociateServiceActionWithProvisioningArtifact -> ShowS
[BatchAssociateServiceActionWithProvisioningArtifact] -> ShowS
BatchAssociateServiceActionWithProvisioningArtifact -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchAssociateServiceActionWithProvisioningArtifact] -> ShowS
$cshowList :: [BatchAssociateServiceActionWithProvisioningArtifact] -> ShowS
show :: BatchAssociateServiceActionWithProvisioningArtifact -> String
$cshow :: BatchAssociateServiceActionWithProvisioningArtifact -> String
showsPrec :: Int -> BatchAssociateServiceActionWithProvisioningArtifact -> ShowS
$cshowsPrec :: Int -> BatchAssociateServiceActionWithProvisioningArtifact -> ShowS
Prelude.Show, forall x.
Rep BatchAssociateServiceActionWithProvisioningArtifact x
-> BatchAssociateServiceActionWithProvisioningArtifact
forall x.
BatchAssociateServiceActionWithProvisioningArtifact
-> Rep BatchAssociateServiceActionWithProvisioningArtifact x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchAssociateServiceActionWithProvisioningArtifact x
-> BatchAssociateServiceActionWithProvisioningArtifact
$cfrom :: forall x.
BatchAssociateServiceActionWithProvisioningArtifact
-> Rep BatchAssociateServiceActionWithProvisioningArtifact x
Prelude.Generic)

-- |
-- Create a value of 'BatchAssociateServiceActionWithProvisioningArtifact' 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', 'batchAssociateServiceActionWithProvisioningArtifact_acceptLanguage' - The language code.
--
-- -   @en@ - English (default)
--
-- -   @jp@ - Japanese
--
-- -   @zh@ - Chinese
--
-- 'serviceActionAssociations', 'batchAssociateServiceActionWithProvisioningArtifact_serviceActionAssociations' - One or more associations, each consisting of the Action ID, the Product
-- ID, and the Provisioning Artifact ID.
newBatchAssociateServiceActionWithProvisioningArtifact ::
  -- | 'serviceActionAssociations'
  Prelude.NonEmpty ServiceActionAssociation ->
  BatchAssociateServiceActionWithProvisioningArtifact
newBatchAssociateServiceActionWithProvisioningArtifact :: NonEmpty ServiceActionAssociation
-> BatchAssociateServiceActionWithProvisioningArtifact
newBatchAssociateServiceActionWithProvisioningArtifact
  NonEmpty ServiceActionAssociation
pServiceActionAssociations_ =
    BatchAssociateServiceActionWithProvisioningArtifact'
      { $sel:acceptLanguage:BatchAssociateServiceActionWithProvisioningArtifact' :: Maybe Text
acceptLanguage =
          forall a. Maybe a
Prelude.Nothing,
        $sel:serviceActionAssociations:BatchAssociateServiceActionWithProvisioningArtifact' :: NonEmpty ServiceActionAssociation
serviceActionAssociations =
          forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
            forall t b. AReview t b -> b -> t
Lens.# NonEmpty ServiceActionAssociation
pServiceActionAssociations_
      }

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

-- | One or more associations, each consisting of the Action ID, the Product
-- ID, and the Provisioning Artifact ID.
batchAssociateServiceActionWithProvisioningArtifact_serviceActionAssociations :: Lens.Lens' BatchAssociateServiceActionWithProvisioningArtifact (Prelude.NonEmpty ServiceActionAssociation)
batchAssociateServiceActionWithProvisioningArtifact_serviceActionAssociations :: Lens'
  BatchAssociateServiceActionWithProvisioningArtifact
  (NonEmpty ServiceActionAssociation)
batchAssociateServiceActionWithProvisioningArtifact_serviceActionAssociations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchAssociateServiceActionWithProvisioningArtifact' {NonEmpty ServiceActionAssociation
serviceActionAssociations :: NonEmpty ServiceActionAssociation
$sel:serviceActionAssociations:BatchAssociateServiceActionWithProvisioningArtifact' :: BatchAssociateServiceActionWithProvisioningArtifact
-> NonEmpty ServiceActionAssociation
serviceActionAssociations} -> NonEmpty ServiceActionAssociation
serviceActionAssociations) (\s :: BatchAssociateServiceActionWithProvisioningArtifact
s@BatchAssociateServiceActionWithProvisioningArtifact' {} NonEmpty ServiceActionAssociation
a -> BatchAssociateServiceActionWithProvisioningArtifact
s {$sel:serviceActionAssociations:BatchAssociateServiceActionWithProvisioningArtifact' :: NonEmpty ServiceActionAssociation
serviceActionAssociations = NonEmpty ServiceActionAssociation
a} :: BatchAssociateServiceActionWithProvisioningArtifact) 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

instance
  Core.AWSRequest
    BatchAssociateServiceActionWithProvisioningArtifact
  where
  type
    AWSResponse
      BatchAssociateServiceActionWithProvisioningArtifact =
      BatchAssociateServiceActionWithProvisioningArtifactResponse
  request :: (Service -> Service)
-> BatchAssociateServiceActionWithProvisioningArtifact
-> Request BatchAssociateServiceActionWithProvisioningArtifact
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 BatchAssociateServiceActionWithProvisioningArtifact
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse BatchAssociateServiceActionWithProvisioningArtifact)))
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 [FailedServiceActionAssociation]
-> Int
-> BatchAssociateServiceActionWithProvisioningArtifactResponse
BatchAssociateServiceActionWithProvisioningArtifactResponse'
            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
"FailedServiceActionAssociations"
                            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance
  Prelude.Hashable
    BatchAssociateServiceActionWithProvisioningArtifact
  where
  hashWithSalt :: Int -> BatchAssociateServiceActionWithProvisioningArtifact -> Int
hashWithSalt
    Int
_salt
    BatchAssociateServiceActionWithProvisioningArtifact' {Maybe Text
NonEmpty ServiceActionAssociation
serviceActionAssociations :: NonEmpty ServiceActionAssociation
acceptLanguage :: Maybe Text
$sel:serviceActionAssociations:BatchAssociateServiceActionWithProvisioningArtifact' :: BatchAssociateServiceActionWithProvisioningArtifact
-> NonEmpty ServiceActionAssociation
$sel:acceptLanguage:BatchAssociateServiceActionWithProvisioningArtifact' :: BatchAssociateServiceActionWithProvisioningArtifact -> 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` NonEmpty ServiceActionAssociation
serviceActionAssociations

instance
  Prelude.NFData
    BatchAssociateServiceActionWithProvisioningArtifact
  where
  rnf :: BatchAssociateServiceActionWithProvisioningArtifact -> ()
rnf
    BatchAssociateServiceActionWithProvisioningArtifact' {Maybe Text
NonEmpty ServiceActionAssociation
serviceActionAssociations :: NonEmpty ServiceActionAssociation
acceptLanguage :: Maybe Text
$sel:serviceActionAssociations:BatchAssociateServiceActionWithProvisioningArtifact' :: BatchAssociateServiceActionWithProvisioningArtifact
-> NonEmpty ServiceActionAssociation
$sel:acceptLanguage:BatchAssociateServiceActionWithProvisioningArtifact' :: BatchAssociateServiceActionWithProvisioningArtifact -> 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 NonEmpty ServiceActionAssociation
serviceActionAssociations

instance
  Data.ToHeaders
    BatchAssociateServiceActionWithProvisioningArtifact
  where
  toHeaders :: BatchAssociateServiceActionWithProvisioningArtifact
-> 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.BatchAssociateServiceActionWithProvisioningArtifact" ::
                          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
    BatchAssociateServiceActionWithProvisioningArtifact
  where
  toJSON :: BatchAssociateServiceActionWithProvisioningArtifact -> Value
toJSON
    BatchAssociateServiceActionWithProvisioningArtifact' {Maybe Text
NonEmpty ServiceActionAssociation
serviceActionAssociations :: NonEmpty ServiceActionAssociation
acceptLanguage :: Maybe Text
$sel:serviceActionAssociations:BatchAssociateServiceActionWithProvisioningArtifact' :: BatchAssociateServiceActionWithProvisioningArtifact
-> NonEmpty ServiceActionAssociation
$sel:acceptLanguage:BatchAssociateServiceActionWithProvisioningArtifact' :: BatchAssociateServiceActionWithProvisioningArtifact -> 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
"ServiceActionAssociations"
                    forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty ServiceActionAssociation
serviceActionAssociations
                )
            ]
        )

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

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

-- | /See:/ 'newBatchAssociateServiceActionWithProvisioningArtifactResponse' smart constructor.
data BatchAssociateServiceActionWithProvisioningArtifactResponse = BatchAssociateServiceActionWithProvisioningArtifactResponse'
  { -- | An object that contains a list of errors, along with information to help
    -- you identify the self-service action.
    BatchAssociateServiceActionWithProvisioningArtifactResponse
-> Maybe [FailedServiceActionAssociation]
failedServiceActionAssociations :: Prelude.Maybe [FailedServiceActionAssociation],
    -- | The response's http status code.
    BatchAssociateServiceActionWithProvisioningArtifactResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (BatchAssociateServiceActionWithProvisioningArtifactResponse
-> BatchAssociateServiceActionWithProvisioningArtifactResponse
-> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchAssociateServiceActionWithProvisioningArtifactResponse
-> BatchAssociateServiceActionWithProvisioningArtifactResponse
-> Bool
$c/= :: BatchAssociateServiceActionWithProvisioningArtifactResponse
-> BatchAssociateServiceActionWithProvisioningArtifactResponse
-> Bool
== :: BatchAssociateServiceActionWithProvisioningArtifactResponse
-> BatchAssociateServiceActionWithProvisioningArtifactResponse
-> Bool
$c== :: BatchAssociateServiceActionWithProvisioningArtifactResponse
-> BatchAssociateServiceActionWithProvisioningArtifactResponse
-> Bool
Prelude.Eq, ReadPrec
  [BatchAssociateServiceActionWithProvisioningArtifactResponse]
ReadPrec
  BatchAssociateServiceActionWithProvisioningArtifactResponse
Int
-> ReadS
     BatchAssociateServiceActionWithProvisioningArtifactResponse
ReadS [BatchAssociateServiceActionWithProvisioningArtifactResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec
  [BatchAssociateServiceActionWithProvisioningArtifactResponse]
$creadListPrec :: ReadPrec
  [BatchAssociateServiceActionWithProvisioningArtifactResponse]
readPrec :: ReadPrec
  BatchAssociateServiceActionWithProvisioningArtifactResponse
$creadPrec :: ReadPrec
  BatchAssociateServiceActionWithProvisioningArtifactResponse
readList :: ReadS [BatchAssociateServiceActionWithProvisioningArtifactResponse]
$creadList :: ReadS [BatchAssociateServiceActionWithProvisioningArtifactResponse]
readsPrec :: Int
-> ReadS
     BatchAssociateServiceActionWithProvisioningArtifactResponse
$creadsPrec :: Int
-> ReadS
     BatchAssociateServiceActionWithProvisioningArtifactResponse
Prelude.Read, Int
-> BatchAssociateServiceActionWithProvisioningArtifactResponse
-> ShowS
[BatchAssociateServiceActionWithProvisioningArtifactResponse]
-> ShowS
BatchAssociateServiceActionWithProvisioningArtifactResponse
-> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchAssociateServiceActionWithProvisioningArtifactResponse]
-> ShowS
$cshowList :: [BatchAssociateServiceActionWithProvisioningArtifactResponse]
-> ShowS
show :: BatchAssociateServiceActionWithProvisioningArtifactResponse
-> String
$cshow :: BatchAssociateServiceActionWithProvisioningArtifactResponse
-> String
showsPrec :: Int
-> BatchAssociateServiceActionWithProvisioningArtifactResponse
-> ShowS
$cshowsPrec :: Int
-> BatchAssociateServiceActionWithProvisioningArtifactResponse
-> ShowS
Prelude.Show, forall x.
Rep BatchAssociateServiceActionWithProvisioningArtifactResponse x
-> BatchAssociateServiceActionWithProvisioningArtifactResponse
forall x.
BatchAssociateServiceActionWithProvisioningArtifactResponse
-> Rep
     BatchAssociateServiceActionWithProvisioningArtifactResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchAssociateServiceActionWithProvisioningArtifactResponse x
-> BatchAssociateServiceActionWithProvisioningArtifactResponse
$cfrom :: forall x.
BatchAssociateServiceActionWithProvisioningArtifactResponse
-> Rep
     BatchAssociateServiceActionWithProvisioningArtifactResponse x
Prelude.Generic)

-- |
-- Create a value of 'BatchAssociateServiceActionWithProvisioningArtifactResponse' 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:
--
-- 'failedServiceActionAssociations', 'batchAssociateServiceActionWithProvisioningArtifactResponse_failedServiceActionAssociations' - An object that contains a list of errors, along with information to help
-- you identify the self-service action.
--
-- 'httpStatus', 'batchAssociateServiceActionWithProvisioningArtifactResponse_httpStatus' - The response's http status code.
newBatchAssociateServiceActionWithProvisioningArtifactResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BatchAssociateServiceActionWithProvisioningArtifactResponse
newBatchAssociateServiceActionWithProvisioningArtifactResponse :: Int -> BatchAssociateServiceActionWithProvisioningArtifactResponse
newBatchAssociateServiceActionWithProvisioningArtifactResponse
  Int
pHttpStatus_ =
    BatchAssociateServiceActionWithProvisioningArtifactResponse'
      { $sel:failedServiceActionAssociations:BatchAssociateServiceActionWithProvisioningArtifactResponse' :: Maybe [FailedServiceActionAssociation]
failedServiceActionAssociations =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:BatchAssociateServiceActionWithProvisioningArtifactResponse' :: Int
httpStatus =
          Int
pHttpStatus_
      }

-- | An object that contains a list of errors, along with information to help
-- you identify the self-service action.
batchAssociateServiceActionWithProvisioningArtifactResponse_failedServiceActionAssociations :: Lens.Lens' BatchAssociateServiceActionWithProvisioningArtifactResponse (Prelude.Maybe [FailedServiceActionAssociation])
batchAssociateServiceActionWithProvisioningArtifactResponse_failedServiceActionAssociations :: Lens'
  BatchAssociateServiceActionWithProvisioningArtifactResponse
  (Maybe [FailedServiceActionAssociation])
batchAssociateServiceActionWithProvisioningArtifactResponse_failedServiceActionAssociations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchAssociateServiceActionWithProvisioningArtifactResponse' {Maybe [FailedServiceActionAssociation]
failedServiceActionAssociations :: Maybe [FailedServiceActionAssociation]
$sel:failedServiceActionAssociations:BatchAssociateServiceActionWithProvisioningArtifactResponse' :: BatchAssociateServiceActionWithProvisioningArtifactResponse
-> Maybe [FailedServiceActionAssociation]
failedServiceActionAssociations} -> Maybe [FailedServiceActionAssociation]
failedServiceActionAssociations) (\s :: BatchAssociateServiceActionWithProvisioningArtifactResponse
s@BatchAssociateServiceActionWithProvisioningArtifactResponse' {} Maybe [FailedServiceActionAssociation]
a -> BatchAssociateServiceActionWithProvisioningArtifactResponse
s {$sel:failedServiceActionAssociations:BatchAssociateServiceActionWithProvisioningArtifactResponse' :: Maybe [FailedServiceActionAssociation]
failedServiceActionAssociations = Maybe [FailedServiceActionAssociation]
a} :: BatchAssociateServiceActionWithProvisioningArtifactResponse) 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 response's http status code.
batchAssociateServiceActionWithProvisioningArtifactResponse_httpStatus :: Lens.Lens' BatchAssociateServiceActionWithProvisioningArtifactResponse Prelude.Int
batchAssociateServiceActionWithProvisioningArtifactResponse_httpStatus :: Lens'
  BatchAssociateServiceActionWithProvisioningArtifactResponse Int
batchAssociateServiceActionWithProvisioningArtifactResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchAssociateServiceActionWithProvisioningArtifactResponse' {Int
httpStatus :: Int
$sel:httpStatus:BatchAssociateServiceActionWithProvisioningArtifactResponse' :: BatchAssociateServiceActionWithProvisioningArtifactResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: BatchAssociateServiceActionWithProvisioningArtifactResponse
s@BatchAssociateServiceActionWithProvisioningArtifactResponse' {} Int
a -> BatchAssociateServiceActionWithProvisioningArtifactResponse
s {$sel:httpStatus:BatchAssociateServiceActionWithProvisioningArtifactResponse' :: Int
httpStatus = Int
a} :: BatchAssociateServiceActionWithProvisioningArtifactResponse)

instance
  Prelude.NFData
    BatchAssociateServiceActionWithProvisioningArtifactResponse
  where
  rnf :: BatchAssociateServiceActionWithProvisioningArtifactResponse -> ()
rnf
    BatchAssociateServiceActionWithProvisioningArtifactResponse' {Int
Maybe [FailedServiceActionAssociation]
httpStatus :: Int
failedServiceActionAssociations :: Maybe [FailedServiceActionAssociation]
$sel:httpStatus:BatchAssociateServiceActionWithProvisioningArtifactResponse' :: BatchAssociateServiceActionWithProvisioningArtifactResponse -> Int
$sel:failedServiceActionAssociations:BatchAssociateServiceActionWithProvisioningArtifactResponse' :: BatchAssociateServiceActionWithProvisioningArtifactResponse
-> Maybe [FailedServiceActionAssociation]
..} =
      forall a. NFData a => a -> ()
Prelude.rnf Maybe [FailedServiceActionAssociation]
failedServiceActionAssociations
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus