{-# 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.SNS.GetPlatformApplicationAttributes
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves the attributes of the platform application object for the
-- supported push notification services, such as APNS and GCM (Firebase
-- Cloud Messaging). For more information, see
-- <https://docs.aws.amazon.com/sns/latest/dg/SNSMobilePush.html Using Amazon SNS Mobile Push Notifications>.
module Amazonka.SNS.GetPlatformApplicationAttributes
  ( -- * Creating a Request
    GetPlatformApplicationAttributes (..),
    newGetPlatformApplicationAttributes,

    -- * Request Lenses
    getPlatformApplicationAttributes_platformApplicationArn,

    -- * Destructuring the Response
    GetPlatformApplicationAttributesResponse (..),
    newGetPlatformApplicationAttributesResponse,

    -- * Response Lenses
    getPlatformApplicationAttributesResponse_attributes,
    getPlatformApplicationAttributesResponse_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.SNS.Types

-- | Input for GetPlatformApplicationAttributes action.
--
-- /See:/ 'newGetPlatformApplicationAttributes' smart constructor.
data GetPlatformApplicationAttributes = GetPlatformApplicationAttributes'
  { -- | PlatformApplicationArn for GetPlatformApplicationAttributesInput.
    GetPlatformApplicationAttributes -> Text
platformApplicationArn :: Prelude.Text
  }
  deriving (GetPlatformApplicationAttributes
-> GetPlatformApplicationAttributes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPlatformApplicationAttributes
-> GetPlatformApplicationAttributes -> Bool
$c/= :: GetPlatformApplicationAttributes
-> GetPlatformApplicationAttributes -> Bool
== :: GetPlatformApplicationAttributes
-> GetPlatformApplicationAttributes -> Bool
$c== :: GetPlatformApplicationAttributes
-> GetPlatformApplicationAttributes -> Bool
Prelude.Eq, ReadPrec [GetPlatformApplicationAttributes]
ReadPrec GetPlatformApplicationAttributes
Int -> ReadS GetPlatformApplicationAttributes
ReadS [GetPlatformApplicationAttributes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetPlatformApplicationAttributes]
$creadListPrec :: ReadPrec [GetPlatformApplicationAttributes]
readPrec :: ReadPrec GetPlatformApplicationAttributes
$creadPrec :: ReadPrec GetPlatformApplicationAttributes
readList :: ReadS [GetPlatformApplicationAttributes]
$creadList :: ReadS [GetPlatformApplicationAttributes]
readsPrec :: Int -> ReadS GetPlatformApplicationAttributes
$creadsPrec :: Int -> ReadS GetPlatformApplicationAttributes
Prelude.Read, Int -> GetPlatformApplicationAttributes -> ShowS
[GetPlatformApplicationAttributes] -> ShowS
GetPlatformApplicationAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPlatformApplicationAttributes] -> ShowS
$cshowList :: [GetPlatformApplicationAttributes] -> ShowS
show :: GetPlatformApplicationAttributes -> String
$cshow :: GetPlatformApplicationAttributes -> String
showsPrec :: Int -> GetPlatformApplicationAttributes -> ShowS
$cshowsPrec :: Int -> GetPlatformApplicationAttributes -> ShowS
Prelude.Show, forall x.
Rep GetPlatformApplicationAttributes x
-> GetPlatformApplicationAttributes
forall x.
GetPlatformApplicationAttributes
-> Rep GetPlatformApplicationAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetPlatformApplicationAttributes x
-> GetPlatformApplicationAttributes
$cfrom :: forall x.
GetPlatformApplicationAttributes
-> Rep GetPlatformApplicationAttributes x
Prelude.Generic)

-- |
-- Create a value of 'GetPlatformApplicationAttributes' 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:
--
-- 'platformApplicationArn', 'getPlatformApplicationAttributes_platformApplicationArn' - PlatformApplicationArn for GetPlatformApplicationAttributesInput.
newGetPlatformApplicationAttributes ::
  -- | 'platformApplicationArn'
  Prelude.Text ->
  GetPlatformApplicationAttributes
newGetPlatformApplicationAttributes :: Text -> GetPlatformApplicationAttributes
newGetPlatformApplicationAttributes
  Text
pPlatformApplicationArn_ =
    GetPlatformApplicationAttributes'
      { $sel:platformApplicationArn:GetPlatformApplicationAttributes' :: Text
platformApplicationArn =
          Text
pPlatformApplicationArn_
      }

-- | PlatformApplicationArn for GetPlatformApplicationAttributesInput.
getPlatformApplicationAttributes_platformApplicationArn :: Lens.Lens' GetPlatformApplicationAttributes Prelude.Text
getPlatformApplicationAttributes_platformApplicationArn :: Lens' GetPlatformApplicationAttributes Text
getPlatformApplicationAttributes_platformApplicationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPlatformApplicationAttributes' {Text
platformApplicationArn :: Text
$sel:platformApplicationArn:GetPlatformApplicationAttributes' :: GetPlatformApplicationAttributes -> Text
platformApplicationArn} -> Text
platformApplicationArn) (\s :: GetPlatformApplicationAttributes
s@GetPlatformApplicationAttributes' {} Text
a -> GetPlatformApplicationAttributes
s {$sel:platformApplicationArn:GetPlatformApplicationAttributes' :: Text
platformApplicationArn = Text
a} :: GetPlatformApplicationAttributes)

instance
  Core.AWSRequest
    GetPlatformApplicationAttributes
  where
  type
    AWSResponse GetPlatformApplicationAttributes =
      GetPlatformApplicationAttributesResponse
  request :: (Service -> Service)
-> GetPlatformApplicationAttributes
-> Request GetPlatformApplicationAttributes
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetPlatformApplicationAttributes
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse GetPlatformApplicationAttributes)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"GetPlatformApplicationAttributesResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe (HashMap Text Text)
-> Int -> GetPlatformApplicationAttributesResponse
GetPlatformApplicationAttributesResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Attributes"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall k v.
(Eq k, Hashable k, FromText k, FromXML v) =>
Text -> Text -> Text -> [Node] -> Either String (HashMap k v)
Data.parseXMLMap Text
"entry" Text
"key" Text
"value")
                        )
            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
    GetPlatformApplicationAttributes
  where
  hashWithSalt :: Int -> GetPlatformApplicationAttributes -> Int
hashWithSalt
    Int
_salt
    GetPlatformApplicationAttributes' {Text
platformApplicationArn :: Text
$sel:platformApplicationArn:GetPlatformApplicationAttributes' :: GetPlatformApplicationAttributes -> Text
..} =
      Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
platformApplicationArn

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

instance
  Data.ToHeaders
    GetPlatformApplicationAttributes
  where
  toHeaders :: GetPlatformApplicationAttributes -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance
  Data.ToQuery
    GetPlatformApplicationAttributes
  where
  toQuery :: GetPlatformApplicationAttributes -> QueryString
toQuery GetPlatformApplicationAttributes' {Text
platformApplicationArn :: Text
$sel:platformApplicationArn:GetPlatformApplicationAttributes' :: GetPlatformApplicationAttributes -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"GetPlatformApplicationAttributes" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-03-31" :: Prelude.ByteString),
        ByteString
"PlatformApplicationArn"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
platformApplicationArn
      ]

-- | Response for GetPlatformApplicationAttributes action.
--
-- /See:/ 'newGetPlatformApplicationAttributesResponse' smart constructor.
data GetPlatformApplicationAttributesResponse = GetPlatformApplicationAttributesResponse'
  { -- | Attributes include the following:
    --
    -- -   @AppleCertificateExpiryDate@ – The expiry date of the SSL
    --     certificate used to configure certificate-based authentication.
    --
    -- -   @ApplePlatformTeamID@ – The Apple developer account ID used to
    --     configure token-based authentication.
    --
    -- -   @ApplePlatformBundleID@ – The app identifier used to configure
    --     token-based authentication.
    --
    -- -   @EventEndpointCreated@ – Topic ARN to which EndpointCreated event
    --     notifications should be sent.
    --
    -- -   @EventEndpointDeleted@ – Topic ARN to which EndpointDeleted event
    --     notifications should be sent.
    --
    -- -   @EventEndpointUpdated@ – Topic ARN to which EndpointUpdate event
    --     notifications should be sent.
    --
    -- -   @EventDeliveryFailure@ – Topic ARN to which DeliveryFailure event
    --     notifications should be sent upon Direct Publish delivery failure
    --     (permanent) to one of the application\'s endpoints.
    GetPlatformApplicationAttributesResponse
-> Maybe (HashMap Text Text)
attributes :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    GetPlatformApplicationAttributesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetPlatformApplicationAttributesResponse
-> GetPlatformApplicationAttributesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPlatformApplicationAttributesResponse
-> GetPlatformApplicationAttributesResponse -> Bool
$c/= :: GetPlatformApplicationAttributesResponse
-> GetPlatformApplicationAttributesResponse -> Bool
== :: GetPlatformApplicationAttributesResponse
-> GetPlatformApplicationAttributesResponse -> Bool
$c== :: GetPlatformApplicationAttributesResponse
-> GetPlatformApplicationAttributesResponse -> Bool
Prelude.Eq, ReadPrec [GetPlatformApplicationAttributesResponse]
ReadPrec GetPlatformApplicationAttributesResponse
Int -> ReadS GetPlatformApplicationAttributesResponse
ReadS [GetPlatformApplicationAttributesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetPlatformApplicationAttributesResponse]
$creadListPrec :: ReadPrec [GetPlatformApplicationAttributesResponse]
readPrec :: ReadPrec GetPlatformApplicationAttributesResponse
$creadPrec :: ReadPrec GetPlatformApplicationAttributesResponse
readList :: ReadS [GetPlatformApplicationAttributesResponse]
$creadList :: ReadS [GetPlatformApplicationAttributesResponse]
readsPrec :: Int -> ReadS GetPlatformApplicationAttributesResponse
$creadsPrec :: Int -> ReadS GetPlatformApplicationAttributesResponse
Prelude.Read, Int -> GetPlatformApplicationAttributesResponse -> ShowS
[GetPlatformApplicationAttributesResponse] -> ShowS
GetPlatformApplicationAttributesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPlatformApplicationAttributesResponse] -> ShowS
$cshowList :: [GetPlatformApplicationAttributesResponse] -> ShowS
show :: GetPlatformApplicationAttributesResponse -> String
$cshow :: GetPlatformApplicationAttributesResponse -> String
showsPrec :: Int -> GetPlatformApplicationAttributesResponse -> ShowS
$cshowsPrec :: Int -> GetPlatformApplicationAttributesResponse -> ShowS
Prelude.Show, forall x.
Rep GetPlatformApplicationAttributesResponse x
-> GetPlatformApplicationAttributesResponse
forall x.
GetPlatformApplicationAttributesResponse
-> Rep GetPlatformApplicationAttributesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetPlatformApplicationAttributesResponse x
-> GetPlatformApplicationAttributesResponse
$cfrom :: forall x.
GetPlatformApplicationAttributesResponse
-> Rep GetPlatformApplicationAttributesResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetPlatformApplicationAttributesResponse' 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:
--
-- 'attributes', 'getPlatformApplicationAttributesResponse_attributes' - Attributes include the following:
--
-- -   @AppleCertificateExpiryDate@ – The expiry date of the SSL
--     certificate used to configure certificate-based authentication.
--
-- -   @ApplePlatformTeamID@ – The Apple developer account ID used to
--     configure token-based authentication.
--
-- -   @ApplePlatformBundleID@ – The app identifier used to configure
--     token-based authentication.
--
-- -   @EventEndpointCreated@ – Topic ARN to which EndpointCreated event
--     notifications should be sent.
--
-- -   @EventEndpointDeleted@ – Topic ARN to which EndpointDeleted event
--     notifications should be sent.
--
-- -   @EventEndpointUpdated@ – Topic ARN to which EndpointUpdate event
--     notifications should be sent.
--
-- -   @EventDeliveryFailure@ – Topic ARN to which DeliveryFailure event
--     notifications should be sent upon Direct Publish delivery failure
--     (permanent) to one of the application\'s endpoints.
--
-- 'httpStatus', 'getPlatformApplicationAttributesResponse_httpStatus' - The response's http status code.
newGetPlatformApplicationAttributesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetPlatformApplicationAttributesResponse
newGetPlatformApplicationAttributesResponse :: Int -> GetPlatformApplicationAttributesResponse
newGetPlatformApplicationAttributesResponse
  Int
pHttpStatus_ =
    GetPlatformApplicationAttributesResponse'
      { $sel:attributes:GetPlatformApplicationAttributesResponse' :: Maybe (HashMap Text Text)
attributes =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetPlatformApplicationAttributesResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | Attributes include the following:
--
-- -   @AppleCertificateExpiryDate@ – The expiry date of the SSL
--     certificate used to configure certificate-based authentication.
--
-- -   @ApplePlatformTeamID@ – The Apple developer account ID used to
--     configure token-based authentication.
--
-- -   @ApplePlatformBundleID@ – The app identifier used to configure
--     token-based authentication.
--
-- -   @EventEndpointCreated@ – Topic ARN to which EndpointCreated event
--     notifications should be sent.
--
-- -   @EventEndpointDeleted@ – Topic ARN to which EndpointDeleted event
--     notifications should be sent.
--
-- -   @EventEndpointUpdated@ – Topic ARN to which EndpointUpdate event
--     notifications should be sent.
--
-- -   @EventDeliveryFailure@ – Topic ARN to which DeliveryFailure event
--     notifications should be sent upon Direct Publish delivery failure
--     (permanent) to one of the application\'s endpoints.
getPlatformApplicationAttributesResponse_attributes :: Lens.Lens' GetPlatformApplicationAttributesResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getPlatformApplicationAttributesResponse_attributes :: Lens'
  GetPlatformApplicationAttributesResponse
  (Maybe (HashMap Text Text))
getPlatformApplicationAttributesResponse_attributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPlatformApplicationAttributesResponse' {Maybe (HashMap Text Text)
attributes :: Maybe (HashMap Text Text)
$sel:attributes:GetPlatformApplicationAttributesResponse' :: GetPlatformApplicationAttributesResponse
-> Maybe (HashMap Text Text)
attributes} -> Maybe (HashMap Text Text)
attributes) (\s :: GetPlatformApplicationAttributesResponse
s@GetPlatformApplicationAttributesResponse' {} Maybe (HashMap Text Text)
a -> GetPlatformApplicationAttributesResponse
s {$sel:attributes:GetPlatformApplicationAttributesResponse' :: Maybe (HashMap Text Text)
attributes = Maybe (HashMap Text Text)
a} :: GetPlatformApplicationAttributesResponse) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

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