{-# 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.BulkPublish
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Initiates a bulk publish of all existing datasets for an Identity Pool
-- to the configured stream. Customers are limited to one successful bulk
-- publish per 24 hours. Bulk publish is an asynchronous request, customers
-- can see the status of the request via the GetBulkPublishDetails
-- operation.
--
-- 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.BulkPublish
  ( -- * Creating a Request
    BulkPublish (..),
    newBulkPublish,

    -- * Request Lenses
    bulkPublish_identityPoolId,

    -- * Destructuring the Response
    BulkPublishResponse (..),
    newBulkPublishResponse,

    -- * Response Lenses
    bulkPublishResponse_identityPoolId,
    bulkPublishResponse_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 BulkPublish operation.
--
-- /See:/ 'newBulkPublish' smart constructor.
data BulkPublish = BulkPublish'
  { -- | 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.
    BulkPublish -> Text
identityPoolId :: Prelude.Text
  }
  deriving (BulkPublish -> BulkPublish -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BulkPublish -> BulkPublish -> Bool
$c/= :: BulkPublish -> BulkPublish -> Bool
== :: BulkPublish -> BulkPublish -> Bool
$c== :: BulkPublish -> BulkPublish -> Bool
Prelude.Eq, ReadPrec [BulkPublish]
ReadPrec BulkPublish
Int -> ReadS BulkPublish
ReadS [BulkPublish]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BulkPublish]
$creadListPrec :: ReadPrec [BulkPublish]
readPrec :: ReadPrec BulkPublish
$creadPrec :: ReadPrec BulkPublish
readList :: ReadS [BulkPublish]
$creadList :: ReadS [BulkPublish]
readsPrec :: Int -> ReadS BulkPublish
$creadsPrec :: Int -> ReadS BulkPublish
Prelude.Read, Int -> BulkPublish -> ShowS
[BulkPublish] -> ShowS
BulkPublish -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BulkPublish] -> ShowS
$cshowList :: [BulkPublish] -> ShowS
show :: BulkPublish -> String
$cshow :: BulkPublish -> String
showsPrec :: Int -> BulkPublish -> ShowS
$cshowsPrec :: Int -> BulkPublish -> ShowS
Prelude.Show, forall x. Rep BulkPublish x -> BulkPublish
forall x. BulkPublish -> Rep BulkPublish x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BulkPublish x -> BulkPublish
$cfrom :: forall x. BulkPublish -> Rep BulkPublish x
Prelude.Generic)

-- |
-- Create a value of 'BulkPublish' 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', 'bulkPublish_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.
newBulkPublish ::
  -- | 'identityPoolId'
  Prelude.Text ->
  BulkPublish
newBulkPublish :: Text -> BulkPublish
newBulkPublish Text
pIdentityPoolId_ =
  BulkPublish' {$sel:identityPoolId:BulkPublish' :: 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.
bulkPublish_identityPoolId :: Lens.Lens' BulkPublish Prelude.Text
bulkPublish_identityPoolId :: Lens' BulkPublish Text
bulkPublish_identityPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BulkPublish' {Text
identityPoolId :: Text
$sel:identityPoolId:BulkPublish' :: BulkPublish -> Text
identityPoolId} -> Text
identityPoolId) (\s :: BulkPublish
s@BulkPublish' {} Text
a -> BulkPublish
s {$sel:identityPoolId:BulkPublish' :: Text
identityPoolId = Text
a} :: BulkPublish)

instance Core.AWSRequest BulkPublish where
  type AWSResponse BulkPublish = BulkPublishResponse
  request :: (Service -> Service) -> BulkPublish -> Request BulkPublish
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 BulkPublish
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse BulkPublish)))
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 -> Int -> BulkPublishResponse
BulkPublishResponse'
            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
"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 BulkPublish where
  hashWithSalt :: Int -> BulkPublish -> Int
hashWithSalt Int
_salt BulkPublish' {Text
identityPoolId :: Text
$sel:identityPoolId:BulkPublish' :: BulkPublish -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
identityPoolId

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

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

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

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

-- | The output for the BulkPublish operation.
--
-- /See:/ 'newBulkPublishResponse' smart constructor.
data BulkPublishResponse = BulkPublishResponse'
  { -- | 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.
    BulkPublishResponse -> Maybe Text
identityPoolId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    BulkPublishResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (BulkPublishResponse -> BulkPublishResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BulkPublishResponse -> BulkPublishResponse -> Bool
$c/= :: BulkPublishResponse -> BulkPublishResponse -> Bool
== :: BulkPublishResponse -> BulkPublishResponse -> Bool
$c== :: BulkPublishResponse -> BulkPublishResponse -> Bool
Prelude.Eq, ReadPrec [BulkPublishResponse]
ReadPrec BulkPublishResponse
Int -> ReadS BulkPublishResponse
ReadS [BulkPublishResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BulkPublishResponse]
$creadListPrec :: ReadPrec [BulkPublishResponse]
readPrec :: ReadPrec BulkPublishResponse
$creadPrec :: ReadPrec BulkPublishResponse
readList :: ReadS [BulkPublishResponse]
$creadList :: ReadS [BulkPublishResponse]
readsPrec :: Int -> ReadS BulkPublishResponse
$creadsPrec :: Int -> ReadS BulkPublishResponse
Prelude.Read, Int -> BulkPublishResponse -> ShowS
[BulkPublishResponse] -> ShowS
BulkPublishResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BulkPublishResponse] -> ShowS
$cshowList :: [BulkPublishResponse] -> ShowS
show :: BulkPublishResponse -> String
$cshow :: BulkPublishResponse -> String
showsPrec :: Int -> BulkPublishResponse -> ShowS
$cshowsPrec :: Int -> BulkPublishResponse -> ShowS
Prelude.Show, forall x. Rep BulkPublishResponse x -> BulkPublishResponse
forall x. BulkPublishResponse -> Rep BulkPublishResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BulkPublishResponse x -> BulkPublishResponse
$cfrom :: forall x. BulkPublishResponse -> Rep BulkPublishResponse x
Prelude.Generic)

-- |
-- Create a value of 'BulkPublishResponse' 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', 'bulkPublishResponse_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', 'bulkPublishResponse_httpStatus' - The response's http status code.
newBulkPublishResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BulkPublishResponse
newBulkPublishResponse :: Int -> BulkPublishResponse
newBulkPublishResponse Int
pHttpStatus_ =
  BulkPublishResponse'
    { $sel:identityPoolId:BulkPublishResponse' :: Maybe Text
identityPoolId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:BulkPublishResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | 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.
bulkPublishResponse_identityPoolId :: Lens.Lens' BulkPublishResponse (Prelude.Maybe Prelude.Text)
bulkPublishResponse_identityPoolId :: Lens' BulkPublishResponse (Maybe Text)
bulkPublishResponse_identityPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BulkPublishResponse' {Maybe Text
identityPoolId :: Maybe Text
$sel:identityPoolId:BulkPublishResponse' :: BulkPublishResponse -> Maybe Text
identityPoolId} -> Maybe Text
identityPoolId) (\s :: BulkPublishResponse
s@BulkPublishResponse' {} Maybe Text
a -> BulkPublishResponse
s {$sel:identityPoolId:BulkPublishResponse' :: Maybe Text
identityPoolId = Maybe Text
a} :: BulkPublishResponse)

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

instance Prelude.NFData BulkPublishResponse where
  rnf :: BulkPublishResponse -> ()
rnf BulkPublishResponse' {Int
Maybe Text
httpStatus :: Int
identityPoolId :: Maybe Text
$sel:httpStatus:BulkPublishResponse' :: BulkPublishResponse -> Int
$sel:identityPoolId:BulkPublishResponse' :: BulkPublishResponse -> Maybe Text
..} =
    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