{-# 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.ConnectParticipant.CompleteAttachmentUpload
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Allows you to confirm that the attachment has been uploaded using the
-- pre-signed URL provided in StartAttachmentUpload API.
--
-- @ConnectionToken@ is used for invoking this API instead of
-- @ParticipantToken@.
--
-- The Amazon Connect Participant Service APIs do not use
-- <https://docs.aws.amazon.com/general/latest/gr/signature-version-4.html Signature Version 4 authentication>.
module Amazonka.ConnectParticipant.CompleteAttachmentUpload
  ( -- * Creating a Request
    CompleteAttachmentUpload (..),
    newCompleteAttachmentUpload,

    -- * Request Lenses
    completeAttachmentUpload_attachmentIds,
    completeAttachmentUpload_clientToken,
    completeAttachmentUpload_connectionToken,

    -- * Destructuring the Response
    CompleteAttachmentUploadResponse (..),
    newCompleteAttachmentUploadResponse,

    -- * Response Lenses
    completeAttachmentUploadResponse_httpStatus,
  )
where

import Amazonka.ConnectParticipant.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:/ 'newCompleteAttachmentUpload' smart constructor.
data CompleteAttachmentUpload = CompleteAttachmentUpload'
  { -- | A list of unique identifiers for the attachments.
    CompleteAttachmentUpload -> NonEmpty Text
attachmentIds :: Prelude.NonEmpty Prelude.Text,
    -- | A unique, case-sensitive identifier that you provide to ensure the
    -- idempotency of the request. If not provided, the Amazon Web Services SDK
    -- populates this field. For more information about idempotency, see
    -- <https://aws.amazon.com/builders-library/making-retries-safe-with-idempotent-APIs/ Making retries safe with idempotent APIs>.
    CompleteAttachmentUpload -> Text
clientToken :: Prelude.Text,
    -- | The authentication token associated with the participant\'s connection.
    CompleteAttachmentUpload -> Text
connectionToken :: Prelude.Text
  }
  deriving (CompleteAttachmentUpload -> CompleteAttachmentUpload -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompleteAttachmentUpload -> CompleteAttachmentUpload -> Bool
$c/= :: CompleteAttachmentUpload -> CompleteAttachmentUpload -> Bool
== :: CompleteAttachmentUpload -> CompleteAttachmentUpload -> Bool
$c== :: CompleteAttachmentUpload -> CompleteAttachmentUpload -> Bool
Prelude.Eq, ReadPrec [CompleteAttachmentUpload]
ReadPrec CompleteAttachmentUpload
Int -> ReadS CompleteAttachmentUpload
ReadS [CompleteAttachmentUpload]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CompleteAttachmentUpload]
$creadListPrec :: ReadPrec [CompleteAttachmentUpload]
readPrec :: ReadPrec CompleteAttachmentUpload
$creadPrec :: ReadPrec CompleteAttachmentUpload
readList :: ReadS [CompleteAttachmentUpload]
$creadList :: ReadS [CompleteAttachmentUpload]
readsPrec :: Int -> ReadS CompleteAttachmentUpload
$creadsPrec :: Int -> ReadS CompleteAttachmentUpload
Prelude.Read, Int -> CompleteAttachmentUpload -> ShowS
[CompleteAttachmentUpload] -> ShowS
CompleteAttachmentUpload -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CompleteAttachmentUpload] -> ShowS
$cshowList :: [CompleteAttachmentUpload] -> ShowS
show :: CompleteAttachmentUpload -> String
$cshow :: CompleteAttachmentUpload -> String
showsPrec :: Int -> CompleteAttachmentUpload -> ShowS
$cshowsPrec :: Int -> CompleteAttachmentUpload -> ShowS
Prelude.Show, forall x.
Rep CompleteAttachmentUpload x -> CompleteAttachmentUpload
forall x.
CompleteAttachmentUpload -> Rep CompleteAttachmentUpload x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CompleteAttachmentUpload x -> CompleteAttachmentUpload
$cfrom :: forall x.
CompleteAttachmentUpload -> Rep CompleteAttachmentUpload x
Prelude.Generic)

-- |
-- Create a value of 'CompleteAttachmentUpload' 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:
--
-- 'attachmentIds', 'completeAttachmentUpload_attachmentIds' - A list of unique identifiers for the attachments.
--
-- 'clientToken', 'completeAttachmentUpload_clientToken' - A unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request. If not provided, the Amazon Web Services SDK
-- populates this field. For more information about idempotency, see
-- <https://aws.amazon.com/builders-library/making-retries-safe-with-idempotent-APIs/ Making retries safe with idempotent APIs>.
--
-- 'connectionToken', 'completeAttachmentUpload_connectionToken' - The authentication token associated with the participant\'s connection.
newCompleteAttachmentUpload ::
  -- | 'attachmentIds'
  Prelude.NonEmpty Prelude.Text ->
  -- | 'clientToken'
  Prelude.Text ->
  -- | 'connectionToken'
  Prelude.Text ->
  CompleteAttachmentUpload
newCompleteAttachmentUpload :: NonEmpty Text -> Text -> Text -> CompleteAttachmentUpload
newCompleteAttachmentUpload
  NonEmpty Text
pAttachmentIds_
  Text
pClientToken_
  Text
pConnectionToken_ =
    CompleteAttachmentUpload'
      { $sel:attachmentIds:CompleteAttachmentUpload' :: NonEmpty Text
attachmentIds =
          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
pAttachmentIds_,
        $sel:clientToken:CompleteAttachmentUpload' :: Text
clientToken = Text
pClientToken_,
        $sel:connectionToken:CompleteAttachmentUpload' :: Text
connectionToken = Text
pConnectionToken_
      }

-- | A list of unique identifiers for the attachments.
completeAttachmentUpload_attachmentIds :: Lens.Lens' CompleteAttachmentUpload (Prelude.NonEmpty Prelude.Text)
completeAttachmentUpload_attachmentIds :: Lens' CompleteAttachmentUpload (NonEmpty Text)
completeAttachmentUpload_attachmentIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompleteAttachmentUpload' {NonEmpty Text
attachmentIds :: NonEmpty Text
$sel:attachmentIds:CompleteAttachmentUpload' :: CompleteAttachmentUpload -> NonEmpty Text
attachmentIds} -> NonEmpty Text
attachmentIds) (\s :: CompleteAttachmentUpload
s@CompleteAttachmentUpload' {} NonEmpty Text
a -> CompleteAttachmentUpload
s {$sel:attachmentIds:CompleteAttachmentUpload' :: NonEmpty Text
attachmentIds = NonEmpty Text
a} :: CompleteAttachmentUpload) 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

-- | A unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request. If not provided, the Amazon Web Services SDK
-- populates this field. For more information about idempotency, see
-- <https://aws.amazon.com/builders-library/making-retries-safe-with-idempotent-APIs/ Making retries safe with idempotent APIs>.
completeAttachmentUpload_clientToken :: Lens.Lens' CompleteAttachmentUpload Prelude.Text
completeAttachmentUpload_clientToken :: Lens' CompleteAttachmentUpload Text
completeAttachmentUpload_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompleteAttachmentUpload' {Text
clientToken :: Text
$sel:clientToken:CompleteAttachmentUpload' :: CompleteAttachmentUpload -> Text
clientToken} -> Text
clientToken) (\s :: CompleteAttachmentUpload
s@CompleteAttachmentUpload' {} Text
a -> CompleteAttachmentUpload
s {$sel:clientToken:CompleteAttachmentUpload' :: Text
clientToken = Text
a} :: CompleteAttachmentUpload)

-- | The authentication token associated with the participant\'s connection.
completeAttachmentUpload_connectionToken :: Lens.Lens' CompleteAttachmentUpload Prelude.Text
completeAttachmentUpload_connectionToken :: Lens' CompleteAttachmentUpload Text
completeAttachmentUpload_connectionToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompleteAttachmentUpload' {Text
connectionToken :: Text
$sel:connectionToken:CompleteAttachmentUpload' :: CompleteAttachmentUpload -> Text
connectionToken} -> Text
connectionToken) (\s :: CompleteAttachmentUpload
s@CompleteAttachmentUpload' {} Text
a -> CompleteAttachmentUpload
s {$sel:connectionToken:CompleteAttachmentUpload' :: Text
connectionToken = Text
a} :: CompleteAttachmentUpload)

instance Core.AWSRequest CompleteAttachmentUpload where
  type
    AWSResponse CompleteAttachmentUpload =
      CompleteAttachmentUploadResponse
  request :: (Service -> Service)
-> CompleteAttachmentUpload -> Request CompleteAttachmentUpload
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 CompleteAttachmentUpload
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CompleteAttachmentUpload)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> CompleteAttachmentUploadResponse
CompleteAttachmentUploadResponse'
            forall (f :: * -> *) a b. Functor 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 CompleteAttachmentUpload where
  hashWithSalt :: Int -> CompleteAttachmentUpload -> Int
hashWithSalt Int
_salt CompleteAttachmentUpload' {NonEmpty Text
Text
connectionToken :: Text
clientToken :: Text
attachmentIds :: NonEmpty Text
$sel:connectionToken:CompleteAttachmentUpload' :: CompleteAttachmentUpload -> Text
$sel:clientToken:CompleteAttachmentUpload' :: CompleteAttachmentUpload -> Text
$sel:attachmentIds:CompleteAttachmentUpload' :: CompleteAttachmentUpload -> NonEmpty Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Text
attachmentIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
connectionToken

instance Prelude.NFData CompleteAttachmentUpload where
  rnf :: CompleteAttachmentUpload -> ()
rnf CompleteAttachmentUpload' {NonEmpty Text
Text
connectionToken :: Text
clientToken :: Text
attachmentIds :: NonEmpty Text
$sel:connectionToken:CompleteAttachmentUpload' :: CompleteAttachmentUpload -> Text
$sel:clientToken:CompleteAttachmentUpload' :: CompleteAttachmentUpload -> Text
$sel:attachmentIds:CompleteAttachmentUpload' :: CompleteAttachmentUpload -> NonEmpty Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Text
attachmentIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
connectionToken

instance Data.ToHeaders CompleteAttachmentUpload where
  toHeaders :: CompleteAttachmentUpload -> ResponseHeaders
toHeaders CompleteAttachmentUpload' {NonEmpty Text
Text
connectionToken :: Text
clientToken :: Text
attachmentIds :: NonEmpty Text
$sel:connectionToken:CompleteAttachmentUpload' :: CompleteAttachmentUpload -> Text
$sel:clientToken:CompleteAttachmentUpload' :: CompleteAttachmentUpload -> Text
$sel:attachmentIds:CompleteAttachmentUpload' :: CompleteAttachmentUpload -> NonEmpty Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ HeaderName
"X-Amz-Bearer" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Text
connectionToken,
        HeaderName
"Content-Type"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"application/x-amz-json-1.1" :: Prelude.ByteString)
      ]

instance Data.ToJSON CompleteAttachmentUpload where
  toJSON :: CompleteAttachmentUpload -> Value
toJSON CompleteAttachmentUpload' {NonEmpty Text
Text
connectionToken :: Text
clientToken :: Text
attachmentIds :: NonEmpty Text
$sel:connectionToken:CompleteAttachmentUpload' :: CompleteAttachmentUpload -> Text
$sel:clientToken:CompleteAttachmentUpload' :: CompleteAttachmentUpload -> Text
$sel:attachmentIds:CompleteAttachmentUpload' :: CompleteAttachmentUpload -> NonEmpty Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"AttachmentIds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty Text
attachmentIds),
            forall a. a -> Maybe a
Prelude.Just (Key
"ClientToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
clientToken)
          ]
      )

instance Data.ToPath CompleteAttachmentUpload where
  toPath :: CompleteAttachmentUpload -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const
      ByteString
"/participant/complete-attachment-upload"

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

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

-- |
-- Create a value of 'CompleteAttachmentUploadResponse' 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:
--
-- 'httpStatus', 'completeAttachmentUploadResponse_httpStatus' - The response's http status code.
newCompleteAttachmentUploadResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CompleteAttachmentUploadResponse
newCompleteAttachmentUploadResponse :: Int -> CompleteAttachmentUploadResponse
newCompleteAttachmentUploadResponse Int
pHttpStatus_ =
  CompleteAttachmentUploadResponse'
    { $sel:httpStatus:CompleteAttachmentUploadResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance
  Prelude.NFData
    CompleteAttachmentUploadResponse
  where
  rnf :: CompleteAttachmentUploadResponse -> ()
rnf CompleteAttachmentUploadResponse' {Int
httpStatus :: Int
$sel:httpStatus:CompleteAttachmentUploadResponse' :: CompleteAttachmentUploadResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus