{-# 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.IoTSiteWise.BatchAssociateProjectAssets
-- 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 a group (batch) of assets with an IoT SiteWise Monitor
-- project.
module Amazonka.IoTSiteWise.BatchAssociateProjectAssets
  ( -- * Creating a Request
    BatchAssociateProjectAssets (..),
    newBatchAssociateProjectAssets,

    -- * Request Lenses
    batchAssociateProjectAssets_clientToken,
    batchAssociateProjectAssets_projectId,
    batchAssociateProjectAssets_assetIds,

    -- * Destructuring the Response
    BatchAssociateProjectAssetsResponse (..),
    newBatchAssociateProjectAssetsResponse,

    -- * Response Lenses
    batchAssociateProjectAssetsResponse_errors,
    batchAssociateProjectAssetsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newBatchAssociateProjectAssets' smart constructor.
data BatchAssociateProjectAssets = BatchAssociateProjectAssets'
  { -- | A unique case-sensitive identifier that you can provide to ensure the
    -- idempotency of the request. Don\'t reuse this client token if a new
    -- idempotent request is required.
    BatchAssociateProjectAssets -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The ID of the project to which to associate the assets.
    BatchAssociateProjectAssets -> Text
projectId :: Prelude.Text,
    -- | The IDs of the assets to be associated to the project.
    BatchAssociateProjectAssets -> NonEmpty Text
assetIds :: Prelude.NonEmpty Prelude.Text
  }
  deriving (BatchAssociateProjectAssets -> BatchAssociateProjectAssets -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchAssociateProjectAssets -> BatchAssociateProjectAssets -> Bool
$c/= :: BatchAssociateProjectAssets -> BatchAssociateProjectAssets -> Bool
== :: BatchAssociateProjectAssets -> BatchAssociateProjectAssets -> Bool
$c== :: BatchAssociateProjectAssets -> BatchAssociateProjectAssets -> Bool
Prelude.Eq, ReadPrec [BatchAssociateProjectAssets]
ReadPrec BatchAssociateProjectAssets
Int -> ReadS BatchAssociateProjectAssets
ReadS [BatchAssociateProjectAssets]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchAssociateProjectAssets]
$creadListPrec :: ReadPrec [BatchAssociateProjectAssets]
readPrec :: ReadPrec BatchAssociateProjectAssets
$creadPrec :: ReadPrec BatchAssociateProjectAssets
readList :: ReadS [BatchAssociateProjectAssets]
$creadList :: ReadS [BatchAssociateProjectAssets]
readsPrec :: Int -> ReadS BatchAssociateProjectAssets
$creadsPrec :: Int -> ReadS BatchAssociateProjectAssets
Prelude.Read, Int -> BatchAssociateProjectAssets -> ShowS
[BatchAssociateProjectAssets] -> ShowS
BatchAssociateProjectAssets -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchAssociateProjectAssets] -> ShowS
$cshowList :: [BatchAssociateProjectAssets] -> ShowS
show :: BatchAssociateProjectAssets -> String
$cshow :: BatchAssociateProjectAssets -> String
showsPrec :: Int -> BatchAssociateProjectAssets -> ShowS
$cshowsPrec :: Int -> BatchAssociateProjectAssets -> ShowS
Prelude.Show, forall x.
Rep BatchAssociateProjectAssets x -> BatchAssociateProjectAssets
forall x.
BatchAssociateProjectAssets -> Rep BatchAssociateProjectAssets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchAssociateProjectAssets x -> BatchAssociateProjectAssets
$cfrom :: forall x.
BatchAssociateProjectAssets -> Rep BatchAssociateProjectAssets x
Prelude.Generic)

-- |
-- Create a value of 'BatchAssociateProjectAssets' 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:
--
-- 'clientToken', 'batchAssociateProjectAssets_clientToken' - A unique case-sensitive identifier that you can provide to ensure the
-- idempotency of the request. Don\'t reuse this client token if a new
-- idempotent request is required.
--
-- 'projectId', 'batchAssociateProjectAssets_projectId' - The ID of the project to which to associate the assets.
--
-- 'assetIds', 'batchAssociateProjectAssets_assetIds' - The IDs of the assets to be associated to the project.
newBatchAssociateProjectAssets ::
  -- | 'projectId'
  Prelude.Text ->
  -- | 'assetIds'
  Prelude.NonEmpty Prelude.Text ->
  BatchAssociateProjectAssets
newBatchAssociateProjectAssets :: Text -> NonEmpty Text -> BatchAssociateProjectAssets
newBatchAssociateProjectAssets Text
pProjectId_ NonEmpty Text
pAssetIds_ =
  BatchAssociateProjectAssets'
    { $sel:clientToken:BatchAssociateProjectAssets' :: Maybe Text
clientToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:projectId:BatchAssociateProjectAssets' :: Text
projectId = Text
pProjectId_,
      $sel:assetIds:BatchAssociateProjectAssets' :: NonEmpty Text
assetIds = 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 Text
pAssetIds_
    }

-- | A unique case-sensitive identifier that you can provide to ensure the
-- idempotency of the request. Don\'t reuse this client token if a new
-- idempotent request is required.
batchAssociateProjectAssets_clientToken :: Lens.Lens' BatchAssociateProjectAssets (Prelude.Maybe Prelude.Text)
batchAssociateProjectAssets_clientToken :: Lens' BatchAssociateProjectAssets (Maybe Text)
batchAssociateProjectAssets_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchAssociateProjectAssets' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:BatchAssociateProjectAssets' :: BatchAssociateProjectAssets -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: BatchAssociateProjectAssets
s@BatchAssociateProjectAssets' {} Maybe Text
a -> BatchAssociateProjectAssets
s {$sel:clientToken:BatchAssociateProjectAssets' :: Maybe Text
clientToken = Maybe Text
a} :: BatchAssociateProjectAssets)

-- | The ID of the project to which to associate the assets.
batchAssociateProjectAssets_projectId :: Lens.Lens' BatchAssociateProjectAssets Prelude.Text
batchAssociateProjectAssets_projectId :: Lens' BatchAssociateProjectAssets Text
batchAssociateProjectAssets_projectId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchAssociateProjectAssets' {Text
projectId :: Text
$sel:projectId:BatchAssociateProjectAssets' :: BatchAssociateProjectAssets -> Text
projectId} -> Text
projectId) (\s :: BatchAssociateProjectAssets
s@BatchAssociateProjectAssets' {} Text
a -> BatchAssociateProjectAssets
s {$sel:projectId:BatchAssociateProjectAssets' :: Text
projectId = Text
a} :: BatchAssociateProjectAssets)

-- | The IDs of the assets to be associated to the project.
batchAssociateProjectAssets_assetIds :: Lens.Lens' BatchAssociateProjectAssets (Prelude.NonEmpty Prelude.Text)
batchAssociateProjectAssets_assetIds :: Lens' BatchAssociateProjectAssets (NonEmpty Text)
batchAssociateProjectAssets_assetIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchAssociateProjectAssets' {NonEmpty Text
assetIds :: NonEmpty Text
$sel:assetIds:BatchAssociateProjectAssets' :: BatchAssociateProjectAssets -> NonEmpty Text
assetIds} -> NonEmpty Text
assetIds) (\s :: BatchAssociateProjectAssets
s@BatchAssociateProjectAssets' {} NonEmpty Text
a -> BatchAssociateProjectAssets
s {$sel:assetIds:BatchAssociateProjectAssets' :: NonEmpty Text
assetIds = NonEmpty Text
a} :: BatchAssociateProjectAssets) 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 BatchAssociateProjectAssets where
  type
    AWSResponse BatchAssociateProjectAssets =
      BatchAssociateProjectAssetsResponse
  request :: (Service -> Service)
-> BatchAssociateProjectAssets
-> Request BatchAssociateProjectAssets
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 BatchAssociateProjectAssets
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse BatchAssociateProjectAssets)))
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 [AssetErrorDetails]
-> Int -> BatchAssociateProjectAssetsResponse
BatchAssociateProjectAssetsResponse'
            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
"errors" 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 BatchAssociateProjectAssets where
  hashWithSalt :: Int -> BatchAssociateProjectAssets -> Int
hashWithSalt Int
_salt BatchAssociateProjectAssets' {Maybe Text
NonEmpty Text
Text
assetIds :: NonEmpty Text
projectId :: Text
clientToken :: Maybe Text
$sel:assetIds:BatchAssociateProjectAssets' :: BatchAssociateProjectAssets -> NonEmpty Text
$sel:projectId:BatchAssociateProjectAssets' :: BatchAssociateProjectAssets -> Text
$sel:clientToken:BatchAssociateProjectAssets' :: BatchAssociateProjectAssets -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
projectId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Text
assetIds

instance Prelude.NFData BatchAssociateProjectAssets where
  rnf :: BatchAssociateProjectAssets -> ()
rnf BatchAssociateProjectAssets' {Maybe Text
NonEmpty Text
Text
assetIds :: NonEmpty Text
projectId :: Text
clientToken :: Maybe Text
$sel:assetIds:BatchAssociateProjectAssets' :: BatchAssociateProjectAssets -> NonEmpty Text
$sel:projectId:BatchAssociateProjectAssets' :: BatchAssociateProjectAssets -> Text
$sel:clientToken:BatchAssociateProjectAssets' :: BatchAssociateProjectAssets -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
projectId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Text
assetIds

instance Data.ToHeaders BatchAssociateProjectAssets where
  toHeaders :: BatchAssociateProjectAssets -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON BatchAssociateProjectAssets where
  toJSON :: BatchAssociateProjectAssets -> Value
toJSON BatchAssociateProjectAssets' {Maybe Text
NonEmpty Text
Text
assetIds :: NonEmpty Text
projectId :: Text
clientToken :: Maybe Text
$sel:assetIds:BatchAssociateProjectAssets' :: BatchAssociateProjectAssets -> NonEmpty Text
$sel:projectId:BatchAssociateProjectAssets' :: BatchAssociateProjectAssets -> Text
$sel:clientToken:BatchAssociateProjectAssets' :: BatchAssociateProjectAssets -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"clientToken" 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
clientToken,
            forall a. a -> Maybe a
Prelude.Just (Key
"assetIds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty Text
assetIds)
          ]
      )

instance Data.ToPath BatchAssociateProjectAssets where
  toPath :: BatchAssociateProjectAssets -> ByteString
toPath BatchAssociateProjectAssets' {Maybe Text
NonEmpty Text
Text
assetIds :: NonEmpty Text
projectId :: Text
clientToken :: Maybe Text
$sel:assetIds:BatchAssociateProjectAssets' :: BatchAssociateProjectAssets -> NonEmpty Text
$sel:projectId:BatchAssociateProjectAssets' :: BatchAssociateProjectAssets -> Text
$sel:clientToken:BatchAssociateProjectAssets' :: BatchAssociateProjectAssets -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/projects/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
projectId,
        ByteString
"/assets/associate"
      ]

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

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

-- |
-- Create a value of 'BatchAssociateProjectAssetsResponse' 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:
--
-- 'errors', 'batchAssociateProjectAssetsResponse_errors' - A list of associated error information, if any.
--
-- 'httpStatus', 'batchAssociateProjectAssetsResponse_httpStatus' - The response's http status code.
newBatchAssociateProjectAssetsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BatchAssociateProjectAssetsResponse
newBatchAssociateProjectAssetsResponse :: Int -> BatchAssociateProjectAssetsResponse
newBatchAssociateProjectAssetsResponse Int
pHttpStatus_ =
  BatchAssociateProjectAssetsResponse'
    { $sel:errors:BatchAssociateProjectAssetsResponse' :: Maybe [AssetErrorDetails]
errors =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:BatchAssociateProjectAssetsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of associated error information, if any.
batchAssociateProjectAssetsResponse_errors :: Lens.Lens' BatchAssociateProjectAssetsResponse (Prelude.Maybe [AssetErrorDetails])
batchAssociateProjectAssetsResponse_errors :: Lens'
  BatchAssociateProjectAssetsResponse (Maybe [AssetErrorDetails])
batchAssociateProjectAssetsResponse_errors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchAssociateProjectAssetsResponse' {Maybe [AssetErrorDetails]
errors :: Maybe [AssetErrorDetails]
$sel:errors:BatchAssociateProjectAssetsResponse' :: BatchAssociateProjectAssetsResponse -> Maybe [AssetErrorDetails]
errors} -> Maybe [AssetErrorDetails]
errors) (\s :: BatchAssociateProjectAssetsResponse
s@BatchAssociateProjectAssetsResponse' {} Maybe [AssetErrorDetails]
a -> BatchAssociateProjectAssetsResponse
s {$sel:errors:BatchAssociateProjectAssetsResponse' :: Maybe [AssetErrorDetails]
errors = Maybe [AssetErrorDetails]
a} :: BatchAssociateProjectAssetsResponse) 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.
batchAssociateProjectAssetsResponse_httpStatus :: Lens.Lens' BatchAssociateProjectAssetsResponse Prelude.Int
batchAssociateProjectAssetsResponse_httpStatus :: Lens' BatchAssociateProjectAssetsResponse Int
batchAssociateProjectAssetsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchAssociateProjectAssetsResponse' {Int
httpStatus :: Int
$sel:httpStatus:BatchAssociateProjectAssetsResponse' :: BatchAssociateProjectAssetsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: BatchAssociateProjectAssetsResponse
s@BatchAssociateProjectAssetsResponse' {} Int
a -> BatchAssociateProjectAssetsResponse
s {$sel:httpStatus:BatchAssociateProjectAssetsResponse' :: Int
httpStatus = Int
a} :: BatchAssociateProjectAssetsResponse)

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