{-# 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.CognitoSync.GetBulkPublishDetails
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Get the status of the last BulkPublish operation for an identity pool.
--
-- This API can only be called with developer credentials. You cannot call
-- this API with the temporary user credentials provided by Cognito
-- Identity.
module Amazonka.CognitoSync.GetBulkPublishDetails
  ( -- * Creating a Request
    GetBulkPublishDetails (..),
    newGetBulkPublishDetails,

    -- * Request Lenses
    getBulkPublishDetails_identityPoolId,

    -- * Destructuring the Response
    GetBulkPublishDetailsResponse (..),
    newGetBulkPublishDetailsResponse,

    -- * Response Lenses
    getBulkPublishDetailsResponse_bulkPublishCompleteTime,
    getBulkPublishDetailsResponse_bulkPublishStartTime,
    getBulkPublishDetailsResponse_bulkPublishStatus,
    getBulkPublishDetailsResponse_failureMessage,
    getBulkPublishDetailsResponse_identityPoolId,
    getBulkPublishDetailsResponse_httpStatus,
  )
where

import Amazonka.CognitoSync.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

-- | The input for the GetBulkPublishDetails operation.
--
-- /See:/ 'newGetBulkPublishDetails' smart constructor.
data GetBulkPublishDetails = GetBulkPublishDetails'
  { -- | A name-spaced GUID (for example,
    -- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
    -- Cognito. GUID generation is unique within a region.
    GetBulkPublishDetails -> Text
identityPoolId :: Prelude.Text
  }
  deriving (GetBulkPublishDetails -> GetBulkPublishDetails -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBulkPublishDetails -> GetBulkPublishDetails -> Bool
$c/= :: GetBulkPublishDetails -> GetBulkPublishDetails -> Bool
== :: GetBulkPublishDetails -> GetBulkPublishDetails -> Bool
$c== :: GetBulkPublishDetails -> GetBulkPublishDetails -> Bool
Prelude.Eq, ReadPrec [GetBulkPublishDetails]
ReadPrec GetBulkPublishDetails
Int -> ReadS GetBulkPublishDetails
ReadS [GetBulkPublishDetails]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBulkPublishDetails]
$creadListPrec :: ReadPrec [GetBulkPublishDetails]
readPrec :: ReadPrec GetBulkPublishDetails
$creadPrec :: ReadPrec GetBulkPublishDetails
readList :: ReadS [GetBulkPublishDetails]
$creadList :: ReadS [GetBulkPublishDetails]
readsPrec :: Int -> ReadS GetBulkPublishDetails
$creadsPrec :: Int -> ReadS GetBulkPublishDetails
Prelude.Read, Int -> GetBulkPublishDetails -> ShowS
[GetBulkPublishDetails] -> ShowS
GetBulkPublishDetails -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBulkPublishDetails] -> ShowS
$cshowList :: [GetBulkPublishDetails] -> ShowS
show :: GetBulkPublishDetails -> String
$cshow :: GetBulkPublishDetails -> String
showsPrec :: Int -> GetBulkPublishDetails -> ShowS
$cshowsPrec :: Int -> GetBulkPublishDetails -> ShowS
Prelude.Show, forall x. Rep GetBulkPublishDetails x -> GetBulkPublishDetails
forall x. GetBulkPublishDetails -> Rep GetBulkPublishDetails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBulkPublishDetails x -> GetBulkPublishDetails
$cfrom :: forall x. GetBulkPublishDetails -> Rep GetBulkPublishDetails x
Prelude.Generic)

-- |
-- Create a value of 'GetBulkPublishDetails' 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:
--
-- 'identityPoolId', 'getBulkPublishDetails_identityPoolId' - A name-spaced GUID (for example,
-- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
-- Cognito. GUID generation is unique within a region.
newGetBulkPublishDetails ::
  -- | 'identityPoolId'
  Prelude.Text ->
  GetBulkPublishDetails
newGetBulkPublishDetails :: Text -> GetBulkPublishDetails
newGetBulkPublishDetails Text
pIdentityPoolId_ =
  GetBulkPublishDetails'
    { $sel:identityPoolId:GetBulkPublishDetails' :: Text
identityPoolId =
        Text
pIdentityPoolId_
    }

-- | A name-spaced GUID (for example,
-- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
-- Cognito. GUID generation is unique within a region.
getBulkPublishDetails_identityPoolId :: Lens.Lens' GetBulkPublishDetails Prelude.Text
getBulkPublishDetails_identityPoolId :: Lens' GetBulkPublishDetails Text
getBulkPublishDetails_identityPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBulkPublishDetails' {Text
identityPoolId :: Text
$sel:identityPoolId:GetBulkPublishDetails' :: GetBulkPublishDetails -> Text
identityPoolId} -> Text
identityPoolId) (\s :: GetBulkPublishDetails
s@GetBulkPublishDetails' {} Text
a -> GetBulkPublishDetails
s {$sel:identityPoolId:GetBulkPublishDetails' :: Text
identityPoolId = Text
a} :: GetBulkPublishDetails)

instance Core.AWSRequest GetBulkPublishDetails where
  type
    AWSResponse GetBulkPublishDetails =
      GetBulkPublishDetailsResponse
  request :: (Service -> Service)
-> GetBulkPublishDetails -> Request GetBulkPublishDetails
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 GetBulkPublishDetails
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetBulkPublishDetails)))
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 POSIX
-> Maybe POSIX
-> Maybe BulkPublishStatus
-> Maybe Text
-> Maybe Text
-> Int
-> GetBulkPublishDetailsResponse
GetBulkPublishDetailsResponse'
            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
"BulkPublishCompleteTime")
            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
"BulkPublishStartTime")
            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
"BulkPublishStatus")
            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
"FailureMessage")
            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
"IdentityPoolId")
            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 GetBulkPublishDetails where
  hashWithSalt :: Int -> GetBulkPublishDetails -> Int
hashWithSalt Int
_salt GetBulkPublishDetails' {Text
identityPoolId :: Text
$sel:identityPoolId:GetBulkPublishDetails' :: GetBulkPublishDetails -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
identityPoolId

instance Prelude.NFData GetBulkPublishDetails where
  rnf :: GetBulkPublishDetails -> ()
rnf GetBulkPublishDetails' {Text
identityPoolId :: Text
$sel:identityPoolId:GetBulkPublishDetails' :: GetBulkPublishDetails -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
identityPoolId

instance Data.ToHeaders GetBulkPublishDetails where
  toHeaders :: GetBulkPublishDetails -> 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 GetBulkPublishDetails where
  toJSON :: GetBulkPublishDetails -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

instance Data.ToPath GetBulkPublishDetails where
  toPath :: GetBulkPublishDetails -> ByteString
toPath GetBulkPublishDetails' {Text
identityPoolId :: Text
$sel:identityPoolId:GetBulkPublishDetails' :: GetBulkPublishDetails -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/identitypools/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
identityPoolId,
        ByteString
"/getBulkPublishDetails"
      ]

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

-- | The output for the GetBulkPublishDetails operation.
--
-- /See:/ 'newGetBulkPublishDetailsResponse' smart constructor.
data GetBulkPublishDetailsResponse = GetBulkPublishDetailsResponse'
  { -- | If BulkPublishStatus is SUCCEEDED, the time the last bulk publish
    -- operation completed.
    GetBulkPublishDetailsResponse -> Maybe POSIX
bulkPublishCompleteTime :: Prelude.Maybe Data.POSIX,
    -- | The date\/time at which the last bulk publish was initiated.
    GetBulkPublishDetailsResponse -> Maybe POSIX
bulkPublishStartTime :: Prelude.Maybe Data.POSIX,
    -- | Status of the last bulk publish operation, valid values are:
    --
    -- NOT_STARTED - No bulk publish has been requested for this identity pool
    --
    -- IN_PROGRESS - Data is being published to the configured stream
    --
    -- SUCCEEDED - All data for the identity pool has been published to the
    -- configured stream
    --
    -- FAILED - Some portion of the data has failed to publish, check
    -- FailureMessage for the cause.
    GetBulkPublishDetailsResponse -> Maybe BulkPublishStatus
bulkPublishStatus :: Prelude.Maybe BulkPublishStatus,
    -- | If BulkPublishStatus is FAILED this field will contain the error message
    -- that caused the bulk publish to fail.
    GetBulkPublishDetailsResponse -> Maybe Text
failureMessage :: Prelude.Maybe Prelude.Text,
    -- | A name-spaced GUID (for example,
    -- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
    -- Cognito. GUID generation is unique within a region.
    GetBulkPublishDetailsResponse -> Maybe Text
identityPoolId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetBulkPublishDetailsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetBulkPublishDetailsResponse
-> GetBulkPublishDetailsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBulkPublishDetailsResponse
-> GetBulkPublishDetailsResponse -> Bool
$c/= :: GetBulkPublishDetailsResponse
-> GetBulkPublishDetailsResponse -> Bool
== :: GetBulkPublishDetailsResponse
-> GetBulkPublishDetailsResponse -> Bool
$c== :: GetBulkPublishDetailsResponse
-> GetBulkPublishDetailsResponse -> Bool
Prelude.Eq, ReadPrec [GetBulkPublishDetailsResponse]
ReadPrec GetBulkPublishDetailsResponse
Int -> ReadS GetBulkPublishDetailsResponse
ReadS [GetBulkPublishDetailsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBulkPublishDetailsResponse]
$creadListPrec :: ReadPrec [GetBulkPublishDetailsResponse]
readPrec :: ReadPrec GetBulkPublishDetailsResponse
$creadPrec :: ReadPrec GetBulkPublishDetailsResponse
readList :: ReadS [GetBulkPublishDetailsResponse]
$creadList :: ReadS [GetBulkPublishDetailsResponse]
readsPrec :: Int -> ReadS GetBulkPublishDetailsResponse
$creadsPrec :: Int -> ReadS GetBulkPublishDetailsResponse
Prelude.Read, Int -> GetBulkPublishDetailsResponse -> ShowS
[GetBulkPublishDetailsResponse] -> ShowS
GetBulkPublishDetailsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBulkPublishDetailsResponse] -> ShowS
$cshowList :: [GetBulkPublishDetailsResponse] -> ShowS
show :: GetBulkPublishDetailsResponse -> String
$cshow :: GetBulkPublishDetailsResponse -> String
showsPrec :: Int -> GetBulkPublishDetailsResponse -> ShowS
$cshowsPrec :: Int -> GetBulkPublishDetailsResponse -> ShowS
Prelude.Show, forall x.
Rep GetBulkPublishDetailsResponse x
-> GetBulkPublishDetailsResponse
forall x.
GetBulkPublishDetailsResponse
-> Rep GetBulkPublishDetailsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetBulkPublishDetailsResponse x
-> GetBulkPublishDetailsResponse
$cfrom :: forall x.
GetBulkPublishDetailsResponse
-> Rep GetBulkPublishDetailsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetBulkPublishDetailsResponse' 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:
--
-- 'bulkPublishCompleteTime', 'getBulkPublishDetailsResponse_bulkPublishCompleteTime' - If BulkPublishStatus is SUCCEEDED, the time the last bulk publish
-- operation completed.
--
-- 'bulkPublishStartTime', 'getBulkPublishDetailsResponse_bulkPublishStartTime' - The date\/time at which the last bulk publish was initiated.
--
-- 'bulkPublishStatus', 'getBulkPublishDetailsResponse_bulkPublishStatus' - Status of the last bulk publish operation, valid values are:
--
-- NOT_STARTED - No bulk publish has been requested for this identity pool
--
-- IN_PROGRESS - Data is being published to the configured stream
--
-- SUCCEEDED - All data for the identity pool has been published to the
-- configured stream
--
-- FAILED - Some portion of the data has failed to publish, check
-- FailureMessage for the cause.
--
-- 'failureMessage', 'getBulkPublishDetailsResponse_failureMessage' - If BulkPublishStatus is FAILED this field will contain the error message
-- that caused the bulk publish to fail.
--
-- 'identityPoolId', 'getBulkPublishDetailsResponse_identityPoolId' - A name-spaced GUID (for example,
-- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
-- Cognito. GUID generation is unique within a region.
--
-- 'httpStatus', 'getBulkPublishDetailsResponse_httpStatus' - The response's http status code.
newGetBulkPublishDetailsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetBulkPublishDetailsResponse
newGetBulkPublishDetailsResponse :: Int -> GetBulkPublishDetailsResponse
newGetBulkPublishDetailsResponse Int
pHttpStatus_ =
  GetBulkPublishDetailsResponse'
    { $sel:bulkPublishCompleteTime:GetBulkPublishDetailsResponse' :: Maybe POSIX
bulkPublishCompleteTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:bulkPublishStartTime:GetBulkPublishDetailsResponse' :: Maybe POSIX
bulkPublishStartTime = forall a. Maybe a
Prelude.Nothing,
      $sel:bulkPublishStatus:GetBulkPublishDetailsResponse' :: Maybe BulkPublishStatus
bulkPublishStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:failureMessage:GetBulkPublishDetailsResponse' :: Maybe Text
failureMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:identityPoolId:GetBulkPublishDetailsResponse' :: Maybe Text
identityPoolId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetBulkPublishDetailsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | If BulkPublishStatus is SUCCEEDED, the time the last bulk publish
-- operation completed.
getBulkPublishDetailsResponse_bulkPublishCompleteTime :: Lens.Lens' GetBulkPublishDetailsResponse (Prelude.Maybe Prelude.UTCTime)
getBulkPublishDetailsResponse_bulkPublishCompleteTime :: Lens' GetBulkPublishDetailsResponse (Maybe UTCTime)
getBulkPublishDetailsResponse_bulkPublishCompleteTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBulkPublishDetailsResponse' {Maybe POSIX
bulkPublishCompleteTime :: Maybe POSIX
$sel:bulkPublishCompleteTime:GetBulkPublishDetailsResponse' :: GetBulkPublishDetailsResponse -> Maybe POSIX
bulkPublishCompleteTime} -> Maybe POSIX
bulkPublishCompleteTime) (\s :: GetBulkPublishDetailsResponse
s@GetBulkPublishDetailsResponse' {} Maybe POSIX
a -> GetBulkPublishDetailsResponse
s {$sel:bulkPublishCompleteTime:GetBulkPublishDetailsResponse' :: Maybe POSIX
bulkPublishCompleteTime = Maybe POSIX
a} :: GetBulkPublishDetailsResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The date\/time at which the last bulk publish was initiated.
getBulkPublishDetailsResponse_bulkPublishStartTime :: Lens.Lens' GetBulkPublishDetailsResponse (Prelude.Maybe Prelude.UTCTime)
getBulkPublishDetailsResponse_bulkPublishStartTime :: Lens' GetBulkPublishDetailsResponse (Maybe UTCTime)
getBulkPublishDetailsResponse_bulkPublishStartTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBulkPublishDetailsResponse' {Maybe POSIX
bulkPublishStartTime :: Maybe POSIX
$sel:bulkPublishStartTime:GetBulkPublishDetailsResponse' :: GetBulkPublishDetailsResponse -> Maybe POSIX
bulkPublishStartTime} -> Maybe POSIX
bulkPublishStartTime) (\s :: GetBulkPublishDetailsResponse
s@GetBulkPublishDetailsResponse' {} Maybe POSIX
a -> GetBulkPublishDetailsResponse
s {$sel:bulkPublishStartTime:GetBulkPublishDetailsResponse' :: Maybe POSIX
bulkPublishStartTime = Maybe POSIX
a} :: GetBulkPublishDetailsResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Status of the last bulk publish operation, valid values are:
--
-- NOT_STARTED - No bulk publish has been requested for this identity pool
--
-- IN_PROGRESS - Data is being published to the configured stream
--
-- SUCCEEDED - All data for the identity pool has been published to the
-- configured stream
--
-- FAILED - Some portion of the data has failed to publish, check
-- FailureMessage for the cause.
getBulkPublishDetailsResponse_bulkPublishStatus :: Lens.Lens' GetBulkPublishDetailsResponse (Prelude.Maybe BulkPublishStatus)
getBulkPublishDetailsResponse_bulkPublishStatus :: Lens' GetBulkPublishDetailsResponse (Maybe BulkPublishStatus)
getBulkPublishDetailsResponse_bulkPublishStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBulkPublishDetailsResponse' {Maybe BulkPublishStatus
bulkPublishStatus :: Maybe BulkPublishStatus
$sel:bulkPublishStatus:GetBulkPublishDetailsResponse' :: GetBulkPublishDetailsResponse -> Maybe BulkPublishStatus
bulkPublishStatus} -> Maybe BulkPublishStatus
bulkPublishStatus) (\s :: GetBulkPublishDetailsResponse
s@GetBulkPublishDetailsResponse' {} Maybe BulkPublishStatus
a -> GetBulkPublishDetailsResponse
s {$sel:bulkPublishStatus:GetBulkPublishDetailsResponse' :: Maybe BulkPublishStatus
bulkPublishStatus = Maybe BulkPublishStatus
a} :: GetBulkPublishDetailsResponse)

-- | If BulkPublishStatus is FAILED this field will contain the error message
-- that caused the bulk publish to fail.
getBulkPublishDetailsResponse_failureMessage :: Lens.Lens' GetBulkPublishDetailsResponse (Prelude.Maybe Prelude.Text)
getBulkPublishDetailsResponse_failureMessage :: Lens' GetBulkPublishDetailsResponse (Maybe Text)
getBulkPublishDetailsResponse_failureMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBulkPublishDetailsResponse' {Maybe Text
failureMessage :: Maybe Text
$sel:failureMessage:GetBulkPublishDetailsResponse' :: GetBulkPublishDetailsResponse -> Maybe Text
failureMessage} -> Maybe Text
failureMessage) (\s :: GetBulkPublishDetailsResponse
s@GetBulkPublishDetailsResponse' {} Maybe Text
a -> GetBulkPublishDetailsResponse
s {$sel:failureMessage:GetBulkPublishDetailsResponse' :: Maybe Text
failureMessage = Maybe Text
a} :: GetBulkPublishDetailsResponse)

-- | A name-spaced GUID (for example,
-- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
-- Cognito. GUID generation is unique within a region.
getBulkPublishDetailsResponse_identityPoolId :: Lens.Lens' GetBulkPublishDetailsResponse (Prelude.Maybe Prelude.Text)
getBulkPublishDetailsResponse_identityPoolId :: Lens' GetBulkPublishDetailsResponse (Maybe Text)
getBulkPublishDetailsResponse_identityPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBulkPublishDetailsResponse' {Maybe Text
identityPoolId :: Maybe Text
$sel:identityPoolId:GetBulkPublishDetailsResponse' :: GetBulkPublishDetailsResponse -> Maybe Text
identityPoolId} -> Maybe Text
identityPoolId) (\s :: GetBulkPublishDetailsResponse
s@GetBulkPublishDetailsResponse' {} Maybe Text
a -> GetBulkPublishDetailsResponse
s {$sel:identityPoolId:GetBulkPublishDetailsResponse' :: Maybe Text
identityPoolId = Maybe Text
a} :: GetBulkPublishDetailsResponse)

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

instance Prelude.NFData GetBulkPublishDetailsResponse where
  rnf :: GetBulkPublishDetailsResponse -> ()
rnf GetBulkPublishDetailsResponse' {Int
Maybe Text
Maybe POSIX
Maybe BulkPublishStatus
httpStatus :: Int
identityPoolId :: Maybe Text
failureMessage :: Maybe Text
bulkPublishStatus :: Maybe BulkPublishStatus
bulkPublishStartTime :: Maybe POSIX
bulkPublishCompleteTime :: Maybe POSIX
$sel:httpStatus:GetBulkPublishDetailsResponse' :: GetBulkPublishDetailsResponse -> Int
$sel:identityPoolId:GetBulkPublishDetailsResponse' :: GetBulkPublishDetailsResponse -> Maybe Text
$sel:failureMessage:GetBulkPublishDetailsResponse' :: GetBulkPublishDetailsResponse -> Maybe Text
$sel:bulkPublishStatus:GetBulkPublishDetailsResponse' :: GetBulkPublishDetailsResponse -> Maybe BulkPublishStatus
$sel:bulkPublishStartTime:GetBulkPublishDetailsResponse' :: GetBulkPublishDetailsResponse -> Maybe POSIX
$sel:bulkPublishCompleteTime:GetBulkPublishDetailsResponse' :: GetBulkPublishDetailsResponse -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
bulkPublishCompleteTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
bulkPublishStartTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BulkPublishStatus
bulkPublishStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
failureMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
identityPoolId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus