{-# 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.BillingConductor.BatchAssociateResourcesToCustomLineItem
-- 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 batch of resources to a percentage custom line item.
module Amazonka.BillingConductor.BatchAssociateResourcesToCustomLineItem
  ( -- * Creating a Request
    BatchAssociateResourcesToCustomLineItem (..),
    newBatchAssociateResourcesToCustomLineItem,

    -- * Request Lenses
    batchAssociateResourcesToCustomLineItem_billingPeriodRange,
    batchAssociateResourcesToCustomLineItem_targetArn,
    batchAssociateResourcesToCustomLineItem_resourceArns,

    -- * Destructuring the Response
    BatchAssociateResourcesToCustomLineItemResponse (..),
    newBatchAssociateResourcesToCustomLineItemResponse,

    -- * Response Lenses
    batchAssociateResourcesToCustomLineItemResponse_failedAssociatedResources,
    batchAssociateResourcesToCustomLineItemResponse_successfullyAssociatedResources,
    batchAssociateResourcesToCustomLineItemResponse_httpStatus,
  )
where

import Amazonka.BillingConductor.Types
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

-- | /See:/ 'newBatchAssociateResourcesToCustomLineItem' smart constructor.
data BatchAssociateResourcesToCustomLineItem = BatchAssociateResourcesToCustomLineItem'
  { BatchAssociateResourcesToCustomLineItem
-> Maybe CustomLineItemBillingPeriodRange
billingPeriodRange :: Prelude.Maybe CustomLineItemBillingPeriodRange,
    -- | A percentage custom line item ARN to associate the resources to.
    BatchAssociateResourcesToCustomLineItem -> Text
targetArn :: Prelude.Text,
    -- | A list containing the ARNs of the resources to be associated.
    BatchAssociateResourcesToCustomLineItem -> NonEmpty Text
resourceArns :: Prelude.NonEmpty Prelude.Text
  }
  deriving (BatchAssociateResourcesToCustomLineItem
-> BatchAssociateResourcesToCustomLineItem -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchAssociateResourcesToCustomLineItem
-> BatchAssociateResourcesToCustomLineItem -> Bool
$c/= :: BatchAssociateResourcesToCustomLineItem
-> BatchAssociateResourcesToCustomLineItem -> Bool
== :: BatchAssociateResourcesToCustomLineItem
-> BatchAssociateResourcesToCustomLineItem -> Bool
$c== :: BatchAssociateResourcesToCustomLineItem
-> BatchAssociateResourcesToCustomLineItem -> Bool
Prelude.Eq, ReadPrec [BatchAssociateResourcesToCustomLineItem]
ReadPrec BatchAssociateResourcesToCustomLineItem
Int -> ReadS BatchAssociateResourcesToCustomLineItem
ReadS [BatchAssociateResourcesToCustomLineItem]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchAssociateResourcesToCustomLineItem]
$creadListPrec :: ReadPrec [BatchAssociateResourcesToCustomLineItem]
readPrec :: ReadPrec BatchAssociateResourcesToCustomLineItem
$creadPrec :: ReadPrec BatchAssociateResourcesToCustomLineItem
readList :: ReadS [BatchAssociateResourcesToCustomLineItem]
$creadList :: ReadS [BatchAssociateResourcesToCustomLineItem]
readsPrec :: Int -> ReadS BatchAssociateResourcesToCustomLineItem
$creadsPrec :: Int -> ReadS BatchAssociateResourcesToCustomLineItem
Prelude.Read, Int -> BatchAssociateResourcesToCustomLineItem -> ShowS
[BatchAssociateResourcesToCustomLineItem] -> ShowS
BatchAssociateResourcesToCustomLineItem -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchAssociateResourcesToCustomLineItem] -> ShowS
$cshowList :: [BatchAssociateResourcesToCustomLineItem] -> ShowS
show :: BatchAssociateResourcesToCustomLineItem -> String
$cshow :: BatchAssociateResourcesToCustomLineItem -> String
showsPrec :: Int -> BatchAssociateResourcesToCustomLineItem -> ShowS
$cshowsPrec :: Int -> BatchAssociateResourcesToCustomLineItem -> ShowS
Prelude.Show, forall x.
Rep BatchAssociateResourcesToCustomLineItem x
-> BatchAssociateResourcesToCustomLineItem
forall x.
BatchAssociateResourcesToCustomLineItem
-> Rep BatchAssociateResourcesToCustomLineItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchAssociateResourcesToCustomLineItem x
-> BatchAssociateResourcesToCustomLineItem
$cfrom :: forall x.
BatchAssociateResourcesToCustomLineItem
-> Rep BatchAssociateResourcesToCustomLineItem x
Prelude.Generic)

-- |
-- Create a value of 'BatchAssociateResourcesToCustomLineItem' 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:
--
-- 'billingPeriodRange', 'batchAssociateResourcesToCustomLineItem_billingPeriodRange' - Undocumented member.
--
-- 'targetArn', 'batchAssociateResourcesToCustomLineItem_targetArn' - A percentage custom line item ARN to associate the resources to.
--
-- 'resourceArns', 'batchAssociateResourcesToCustomLineItem_resourceArns' - A list containing the ARNs of the resources to be associated.
newBatchAssociateResourcesToCustomLineItem ::
  -- | 'targetArn'
  Prelude.Text ->
  -- | 'resourceArns'
  Prelude.NonEmpty Prelude.Text ->
  BatchAssociateResourcesToCustomLineItem
newBatchAssociateResourcesToCustomLineItem :: Text -> NonEmpty Text -> BatchAssociateResourcesToCustomLineItem
newBatchAssociateResourcesToCustomLineItem
  Text
pTargetArn_
  NonEmpty Text
pResourceArns_ =
    BatchAssociateResourcesToCustomLineItem'
      { $sel:billingPeriodRange:BatchAssociateResourcesToCustomLineItem' :: Maybe CustomLineItemBillingPeriodRange
billingPeriodRange =
          forall a. Maybe a
Prelude.Nothing,
        $sel:targetArn:BatchAssociateResourcesToCustomLineItem' :: Text
targetArn = Text
pTargetArn_,
        $sel:resourceArns:BatchAssociateResourcesToCustomLineItem' :: NonEmpty Text
resourceArns =
          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
pResourceArns_
      }

-- | Undocumented member.
batchAssociateResourcesToCustomLineItem_billingPeriodRange :: Lens.Lens' BatchAssociateResourcesToCustomLineItem (Prelude.Maybe CustomLineItemBillingPeriodRange)
batchAssociateResourcesToCustomLineItem_billingPeriodRange :: Lens'
  BatchAssociateResourcesToCustomLineItem
  (Maybe CustomLineItemBillingPeriodRange)
batchAssociateResourcesToCustomLineItem_billingPeriodRange = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchAssociateResourcesToCustomLineItem' {Maybe CustomLineItemBillingPeriodRange
billingPeriodRange :: Maybe CustomLineItemBillingPeriodRange
$sel:billingPeriodRange:BatchAssociateResourcesToCustomLineItem' :: BatchAssociateResourcesToCustomLineItem
-> Maybe CustomLineItemBillingPeriodRange
billingPeriodRange} -> Maybe CustomLineItemBillingPeriodRange
billingPeriodRange) (\s :: BatchAssociateResourcesToCustomLineItem
s@BatchAssociateResourcesToCustomLineItem' {} Maybe CustomLineItemBillingPeriodRange
a -> BatchAssociateResourcesToCustomLineItem
s {$sel:billingPeriodRange:BatchAssociateResourcesToCustomLineItem' :: Maybe CustomLineItemBillingPeriodRange
billingPeriodRange = Maybe CustomLineItemBillingPeriodRange
a} :: BatchAssociateResourcesToCustomLineItem)

-- | A percentage custom line item ARN to associate the resources to.
batchAssociateResourcesToCustomLineItem_targetArn :: Lens.Lens' BatchAssociateResourcesToCustomLineItem Prelude.Text
batchAssociateResourcesToCustomLineItem_targetArn :: Lens' BatchAssociateResourcesToCustomLineItem Text
batchAssociateResourcesToCustomLineItem_targetArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchAssociateResourcesToCustomLineItem' {Text
targetArn :: Text
$sel:targetArn:BatchAssociateResourcesToCustomLineItem' :: BatchAssociateResourcesToCustomLineItem -> Text
targetArn} -> Text
targetArn) (\s :: BatchAssociateResourcesToCustomLineItem
s@BatchAssociateResourcesToCustomLineItem' {} Text
a -> BatchAssociateResourcesToCustomLineItem
s {$sel:targetArn:BatchAssociateResourcesToCustomLineItem' :: Text
targetArn = Text
a} :: BatchAssociateResourcesToCustomLineItem)

-- | A list containing the ARNs of the resources to be associated.
batchAssociateResourcesToCustomLineItem_resourceArns :: Lens.Lens' BatchAssociateResourcesToCustomLineItem (Prelude.NonEmpty Prelude.Text)
batchAssociateResourcesToCustomLineItem_resourceArns :: Lens' BatchAssociateResourcesToCustomLineItem (NonEmpty Text)
batchAssociateResourcesToCustomLineItem_resourceArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchAssociateResourcesToCustomLineItem' {NonEmpty Text
resourceArns :: NonEmpty Text
$sel:resourceArns:BatchAssociateResourcesToCustomLineItem' :: BatchAssociateResourcesToCustomLineItem -> NonEmpty Text
resourceArns} -> NonEmpty Text
resourceArns) (\s :: BatchAssociateResourcesToCustomLineItem
s@BatchAssociateResourcesToCustomLineItem' {} NonEmpty Text
a -> BatchAssociateResourcesToCustomLineItem
s {$sel:resourceArns:BatchAssociateResourcesToCustomLineItem' :: NonEmpty Text
resourceArns = NonEmpty Text
a} :: BatchAssociateResourcesToCustomLineItem) 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
    BatchAssociateResourcesToCustomLineItem
  where
  type
    AWSResponse
      BatchAssociateResourcesToCustomLineItem =
      BatchAssociateResourcesToCustomLineItemResponse
  request :: (Service -> Service)
-> BatchAssociateResourcesToCustomLineItem
-> Request BatchAssociateResourcesToCustomLineItem
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy BatchAssociateResourcesToCustomLineItem
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse BatchAssociateResourcesToCustomLineItem)))
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 [AssociateResourceResponseElement]
-> Maybe [AssociateResourceResponseElement]
-> Int
-> BatchAssociateResourcesToCustomLineItemResponse
BatchAssociateResourcesToCustomLineItemResponse'
            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
"FailedAssociatedResources"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"SuccessfullyAssociatedResources"
                            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
    BatchAssociateResourcesToCustomLineItem
  where
  hashWithSalt :: Int -> BatchAssociateResourcesToCustomLineItem -> Int
hashWithSalt
    Int
_salt
    BatchAssociateResourcesToCustomLineItem' {Maybe CustomLineItemBillingPeriodRange
NonEmpty Text
Text
resourceArns :: NonEmpty Text
targetArn :: Text
billingPeriodRange :: Maybe CustomLineItemBillingPeriodRange
$sel:resourceArns:BatchAssociateResourcesToCustomLineItem' :: BatchAssociateResourcesToCustomLineItem -> NonEmpty Text
$sel:targetArn:BatchAssociateResourcesToCustomLineItem' :: BatchAssociateResourcesToCustomLineItem -> Text
$sel:billingPeriodRange:BatchAssociateResourcesToCustomLineItem' :: BatchAssociateResourcesToCustomLineItem
-> Maybe CustomLineItemBillingPeriodRange
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CustomLineItemBillingPeriodRange
billingPeriodRange
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
targetArn
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Text
resourceArns

instance
  Prelude.NFData
    BatchAssociateResourcesToCustomLineItem
  where
  rnf :: BatchAssociateResourcesToCustomLineItem -> ()
rnf BatchAssociateResourcesToCustomLineItem' {Maybe CustomLineItemBillingPeriodRange
NonEmpty Text
Text
resourceArns :: NonEmpty Text
targetArn :: Text
billingPeriodRange :: Maybe CustomLineItemBillingPeriodRange
$sel:resourceArns:BatchAssociateResourcesToCustomLineItem' :: BatchAssociateResourcesToCustomLineItem -> NonEmpty Text
$sel:targetArn:BatchAssociateResourcesToCustomLineItem' :: BatchAssociateResourcesToCustomLineItem -> Text
$sel:billingPeriodRange:BatchAssociateResourcesToCustomLineItem' :: BatchAssociateResourcesToCustomLineItem
-> Maybe CustomLineItemBillingPeriodRange
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CustomLineItemBillingPeriodRange
billingPeriodRange
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
targetArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Text
resourceArns

instance
  Data.ToHeaders
    BatchAssociateResourcesToCustomLineItem
  where
  toHeaders :: BatchAssociateResourcesToCustomLineItem -> 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
    BatchAssociateResourcesToCustomLineItem
  where
  toJSON :: BatchAssociateResourcesToCustomLineItem -> Value
toJSON BatchAssociateResourcesToCustomLineItem' {Maybe CustomLineItemBillingPeriodRange
NonEmpty Text
Text
resourceArns :: NonEmpty Text
targetArn :: Text
billingPeriodRange :: Maybe CustomLineItemBillingPeriodRange
$sel:resourceArns:BatchAssociateResourcesToCustomLineItem' :: BatchAssociateResourcesToCustomLineItem -> NonEmpty Text
$sel:targetArn:BatchAssociateResourcesToCustomLineItem' :: BatchAssociateResourcesToCustomLineItem -> Text
$sel:billingPeriodRange:BatchAssociateResourcesToCustomLineItem' :: BatchAssociateResourcesToCustomLineItem
-> Maybe CustomLineItemBillingPeriodRange
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"BillingPeriodRange" 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 CustomLineItemBillingPeriodRange
billingPeriodRange,
            forall a. a -> Maybe a
Prelude.Just (Key
"TargetArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
targetArn),
            forall a. a -> Maybe a
Prelude.Just (Key
"ResourceArns" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty Text
resourceArns)
          ]
      )

instance
  Data.ToPath
    BatchAssociateResourcesToCustomLineItem
  where
  toPath :: BatchAssociateResourcesToCustomLineItem -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const
      ByteString
"/batch-associate-resources-to-custom-line-item"

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

-- | /See:/ 'newBatchAssociateResourcesToCustomLineItemResponse' smart constructor.
data BatchAssociateResourcesToCustomLineItemResponse = BatchAssociateResourcesToCustomLineItemResponse'
  { -- | A list of @AssociateResourceResponseElement@ for each resource that
    -- failed association to a percentage custom line item.
    BatchAssociateResourcesToCustomLineItemResponse
-> Maybe [AssociateResourceResponseElement]
failedAssociatedResources :: Prelude.Maybe [AssociateResourceResponseElement],
    -- | A list of @AssociateResourceResponseElement@ for each resource that\'s
    -- been associated to a percentage custom line item successfully.
    BatchAssociateResourcesToCustomLineItemResponse
-> Maybe [AssociateResourceResponseElement]
successfullyAssociatedResources :: Prelude.Maybe [AssociateResourceResponseElement],
    -- | The response's http status code.
    BatchAssociateResourcesToCustomLineItemResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (BatchAssociateResourcesToCustomLineItemResponse
-> BatchAssociateResourcesToCustomLineItemResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchAssociateResourcesToCustomLineItemResponse
-> BatchAssociateResourcesToCustomLineItemResponse -> Bool
$c/= :: BatchAssociateResourcesToCustomLineItemResponse
-> BatchAssociateResourcesToCustomLineItemResponse -> Bool
== :: BatchAssociateResourcesToCustomLineItemResponse
-> BatchAssociateResourcesToCustomLineItemResponse -> Bool
$c== :: BatchAssociateResourcesToCustomLineItemResponse
-> BatchAssociateResourcesToCustomLineItemResponse -> Bool
Prelude.Eq, ReadPrec [BatchAssociateResourcesToCustomLineItemResponse]
ReadPrec BatchAssociateResourcesToCustomLineItemResponse
Int -> ReadS BatchAssociateResourcesToCustomLineItemResponse
ReadS [BatchAssociateResourcesToCustomLineItemResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchAssociateResourcesToCustomLineItemResponse]
$creadListPrec :: ReadPrec [BatchAssociateResourcesToCustomLineItemResponse]
readPrec :: ReadPrec BatchAssociateResourcesToCustomLineItemResponse
$creadPrec :: ReadPrec BatchAssociateResourcesToCustomLineItemResponse
readList :: ReadS [BatchAssociateResourcesToCustomLineItemResponse]
$creadList :: ReadS [BatchAssociateResourcesToCustomLineItemResponse]
readsPrec :: Int -> ReadS BatchAssociateResourcesToCustomLineItemResponse
$creadsPrec :: Int -> ReadS BatchAssociateResourcesToCustomLineItemResponse
Prelude.Read, Int -> BatchAssociateResourcesToCustomLineItemResponse -> ShowS
[BatchAssociateResourcesToCustomLineItemResponse] -> ShowS
BatchAssociateResourcesToCustomLineItemResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchAssociateResourcesToCustomLineItemResponse] -> ShowS
$cshowList :: [BatchAssociateResourcesToCustomLineItemResponse] -> ShowS
show :: BatchAssociateResourcesToCustomLineItemResponse -> String
$cshow :: BatchAssociateResourcesToCustomLineItemResponse -> String
showsPrec :: Int -> BatchAssociateResourcesToCustomLineItemResponse -> ShowS
$cshowsPrec :: Int -> BatchAssociateResourcesToCustomLineItemResponse -> ShowS
Prelude.Show, forall x.
Rep BatchAssociateResourcesToCustomLineItemResponse x
-> BatchAssociateResourcesToCustomLineItemResponse
forall x.
BatchAssociateResourcesToCustomLineItemResponse
-> Rep BatchAssociateResourcesToCustomLineItemResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchAssociateResourcesToCustomLineItemResponse x
-> BatchAssociateResourcesToCustomLineItemResponse
$cfrom :: forall x.
BatchAssociateResourcesToCustomLineItemResponse
-> Rep BatchAssociateResourcesToCustomLineItemResponse x
Prelude.Generic)

-- |
-- Create a value of 'BatchAssociateResourcesToCustomLineItemResponse' 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:
--
-- 'failedAssociatedResources', 'batchAssociateResourcesToCustomLineItemResponse_failedAssociatedResources' - A list of @AssociateResourceResponseElement@ for each resource that
-- failed association to a percentage custom line item.
--
-- 'successfullyAssociatedResources', 'batchAssociateResourcesToCustomLineItemResponse_successfullyAssociatedResources' - A list of @AssociateResourceResponseElement@ for each resource that\'s
-- been associated to a percentage custom line item successfully.
--
-- 'httpStatus', 'batchAssociateResourcesToCustomLineItemResponse_httpStatus' - The response's http status code.
newBatchAssociateResourcesToCustomLineItemResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BatchAssociateResourcesToCustomLineItemResponse
newBatchAssociateResourcesToCustomLineItemResponse :: Int -> BatchAssociateResourcesToCustomLineItemResponse
newBatchAssociateResourcesToCustomLineItemResponse
  Int
pHttpStatus_ =
    BatchAssociateResourcesToCustomLineItemResponse'
      { $sel:failedAssociatedResources:BatchAssociateResourcesToCustomLineItemResponse' :: Maybe [AssociateResourceResponseElement]
failedAssociatedResources =
          forall a. Maybe a
Prelude.Nothing,
        $sel:successfullyAssociatedResources:BatchAssociateResourcesToCustomLineItemResponse' :: Maybe [AssociateResourceResponseElement]
successfullyAssociatedResources =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:BatchAssociateResourcesToCustomLineItemResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | A list of @AssociateResourceResponseElement@ for each resource that
-- failed association to a percentage custom line item.
batchAssociateResourcesToCustomLineItemResponse_failedAssociatedResources :: Lens.Lens' BatchAssociateResourcesToCustomLineItemResponse (Prelude.Maybe [AssociateResourceResponseElement])
batchAssociateResourcesToCustomLineItemResponse_failedAssociatedResources :: Lens'
  BatchAssociateResourcesToCustomLineItemResponse
  (Maybe [AssociateResourceResponseElement])
batchAssociateResourcesToCustomLineItemResponse_failedAssociatedResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchAssociateResourcesToCustomLineItemResponse' {Maybe [AssociateResourceResponseElement]
failedAssociatedResources :: Maybe [AssociateResourceResponseElement]
$sel:failedAssociatedResources:BatchAssociateResourcesToCustomLineItemResponse' :: BatchAssociateResourcesToCustomLineItemResponse
-> Maybe [AssociateResourceResponseElement]
failedAssociatedResources} -> Maybe [AssociateResourceResponseElement]
failedAssociatedResources) (\s :: BatchAssociateResourcesToCustomLineItemResponse
s@BatchAssociateResourcesToCustomLineItemResponse' {} Maybe [AssociateResourceResponseElement]
a -> BatchAssociateResourcesToCustomLineItemResponse
s {$sel:failedAssociatedResources:BatchAssociateResourcesToCustomLineItemResponse' :: Maybe [AssociateResourceResponseElement]
failedAssociatedResources = Maybe [AssociateResourceResponseElement]
a} :: BatchAssociateResourcesToCustomLineItemResponse) 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

-- | A list of @AssociateResourceResponseElement@ for each resource that\'s
-- been associated to a percentage custom line item successfully.
batchAssociateResourcesToCustomLineItemResponse_successfullyAssociatedResources :: Lens.Lens' BatchAssociateResourcesToCustomLineItemResponse (Prelude.Maybe [AssociateResourceResponseElement])
batchAssociateResourcesToCustomLineItemResponse_successfullyAssociatedResources :: Lens'
  BatchAssociateResourcesToCustomLineItemResponse
  (Maybe [AssociateResourceResponseElement])
batchAssociateResourcesToCustomLineItemResponse_successfullyAssociatedResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchAssociateResourcesToCustomLineItemResponse' {Maybe [AssociateResourceResponseElement]
successfullyAssociatedResources :: Maybe [AssociateResourceResponseElement]
$sel:successfullyAssociatedResources:BatchAssociateResourcesToCustomLineItemResponse' :: BatchAssociateResourcesToCustomLineItemResponse
-> Maybe [AssociateResourceResponseElement]
successfullyAssociatedResources} -> Maybe [AssociateResourceResponseElement]
successfullyAssociatedResources) (\s :: BatchAssociateResourcesToCustomLineItemResponse
s@BatchAssociateResourcesToCustomLineItemResponse' {} Maybe [AssociateResourceResponseElement]
a -> BatchAssociateResourcesToCustomLineItemResponse
s {$sel:successfullyAssociatedResources:BatchAssociateResourcesToCustomLineItemResponse' :: Maybe [AssociateResourceResponseElement]
successfullyAssociatedResources = Maybe [AssociateResourceResponseElement]
a} :: BatchAssociateResourcesToCustomLineItemResponse) 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.
batchAssociateResourcesToCustomLineItemResponse_httpStatus :: Lens.Lens' BatchAssociateResourcesToCustomLineItemResponse Prelude.Int
batchAssociateResourcesToCustomLineItemResponse_httpStatus :: Lens' BatchAssociateResourcesToCustomLineItemResponse Int
batchAssociateResourcesToCustomLineItemResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchAssociateResourcesToCustomLineItemResponse' {Int
httpStatus :: Int
$sel:httpStatus:BatchAssociateResourcesToCustomLineItemResponse' :: BatchAssociateResourcesToCustomLineItemResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: BatchAssociateResourcesToCustomLineItemResponse
s@BatchAssociateResourcesToCustomLineItemResponse' {} Int
a -> BatchAssociateResourcesToCustomLineItemResponse
s {$sel:httpStatus:BatchAssociateResourcesToCustomLineItemResponse' :: Int
httpStatus = Int
a} :: BatchAssociateResourcesToCustomLineItemResponse)

instance
  Prelude.NFData
    BatchAssociateResourcesToCustomLineItemResponse
  where
  rnf :: BatchAssociateResourcesToCustomLineItemResponse -> ()
rnf
    BatchAssociateResourcesToCustomLineItemResponse' {Int
Maybe [AssociateResourceResponseElement]
httpStatus :: Int
successfullyAssociatedResources :: Maybe [AssociateResourceResponseElement]
failedAssociatedResources :: Maybe [AssociateResourceResponseElement]
$sel:httpStatus:BatchAssociateResourcesToCustomLineItemResponse' :: BatchAssociateResourcesToCustomLineItemResponse -> Int
$sel:successfullyAssociatedResources:BatchAssociateResourcesToCustomLineItemResponse' :: BatchAssociateResourcesToCustomLineItemResponse
-> Maybe [AssociateResourceResponseElement]
$sel:failedAssociatedResources:BatchAssociateResourcesToCustomLineItemResponse' :: BatchAssociateResourcesToCustomLineItemResponse
-> Maybe [AssociateResourceResponseElement]
..} =
      forall a. NFData a => a -> ()
Prelude.rnf Maybe [AssociateResourceResponseElement]
failedAssociatedResources
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [AssociateResourceResponseElement]
successfullyAssociatedResources
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus