{-# 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.GetIdentityPoolConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets the configuration settings of 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.GetIdentityPoolConfiguration
  ( -- * Creating a Request
    GetIdentityPoolConfiguration (..),
    newGetIdentityPoolConfiguration,

    -- * Request Lenses
    getIdentityPoolConfiguration_identityPoolId,

    -- * Destructuring the Response
    GetIdentityPoolConfigurationResponse (..),
    newGetIdentityPoolConfigurationResponse,

    -- * Response Lenses
    getIdentityPoolConfigurationResponse_cognitoStreams,
    getIdentityPoolConfigurationResponse_identityPoolId,
    getIdentityPoolConfigurationResponse_pushSync,
    getIdentityPoolConfigurationResponse_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 GetIdentityPoolConfiguration operation.
--
-- /See:/ 'newGetIdentityPoolConfiguration' smart constructor.
data GetIdentityPoolConfiguration = GetIdentityPoolConfiguration'
  { -- | A name-spaced GUID (for example,
    -- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
    -- Cognito. This is the ID of the pool for which to return a configuration.
    GetIdentityPoolConfiguration -> Text
identityPoolId :: Prelude.Text
  }
  deriving (GetIdentityPoolConfiguration
-> GetIdentityPoolConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetIdentityPoolConfiguration
-> GetIdentityPoolConfiguration -> Bool
$c/= :: GetIdentityPoolConfiguration
-> GetIdentityPoolConfiguration -> Bool
== :: GetIdentityPoolConfiguration
-> GetIdentityPoolConfiguration -> Bool
$c== :: GetIdentityPoolConfiguration
-> GetIdentityPoolConfiguration -> Bool
Prelude.Eq, ReadPrec [GetIdentityPoolConfiguration]
ReadPrec GetIdentityPoolConfiguration
Int -> ReadS GetIdentityPoolConfiguration
ReadS [GetIdentityPoolConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetIdentityPoolConfiguration]
$creadListPrec :: ReadPrec [GetIdentityPoolConfiguration]
readPrec :: ReadPrec GetIdentityPoolConfiguration
$creadPrec :: ReadPrec GetIdentityPoolConfiguration
readList :: ReadS [GetIdentityPoolConfiguration]
$creadList :: ReadS [GetIdentityPoolConfiguration]
readsPrec :: Int -> ReadS GetIdentityPoolConfiguration
$creadsPrec :: Int -> ReadS GetIdentityPoolConfiguration
Prelude.Read, Int -> GetIdentityPoolConfiguration -> ShowS
[GetIdentityPoolConfiguration] -> ShowS
GetIdentityPoolConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetIdentityPoolConfiguration] -> ShowS
$cshowList :: [GetIdentityPoolConfiguration] -> ShowS
show :: GetIdentityPoolConfiguration -> String
$cshow :: GetIdentityPoolConfiguration -> String
showsPrec :: Int -> GetIdentityPoolConfiguration -> ShowS
$cshowsPrec :: Int -> GetIdentityPoolConfiguration -> ShowS
Prelude.Show, forall x.
Rep GetIdentityPoolConfiguration x -> GetIdentityPoolConfiguration
forall x.
GetIdentityPoolConfiguration -> Rep GetIdentityPoolConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetIdentityPoolConfiguration x -> GetIdentityPoolConfiguration
$cfrom :: forall x.
GetIdentityPoolConfiguration -> Rep GetIdentityPoolConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'GetIdentityPoolConfiguration' 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', 'getIdentityPoolConfiguration_identityPoolId' - A name-spaced GUID (for example,
-- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
-- Cognito. This is the ID of the pool for which to return a configuration.
newGetIdentityPoolConfiguration ::
  -- | 'identityPoolId'
  Prelude.Text ->
  GetIdentityPoolConfiguration
newGetIdentityPoolConfiguration :: Text -> GetIdentityPoolConfiguration
newGetIdentityPoolConfiguration Text
pIdentityPoolId_ =
  GetIdentityPoolConfiguration'
    { $sel:identityPoolId:GetIdentityPoolConfiguration' :: Text
identityPoolId =
        Text
pIdentityPoolId_
    }

-- | A name-spaced GUID (for example,
-- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
-- Cognito. This is the ID of the pool for which to return a configuration.
getIdentityPoolConfiguration_identityPoolId :: Lens.Lens' GetIdentityPoolConfiguration Prelude.Text
getIdentityPoolConfiguration_identityPoolId :: Lens' GetIdentityPoolConfiguration Text
getIdentityPoolConfiguration_identityPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIdentityPoolConfiguration' {Text
identityPoolId :: Text
$sel:identityPoolId:GetIdentityPoolConfiguration' :: GetIdentityPoolConfiguration -> Text
identityPoolId} -> Text
identityPoolId) (\s :: GetIdentityPoolConfiguration
s@GetIdentityPoolConfiguration' {} Text
a -> GetIdentityPoolConfiguration
s {$sel:identityPoolId:GetIdentityPoolConfiguration' :: Text
identityPoolId = Text
a} :: GetIdentityPoolConfiguration)

instance Core.AWSRequest GetIdentityPoolConfiguration where
  type
    AWSResponse GetIdentityPoolConfiguration =
      GetIdentityPoolConfigurationResponse
  request :: (Service -> Service)
-> GetIdentityPoolConfiguration
-> Request GetIdentityPoolConfiguration
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetIdentityPoolConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetIdentityPoolConfiguration)))
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 CognitoStreams
-> Maybe Text
-> Maybe PushSync
-> Int
-> GetIdentityPoolConfigurationResponse
GetIdentityPoolConfigurationResponse'
            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
"CognitoStreams")
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"PushSync")
            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
    GetIdentityPoolConfiguration
  where
  hashWithSalt :: Int -> GetIdentityPoolConfiguration -> Int
hashWithSalt Int
_salt GetIdentityPoolConfiguration' {Text
identityPoolId :: Text
$sel:identityPoolId:GetIdentityPoolConfiguration' :: GetIdentityPoolConfiguration -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
identityPoolId

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

instance Data.ToHeaders GetIdentityPoolConfiguration where
  toHeaders :: GetIdentityPoolConfiguration -> 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.ToPath GetIdentityPoolConfiguration where
  toPath :: GetIdentityPoolConfiguration -> ByteString
toPath GetIdentityPoolConfiguration' {Text
identityPoolId :: Text
$sel:identityPoolId:GetIdentityPoolConfiguration' :: GetIdentityPoolConfiguration -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/identitypools/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
identityPoolId,
        ByteString
"/configuration"
      ]

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

-- | The output for the GetIdentityPoolConfiguration operation.
--
-- /See:/ 'newGetIdentityPoolConfigurationResponse' smart constructor.
data GetIdentityPoolConfigurationResponse = GetIdentityPoolConfigurationResponse'
  { -- | Options to apply to this identity pool for Amazon Cognito streams.
    GetIdentityPoolConfigurationResponse -> Maybe CognitoStreams
cognitoStreams :: Prelude.Maybe CognitoStreams,
    -- | A name-spaced GUID (for example,
    -- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
    -- Cognito.
    GetIdentityPoolConfigurationResponse -> Maybe Text
identityPoolId :: Prelude.Maybe Prelude.Text,
    -- | Options to apply to this identity pool for push synchronization.
    GetIdentityPoolConfigurationResponse -> Maybe PushSync
pushSync :: Prelude.Maybe PushSync,
    -- | The response's http status code.
    GetIdentityPoolConfigurationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetIdentityPoolConfigurationResponse
-> GetIdentityPoolConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetIdentityPoolConfigurationResponse
-> GetIdentityPoolConfigurationResponse -> Bool
$c/= :: GetIdentityPoolConfigurationResponse
-> GetIdentityPoolConfigurationResponse -> Bool
== :: GetIdentityPoolConfigurationResponse
-> GetIdentityPoolConfigurationResponse -> Bool
$c== :: GetIdentityPoolConfigurationResponse
-> GetIdentityPoolConfigurationResponse -> Bool
Prelude.Eq, ReadPrec [GetIdentityPoolConfigurationResponse]
ReadPrec GetIdentityPoolConfigurationResponse
Int -> ReadS GetIdentityPoolConfigurationResponse
ReadS [GetIdentityPoolConfigurationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetIdentityPoolConfigurationResponse]
$creadListPrec :: ReadPrec [GetIdentityPoolConfigurationResponse]
readPrec :: ReadPrec GetIdentityPoolConfigurationResponse
$creadPrec :: ReadPrec GetIdentityPoolConfigurationResponse
readList :: ReadS [GetIdentityPoolConfigurationResponse]
$creadList :: ReadS [GetIdentityPoolConfigurationResponse]
readsPrec :: Int -> ReadS GetIdentityPoolConfigurationResponse
$creadsPrec :: Int -> ReadS GetIdentityPoolConfigurationResponse
Prelude.Read, Int -> GetIdentityPoolConfigurationResponse -> ShowS
[GetIdentityPoolConfigurationResponse] -> ShowS
GetIdentityPoolConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetIdentityPoolConfigurationResponse] -> ShowS
$cshowList :: [GetIdentityPoolConfigurationResponse] -> ShowS
show :: GetIdentityPoolConfigurationResponse -> String
$cshow :: GetIdentityPoolConfigurationResponse -> String
showsPrec :: Int -> GetIdentityPoolConfigurationResponse -> ShowS
$cshowsPrec :: Int -> GetIdentityPoolConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep GetIdentityPoolConfigurationResponse x
-> GetIdentityPoolConfigurationResponse
forall x.
GetIdentityPoolConfigurationResponse
-> Rep GetIdentityPoolConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetIdentityPoolConfigurationResponse x
-> GetIdentityPoolConfigurationResponse
$cfrom :: forall x.
GetIdentityPoolConfigurationResponse
-> Rep GetIdentityPoolConfigurationResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetIdentityPoolConfigurationResponse' 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:
--
-- 'cognitoStreams', 'getIdentityPoolConfigurationResponse_cognitoStreams' - Options to apply to this identity pool for Amazon Cognito streams.
--
-- 'identityPoolId', 'getIdentityPoolConfigurationResponse_identityPoolId' - A name-spaced GUID (for example,
-- us-east-1:23EC4050-6AEA-7089-A2DD-08002EXAMPLE) created by Amazon
-- Cognito.
--
-- 'pushSync', 'getIdentityPoolConfigurationResponse_pushSync' - Options to apply to this identity pool for push synchronization.
--
-- 'httpStatus', 'getIdentityPoolConfigurationResponse_httpStatus' - The response's http status code.
newGetIdentityPoolConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetIdentityPoolConfigurationResponse
newGetIdentityPoolConfigurationResponse :: Int -> GetIdentityPoolConfigurationResponse
newGetIdentityPoolConfigurationResponse Int
pHttpStatus_ =
  GetIdentityPoolConfigurationResponse'
    { $sel:cognitoStreams:GetIdentityPoolConfigurationResponse' :: Maybe CognitoStreams
cognitoStreams =
        forall a. Maybe a
Prelude.Nothing,
      $sel:identityPoolId:GetIdentityPoolConfigurationResponse' :: Maybe Text
identityPoolId = forall a. Maybe a
Prelude.Nothing,
      $sel:pushSync:GetIdentityPoolConfigurationResponse' :: Maybe PushSync
pushSync = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetIdentityPoolConfigurationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Options to apply to this identity pool for Amazon Cognito streams.
getIdentityPoolConfigurationResponse_cognitoStreams :: Lens.Lens' GetIdentityPoolConfigurationResponse (Prelude.Maybe CognitoStreams)
getIdentityPoolConfigurationResponse_cognitoStreams :: Lens' GetIdentityPoolConfigurationResponse (Maybe CognitoStreams)
getIdentityPoolConfigurationResponse_cognitoStreams = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIdentityPoolConfigurationResponse' {Maybe CognitoStreams
cognitoStreams :: Maybe CognitoStreams
$sel:cognitoStreams:GetIdentityPoolConfigurationResponse' :: GetIdentityPoolConfigurationResponse -> Maybe CognitoStreams
cognitoStreams} -> Maybe CognitoStreams
cognitoStreams) (\s :: GetIdentityPoolConfigurationResponse
s@GetIdentityPoolConfigurationResponse' {} Maybe CognitoStreams
a -> GetIdentityPoolConfigurationResponse
s {$sel:cognitoStreams:GetIdentityPoolConfigurationResponse' :: Maybe CognitoStreams
cognitoStreams = Maybe CognitoStreams
a} :: GetIdentityPoolConfigurationResponse)

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

-- | Options to apply to this identity pool for push synchronization.
getIdentityPoolConfigurationResponse_pushSync :: Lens.Lens' GetIdentityPoolConfigurationResponse (Prelude.Maybe PushSync)
getIdentityPoolConfigurationResponse_pushSync :: Lens' GetIdentityPoolConfigurationResponse (Maybe PushSync)
getIdentityPoolConfigurationResponse_pushSync = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIdentityPoolConfigurationResponse' {Maybe PushSync
pushSync :: Maybe PushSync
$sel:pushSync:GetIdentityPoolConfigurationResponse' :: GetIdentityPoolConfigurationResponse -> Maybe PushSync
pushSync} -> Maybe PushSync
pushSync) (\s :: GetIdentityPoolConfigurationResponse
s@GetIdentityPoolConfigurationResponse' {} Maybe PushSync
a -> GetIdentityPoolConfigurationResponse
s {$sel:pushSync:GetIdentityPoolConfigurationResponse' :: Maybe PushSync
pushSync = Maybe PushSync
a} :: GetIdentityPoolConfigurationResponse)

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

instance
  Prelude.NFData
    GetIdentityPoolConfigurationResponse
  where
  rnf :: GetIdentityPoolConfigurationResponse -> ()
rnf GetIdentityPoolConfigurationResponse' {Int
Maybe Text
Maybe PushSync
Maybe CognitoStreams
httpStatus :: Int
pushSync :: Maybe PushSync
identityPoolId :: Maybe Text
cognitoStreams :: Maybe CognitoStreams
$sel:httpStatus:GetIdentityPoolConfigurationResponse' :: GetIdentityPoolConfigurationResponse -> Int
$sel:pushSync:GetIdentityPoolConfigurationResponse' :: GetIdentityPoolConfigurationResponse -> Maybe PushSync
$sel:identityPoolId:GetIdentityPoolConfigurationResponse' :: GetIdentityPoolConfigurationResponse -> Maybe Text
$sel:cognitoStreams:GetIdentityPoolConfigurationResponse' :: GetIdentityPoolConfigurationResponse -> Maybe CognitoStreams
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CognitoStreams
cognitoStreams
      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 Maybe PushSync
pushSync
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus