{-# 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.Support.AddAttachmentsToSet
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Adds one or more attachments to an attachment set.
--
-- An attachment set is a temporary container for attachments that you add
-- to a case or case communication. The set is available for 1 hour after
-- it\'s created. The @expiryTime@ returned in the response is when the set
-- expires.
--
-- -   You must have a Business, Enterprise On-Ramp, or Enterprise Support
--     plan to use the Amazon Web Services Support API.
--
-- -   If you call the Amazon Web Services Support API from an account that
--     doesn\'t have a Business, Enterprise On-Ramp, or Enterprise Support
--     plan, the @SubscriptionRequiredException@ error message appears. For
--     information about changing your support plan, see
--     <http://aws.amazon.com/premiumsupport/ Amazon Web Services Support>.
module Amazonka.Support.AddAttachmentsToSet
  ( -- * Creating a Request
    AddAttachmentsToSet (..),
    newAddAttachmentsToSet,

    -- * Request Lenses
    addAttachmentsToSet_attachmentSetId,
    addAttachmentsToSet_attachments,

    -- * Destructuring the Response
    AddAttachmentsToSetResponse (..),
    newAddAttachmentsToSetResponse,

    -- * Response Lenses
    addAttachmentsToSetResponse_attachmentSetId,
    addAttachmentsToSetResponse_expiryTime,
    addAttachmentsToSetResponse_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.Support.Types

-- | /See:/ 'newAddAttachmentsToSet' smart constructor.
data AddAttachmentsToSet = AddAttachmentsToSet'
  { -- | The ID of the attachment set. If an @attachmentSetId@ is not specified,
    -- a new attachment set is created, and the ID of the set is returned in
    -- the response. If an @attachmentSetId@ is specified, the attachments are
    -- added to the specified set, if it exists.
    AddAttachmentsToSet -> Maybe Text
attachmentSetId :: Prelude.Maybe Prelude.Text,
    -- | One or more attachments to add to the set. You can add up to three
    -- attachments per set. The size limit is 5 MB per attachment.
    --
    -- In the @Attachment@ object, use the @data@ parameter to specify the
    -- contents of the attachment file. In the previous request syntax, the
    -- value for @data@ appear as @blob@, which is represented as a
    -- base64-encoded string. The value for @fileName@ is the name of the
    -- attachment, such as @troubleshoot-screenshot.png@.
    AddAttachmentsToSet -> [Attachment]
attachments :: [Attachment]
  }
  deriving (AddAttachmentsToSet -> AddAttachmentsToSet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddAttachmentsToSet -> AddAttachmentsToSet -> Bool
$c/= :: AddAttachmentsToSet -> AddAttachmentsToSet -> Bool
== :: AddAttachmentsToSet -> AddAttachmentsToSet -> Bool
$c== :: AddAttachmentsToSet -> AddAttachmentsToSet -> Bool
Prelude.Eq, ReadPrec [AddAttachmentsToSet]
ReadPrec AddAttachmentsToSet
Int -> ReadS AddAttachmentsToSet
ReadS [AddAttachmentsToSet]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddAttachmentsToSet]
$creadListPrec :: ReadPrec [AddAttachmentsToSet]
readPrec :: ReadPrec AddAttachmentsToSet
$creadPrec :: ReadPrec AddAttachmentsToSet
readList :: ReadS [AddAttachmentsToSet]
$creadList :: ReadS [AddAttachmentsToSet]
readsPrec :: Int -> ReadS AddAttachmentsToSet
$creadsPrec :: Int -> ReadS AddAttachmentsToSet
Prelude.Read, Int -> AddAttachmentsToSet -> ShowS
[AddAttachmentsToSet] -> ShowS
AddAttachmentsToSet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddAttachmentsToSet] -> ShowS
$cshowList :: [AddAttachmentsToSet] -> ShowS
show :: AddAttachmentsToSet -> String
$cshow :: AddAttachmentsToSet -> String
showsPrec :: Int -> AddAttachmentsToSet -> ShowS
$cshowsPrec :: Int -> AddAttachmentsToSet -> ShowS
Prelude.Show, forall x. Rep AddAttachmentsToSet x -> AddAttachmentsToSet
forall x. AddAttachmentsToSet -> Rep AddAttachmentsToSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddAttachmentsToSet x -> AddAttachmentsToSet
$cfrom :: forall x. AddAttachmentsToSet -> Rep AddAttachmentsToSet x
Prelude.Generic)

-- |
-- Create a value of 'AddAttachmentsToSet' 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:
--
-- 'attachmentSetId', 'addAttachmentsToSet_attachmentSetId' - The ID of the attachment set. If an @attachmentSetId@ is not specified,
-- a new attachment set is created, and the ID of the set is returned in
-- the response. If an @attachmentSetId@ is specified, the attachments are
-- added to the specified set, if it exists.
--
-- 'attachments', 'addAttachmentsToSet_attachments' - One or more attachments to add to the set. You can add up to three
-- attachments per set. The size limit is 5 MB per attachment.
--
-- In the @Attachment@ object, use the @data@ parameter to specify the
-- contents of the attachment file. In the previous request syntax, the
-- value for @data@ appear as @blob@, which is represented as a
-- base64-encoded string. The value for @fileName@ is the name of the
-- attachment, such as @troubleshoot-screenshot.png@.
newAddAttachmentsToSet ::
  AddAttachmentsToSet
newAddAttachmentsToSet :: AddAttachmentsToSet
newAddAttachmentsToSet =
  AddAttachmentsToSet'
    { $sel:attachmentSetId:AddAttachmentsToSet' :: Maybe Text
attachmentSetId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:attachments:AddAttachmentsToSet' :: [Attachment]
attachments = forall a. Monoid a => a
Prelude.mempty
    }

-- | The ID of the attachment set. If an @attachmentSetId@ is not specified,
-- a new attachment set is created, and the ID of the set is returned in
-- the response. If an @attachmentSetId@ is specified, the attachments are
-- added to the specified set, if it exists.
addAttachmentsToSet_attachmentSetId :: Lens.Lens' AddAttachmentsToSet (Prelude.Maybe Prelude.Text)
addAttachmentsToSet_attachmentSetId :: Lens' AddAttachmentsToSet (Maybe Text)
addAttachmentsToSet_attachmentSetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddAttachmentsToSet' {Maybe Text
attachmentSetId :: Maybe Text
$sel:attachmentSetId:AddAttachmentsToSet' :: AddAttachmentsToSet -> Maybe Text
attachmentSetId} -> Maybe Text
attachmentSetId) (\s :: AddAttachmentsToSet
s@AddAttachmentsToSet' {} Maybe Text
a -> AddAttachmentsToSet
s {$sel:attachmentSetId:AddAttachmentsToSet' :: Maybe Text
attachmentSetId = Maybe Text
a} :: AddAttachmentsToSet)

-- | One or more attachments to add to the set. You can add up to three
-- attachments per set. The size limit is 5 MB per attachment.
--
-- In the @Attachment@ object, use the @data@ parameter to specify the
-- contents of the attachment file. In the previous request syntax, the
-- value for @data@ appear as @blob@, which is represented as a
-- base64-encoded string. The value for @fileName@ is the name of the
-- attachment, such as @troubleshoot-screenshot.png@.
addAttachmentsToSet_attachments :: Lens.Lens' AddAttachmentsToSet [Attachment]
addAttachmentsToSet_attachments :: Lens' AddAttachmentsToSet [Attachment]
addAttachmentsToSet_attachments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddAttachmentsToSet' {[Attachment]
attachments :: [Attachment]
$sel:attachments:AddAttachmentsToSet' :: AddAttachmentsToSet -> [Attachment]
attachments} -> [Attachment]
attachments) (\s :: AddAttachmentsToSet
s@AddAttachmentsToSet' {} [Attachment]
a -> AddAttachmentsToSet
s {$sel:attachments:AddAttachmentsToSet' :: [Attachment]
attachments = [Attachment]
a} :: AddAttachmentsToSet) 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 AddAttachmentsToSet where
  type
    AWSResponse AddAttachmentsToSet =
      AddAttachmentsToSetResponse
  request :: (Service -> Service)
-> AddAttachmentsToSet -> Request AddAttachmentsToSet
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 AddAttachmentsToSet
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AddAttachmentsToSet)))
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 Text -> Maybe Text -> Int -> AddAttachmentsToSetResponse
AddAttachmentsToSetResponse'
            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
"attachmentSetId")
            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
"expiryTime")
            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 AddAttachmentsToSet where
  hashWithSalt :: Int -> AddAttachmentsToSet -> Int
hashWithSalt Int
_salt AddAttachmentsToSet' {[Attachment]
Maybe Text
attachments :: [Attachment]
attachmentSetId :: Maybe Text
$sel:attachments:AddAttachmentsToSet' :: AddAttachmentsToSet -> [Attachment]
$sel:attachmentSetId:AddAttachmentsToSet' :: AddAttachmentsToSet -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
attachmentSetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Attachment]
attachments

instance Prelude.NFData AddAttachmentsToSet where
  rnf :: AddAttachmentsToSet -> ()
rnf AddAttachmentsToSet' {[Attachment]
Maybe Text
attachments :: [Attachment]
attachmentSetId :: Maybe Text
$sel:attachments:AddAttachmentsToSet' :: AddAttachmentsToSet -> [Attachment]
$sel:attachmentSetId:AddAttachmentsToSet' :: AddAttachmentsToSet -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
attachmentSetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Attachment]
attachments

instance Data.ToHeaders AddAttachmentsToSet where
  toHeaders :: AddAttachmentsToSet -> 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
"AWSSupport_20130415.AddAttachmentsToSet" ::
                          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 AddAttachmentsToSet where
  toJSON :: AddAttachmentsToSet -> Value
toJSON AddAttachmentsToSet' {[Attachment]
Maybe Text
attachments :: [Attachment]
attachmentSetId :: Maybe Text
$sel:attachments:AddAttachmentsToSet' :: AddAttachmentsToSet -> [Attachment]
$sel:attachmentSetId:AddAttachmentsToSet' :: AddAttachmentsToSet -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"attachmentSetId" 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
attachmentSetId,
            forall a. a -> Maybe a
Prelude.Just (Key
"attachments" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Attachment]
attachments)
          ]
      )

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

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

-- | The ID and expiry time of the attachment set returned by the
-- AddAttachmentsToSet operation.
--
-- /See:/ 'newAddAttachmentsToSetResponse' smart constructor.
data AddAttachmentsToSetResponse = AddAttachmentsToSetResponse'
  { -- | The ID of the attachment set. If an @attachmentSetId@ was not specified,
    -- a new attachment set is created, and the ID of the set is returned in
    -- the response. If an @attachmentSetId@ was specified, the attachments are
    -- added to the specified set, if it exists.
    AddAttachmentsToSetResponse -> Maybe Text
attachmentSetId :: Prelude.Maybe Prelude.Text,
    -- | The time and date when the attachment set expires.
    AddAttachmentsToSetResponse -> Maybe Text
expiryTime :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    AddAttachmentsToSetResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (AddAttachmentsToSetResponse -> AddAttachmentsToSetResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddAttachmentsToSetResponse -> AddAttachmentsToSetResponse -> Bool
$c/= :: AddAttachmentsToSetResponse -> AddAttachmentsToSetResponse -> Bool
== :: AddAttachmentsToSetResponse -> AddAttachmentsToSetResponse -> Bool
$c== :: AddAttachmentsToSetResponse -> AddAttachmentsToSetResponse -> Bool
Prelude.Eq, ReadPrec [AddAttachmentsToSetResponse]
ReadPrec AddAttachmentsToSetResponse
Int -> ReadS AddAttachmentsToSetResponse
ReadS [AddAttachmentsToSetResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddAttachmentsToSetResponse]
$creadListPrec :: ReadPrec [AddAttachmentsToSetResponse]
readPrec :: ReadPrec AddAttachmentsToSetResponse
$creadPrec :: ReadPrec AddAttachmentsToSetResponse
readList :: ReadS [AddAttachmentsToSetResponse]
$creadList :: ReadS [AddAttachmentsToSetResponse]
readsPrec :: Int -> ReadS AddAttachmentsToSetResponse
$creadsPrec :: Int -> ReadS AddAttachmentsToSetResponse
Prelude.Read, Int -> AddAttachmentsToSetResponse -> ShowS
[AddAttachmentsToSetResponse] -> ShowS
AddAttachmentsToSetResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddAttachmentsToSetResponse] -> ShowS
$cshowList :: [AddAttachmentsToSetResponse] -> ShowS
show :: AddAttachmentsToSetResponse -> String
$cshow :: AddAttachmentsToSetResponse -> String
showsPrec :: Int -> AddAttachmentsToSetResponse -> ShowS
$cshowsPrec :: Int -> AddAttachmentsToSetResponse -> ShowS
Prelude.Show, forall x.
Rep AddAttachmentsToSetResponse x -> AddAttachmentsToSetResponse
forall x.
AddAttachmentsToSetResponse -> Rep AddAttachmentsToSetResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AddAttachmentsToSetResponse x -> AddAttachmentsToSetResponse
$cfrom :: forall x.
AddAttachmentsToSetResponse -> Rep AddAttachmentsToSetResponse x
Prelude.Generic)

-- |
-- Create a value of 'AddAttachmentsToSetResponse' 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:
--
-- 'attachmentSetId', 'addAttachmentsToSetResponse_attachmentSetId' - The ID of the attachment set. If an @attachmentSetId@ was not specified,
-- a new attachment set is created, and the ID of the set is returned in
-- the response. If an @attachmentSetId@ was specified, the attachments are
-- added to the specified set, if it exists.
--
-- 'expiryTime', 'addAttachmentsToSetResponse_expiryTime' - The time and date when the attachment set expires.
--
-- 'httpStatus', 'addAttachmentsToSetResponse_httpStatus' - The response's http status code.
newAddAttachmentsToSetResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AddAttachmentsToSetResponse
newAddAttachmentsToSetResponse :: Int -> AddAttachmentsToSetResponse
newAddAttachmentsToSetResponse Int
pHttpStatus_ =
  AddAttachmentsToSetResponse'
    { $sel:attachmentSetId:AddAttachmentsToSetResponse' :: Maybe Text
attachmentSetId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:expiryTime:AddAttachmentsToSetResponse' :: Maybe Text
expiryTime = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:AddAttachmentsToSetResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ID of the attachment set. If an @attachmentSetId@ was not specified,
-- a new attachment set is created, and the ID of the set is returned in
-- the response. If an @attachmentSetId@ was specified, the attachments are
-- added to the specified set, if it exists.
addAttachmentsToSetResponse_attachmentSetId :: Lens.Lens' AddAttachmentsToSetResponse (Prelude.Maybe Prelude.Text)
addAttachmentsToSetResponse_attachmentSetId :: Lens' AddAttachmentsToSetResponse (Maybe Text)
addAttachmentsToSetResponse_attachmentSetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddAttachmentsToSetResponse' {Maybe Text
attachmentSetId :: Maybe Text
$sel:attachmentSetId:AddAttachmentsToSetResponse' :: AddAttachmentsToSetResponse -> Maybe Text
attachmentSetId} -> Maybe Text
attachmentSetId) (\s :: AddAttachmentsToSetResponse
s@AddAttachmentsToSetResponse' {} Maybe Text
a -> AddAttachmentsToSetResponse
s {$sel:attachmentSetId:AddAttachmentsToSetResponse' :: Maybe Text
attachmentSetId = Maybe Text
a} :: AddAttachmentsToSetResponse)

-- | The time and date when the attachment set expires.
addAttachmentsToSetResponse_expiryTime :: Lens.Lens' AddAttachmentsToSetResponse (Prelude.Maybe Prelude.Text)
addAttachmentsToSetResponse_expiryTime :: Lens' AddAttachmentsToSetResponse (Maybe Text)
addAttachmentsToSetResponse_expiryTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddAttachmentsToSetResponse' {Maybe Text
expiryTime :: Maybe Text
$sel:expiryTime:AddAttachmentsToSetResponse' :: AddAttachmentsToSetResponse -> Maybe Text
expiryTime} -> Maybe Text
expiryTime) (\s :: AddAttachmentsToSetResponse
s@AddAttachmentsToSetResponse' {} Maybe Text
a -> AddAttachmentsToSetResponse
s {$sel:expiryTime:AddAttachmentsToSetResponse' :: Maybe Text
expiryTime = Maybe Text
a} :: AddAttachmentsToSetResponse)

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

instance Prelude.NFData AddAttachmentsToSetResponse where
  rnf :: AddAttachmentsToSetResponse -> ()
rnf AddAttachmentsToSetResponse' {Int
Maybe Text
httpStatus :: Int
expiryTime :: Maybe Text
attachmentSetId :: Maybe Text
$sel:httpStatus:AddAttachmentsToSetResponse' :: AddAttachmentsToSetResponse -> Int
$sel:expiryTime:AddAttachmentsToSetResponse' :: AddAttachmentsToSetResponse -> Maybe Text
$sel:attachmentSetId:AddAttachmentsToSetResponse' :: AddAttachmentsToSetResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
attachmentSetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
expiryTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus