{-# 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.SetPlatformApplicationAttributes
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Sets 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>.
-- For information on configuring attributes for message delivery status,
-- see
-- <https://docs.aws.amazon.com/sns/latest/dg/sns-msg-status.html Using Amazon SNS Application Attributes for Message Delivery Status>.
module Amazonka.SNS.SetPlatformApplicationAttributes
  ( -- * Creating a Request
    SetPlatformApplicationAttributes (..),
    newSetPlatformApplicationAttributes,

    -- * Request Lenses
    setPlatformApplicationAttributes_platformApplicationArn,
    setPlatformApplicationAttributes_attributes,

    -- * Destructuring the Response
    SetPlatformApplicationAttributesResponse (..),
    newSetPlatformApplicationAttributesResponse,
  )
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 SetPlatformApplicationAttributes action.
--
-- /See:/ 'newSetPlatformApplicationAttributes' smart constructor.
data SetPlatformApplicationAttributes = SetPlatformApplicationAttributes'
  { -- | PlatformApplicationArn for SetPlatformApplicationAttributes action.
    SetPlatformApplicationAttributes -> Text
platformApplicationArn :: Prelude.Text,
    -- | A map of the platform application attributes. Attributes in this map
    -- include the following:
    --
    -- -   @PlatformCredential@ – The credential received from the notification
    --     service.
    --
    --     -   For ADM, @PlatformCredential@is client secret.
    --
    --     -   For Apple Services using certificate credentials,
    --         @PlatformCredential@ is private key.
    --
    --     -   For Apple Services using token credentials, @PlatformCredential@
    --         is signing key.
    --
    --     -   For GCM (Firebase Cloud Messaging), @PlatformCredential@ is API
    --         key.
    --
    -- -   @PlatformPrincipal@ – The principal received from the notification
    --     service.
    --
    --     -   For ADM, @PlatformPrincipal@is client id.
    --
    --     -   For Apple Services using certificate credentials,
    --         @PlatformPrincipal@ is SSL certificate.
    --
    --     -   For Apple Services using token credentials, @PlatformPrincipal@
    --         is signing key ID.
    --
    --     -   For GCM (Firebase Cloud Messaging), there is no
    --         @PlatformPrincipal@.
    --
    -- -   @EventEndpointCreated@ – Topic ARN to which @EndpointCreated@ event
    --     notifications are sent.
    --
    -- -   @EventEndpointDeleted@ – Topic ARN to which @EndpointDeleted@ event
    --     notifications are sent.
    --
    -- -   @EventEndpointUpdated@ – Topic ARN to which @EndpointUpdate@ event
    --     notifications are sent.
    --
    -- -   @EventDeliveryFailure@ – Topic ARN to which @DeliveryFailure@ event
    --     notifications are sent upon Direct Publish delivery failure
    --     (permanent) to one of the application\'s endpoints.
    --
    -- -   @SuccessFeedbackRoleArn@ – IAM role ARN used to give Amazon SNS
    --     write access to use CloudWatch Logs on your behalf.
    --
    -- -   @FailureFeedbackRoleArn@ – IAM role ARN used to give Amazon SNS
    --     write access to use CloudWatch Logs on your behalf.
    --
    -- -   @SuccessFeedbackSampleRate@ – Sample rate percentage (0-100) of
    --     successfully delivered messages.
    --
    -- The following attributes only apply to @APNs@ token-based
    -- authentication:
    --
    -- -   @ApplePlatformTeamID@ – The identifier that\'s assigned to your
    --     Apple developer account team.
    --
    -- -   @ApplePlatformBundleID@ – The bundle identifier that\'s assigned to
    --     your iOS app.
    SetPlatformApplicationAttributes -> HashMap Text Text
attributes :: Prelude.HashMap Prelude.Text Prelude.Text
  }
  deriving (SetPlatformApplicationAttributes
-> SetPlatformApplicationAttributes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetPlatformApplicationAttributes
-> SetPlatformApplicationAttributes -> Bool
$c/= :: SetPlatformApplicationAttributes
-> SetPlatformApplicationAttributes -> Bool
== :: SetPlatformApplicationAttributes
-> SetPlatformApplicationAttributes -> Bool
$c== :: SetPlatformApplicationAttributes
-> SetPlatformApplicationAttributes -> Bool
Prelude.Eq, ReadPrec [SetPlatformApplicationAttributes]
ReadPrec SetPlatformApplicationAttributes
Int -> ReadS SetPlatformApplicationAttributes
ReadS [SetPlatformApplicationAttributes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SetPlatformApplicationAttributes]
$creadListPrec :: ReadPrec [SetPlatformApplicationAttributes]
readPrec :: ReadPrec SetPlatformApplicationAttributes
$creadPrec :: ReadPrec SetPlatformApplicationAttributes
readList :: ReadS [SetPlatformApplicationAttributes]
$creadList :: ReadS [SetPlatformApplicationAttributes]
readsPrec :: Int -> ReadS SetPlatformApplicationAttributes
$creadsPrec :: Int -> ReadS SetPlatformApplicationAttributes
Prelude.Read, Int -> SetPlatformApplicationAttributes -> ShowS
[SetPlatformApplicationAttributes] -> ShowS
SetPlatformApplicationAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetPlatformApplicationAttributes] -> ShowS
$cshowList :: [SetPlatformApplicationAttributes] -> ShowS
show :: SetPlatformApplicationAttributes -> String
$cshow :: SetPlatformApplicationAttributes -> String
showsPrec :: Int -> SetPlatformApplicationAttributes -> ShowS
$cshowsPrec :: Int -> SetPlatformApplicationAttributes -> ShowS
Prelude.Show, forall x.
Rep SetPlatformApplicationAttributes x
-> SetPlatformApplicationAttributes
forall x.
SetPlatformApplicationAttributes
-> Rep SetPlatformApplicationAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SetPlatformApplicationAttributes x
-> SetPlatformApplicationAttributes
$cfrom :: forall x.
SetPlatformApplicationAttributes
-> Rep SetPlatformApplicationAttributes x
Prelude.Generic)

-- |
-- Create a value of 'SetPlatformApplicationAttributes' 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', 'setPlatformApplicationAttributes_platformApplicationArn' - PlatformApplicationArn for SetPlatformApplicationAttributes action.
--
-- 'attributes', 'setPlatformApplicationAttributes_attributes' - A map of the platform application attributes. Attributes in this map
-- include the following:
--
-- -   @PlatformCredential@ – The credential received from the notification
--     service.
--
--     -   For ADM, @PlatformCredential@is client secret.
--
--     -   For Apple Services using certificate credentials,
--         @PlatformCredential@ is private key.
--
--     -   For Apple Services using token credentials, @PlatformCredential@
--         is signing key.
--
--     -   For GCM (Firebase Cloud Messaging), @PlatformCredential@ is API
--         key.
--
-- -   @PlatformPrincipal@ – The principal received from the notification
--     service.
--
--     -   For ADM, @PlatformPrincipal@is client id.
--
--     -   For Apple Services using certificate credentials,
--         @PlatformPrincipal@ is SSL certificate.
--
--     -   For Apple Services using token credentials, @PlatformPrincipal@
--         is signing key ID.
--
--     -   For GCM (Firebase Cloud Messaging), there is no
--         @PlatformPrincipal@.
--
-- -   @EventEndpointCreated@ – Topic ARN to which @EndpointCreated@ event
--     notifications are sent.
--
-- -   @EventEndpointDeleted@ – Topic ARN to which @EndpointDeleted@ event
--     notifications are sent.
--
-- -   @EventEndpointUpdated@ – Topic ARN to which @EndpointUpdate@ event
--     notifications are sent.
--
-- -   @EventDeliveryFailure@ – Topic ARN to which @DeliveryFailure@ event
--     notifications are sent upon Direct Publish delivery failure
--     (permanent) to one of the application\'s endpoints.
--
-- -   @SuccessFeedbackRoleArn@ – IAM role ARN used to give Amazon SNS
--     write access to use CloudWatch Logs on your behalf.
--
-- -   @FailureFeedbackRoleArn@ – IAM role ARN used to give Amazon SNS
--     write access to use CloudWatch Logs on your behalf.
--
-- -   @SuccessFeedbackSampleRate@ – Sample rate percentage (0-100) of
--     successfully delivered messages.
--
-- The following attributes only apply to @APNs@ token-based
-- authentication:
--
-- -   @ApplePlatformTeamID@ – The identifier that\'s assigned to your
--     Apple developer account team.
--
-- -   @ApplePlatformBundleID@ – The bundle identifier that\'s assigned to
--     your iOS app.
newSetPlatformApplicationAttributes ::
  -- | 'platformApplicationArn'
  Prelude.Text ->
  SetPlatformApplicationAttributes
newSetPlatformApplicationAttributes :: Text -> SetPlatformApplicationAttributes
newSetPlatformApplicationAttributes
  Text
pPlatformApplicationArn_ =
    SetPlatformApplicationAttributes'
      { $sel:platformApplicationArn:SetPlatformApplicationAttributes' :: Text
platformApplicationArn =
          Text
pPlatformApplicationArn_,
        $sel:attributes:SetPlatformApplicationAttributes' :: HashMap Text Text
attributes = forall a. Monoid a => a
Prelude.mempty
      }

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

-- | A map of the platform application attributes. Attributes in this map
-- include the following:
--
-- -   @PlatformCredential@ – The credential received from the notification
--     service.
--
--     -   For ADM, @PlatformCredential@is client secret.
--
--     -   For Apple Services using certificate credentials,
--         @PlatformCredential@ is private key.
--
--     -   For Apple Services using token credentials, @PlatformCredential@
--         is signing key.
--
--     -   For GCM (Firebase Cloud Messaging), @PlatformCredential@ is API
--         key.
--
-- -   @PlatformPrincipal@ – The principal received from the notification
--     service.
--
--     -   For ADM, @PlatformPrincipal@is client id.
--
--     -   For Apple Services using certificate credentials,
--         @PlatformPrincipal@ is SSL certificate.
--
--     -   For Apple Services using token credentials, @PlatformPrincipal@
--         is signing key ID.
--
--     -   For GCM (Firebase Cloud Messaging), there is no
--         @PlatformPrincipal@.
--
-- -   @EventEndpointCreated@ – Topic ARN to which @EndpointCreated@ event
--     notifications are sent.
--
-- -   @EventEndpointDeleted@ – Topic ARN to which @EndpointDeleted@ event
--     notifications are sent.
--
-- -   @EventEndpointUpdated@ – Topic ARN to which @EndpointUpdate@ event
--     notifications are sent.
--
-- -   @EventDeliveryFailure@ – Topic ARN to which @DeliveryFailure@ event
--     notifications are sent upon Direct Publish delivery failure
--     (permanent) to one of the application\'s endpoints.
--
-- -   @SuccessFeedbackRoleArn@ – IAM role ARN used to give Amazon SNS
--     write access to use CloudWatch Logs on your behalf.
--
-- -   @FailureFeedbackRoleArn@ – IAM role ARN used to give Amazon SNS
--     write access to use CloudWatch Logs on your behalf.
--
-- -   @SuccessFeedbackSampleRate@ – Sample rate percentage (0-100) of
--     successfully delivered messages.
--
-- The following attributes only apply to @APNs@ token-based
-- authentication:
--
-- -   @ApplePlatformTeamID@ – The identifier that\'s assigned to your
--     Apple developer account team.
--
-- -   @ApplePlatformBundleID@ – The bundle identifier that\'s assigned to
--     your iOS app.
setPlatformApplicationAttributes_attributes :: Lens.Lens' SetPlatformApplicationAttributes (Prelude.HashMap Prelude.Text Prelude.Text)
setPlatformApplicationAttributes_attributes :: Lens' SetPlatformApplicationAttributes (HashMap Text Text)
setPlatformApplicationAttributes_attributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SetPlatformApplicationAttributes' {HashMap Text Text
attributes :: HashMap Text Text
$sel:attributes:SetPlatformApplicationAttributes' :: SetPlatformApplicationAttributes -> HashMap Text Text
attributes} -> HashMap Text Text
attributes) (\s :: SetPlatformApplicationAttributes
s@SetPlatformApplicationAttributes' {} HashMap Text Text
a -> SetPlatformApplicationAttributes
s {$sel:attributes:SetPlatformApplicationAttributes' :: HashMap Text Text
attributes = HashMap Text Text
a} :: SetPlatformApplicationAttributes) 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

instance
  Core.AWSRequest
    SetPlatformApplicationAttributes
  where
  type
    AWSResponse SetPlatformApplicationAttributes =
      SetPlatformApplicationAttributesResponse
  request :: (Service -> Service)
-> SetPlatformApplicationAttributes
-> Request SetPlatformApplicationAttributes
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 SetPlatformApplicationAttributes
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse SetPlatformApplicationAttributes)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      SetPlatformApplicationAttributesResponse
SetPlatformApplicationAttributesResponse'

instance
  Prelude.Hashable
    SetPlatformApplicationAttributes
  where
  hashWithSalt :: Int -> SetPlatformApplicationAttributes -> Int
hashWithSalt
    Int
_salt
    SetPlatformApplicationAttributes' {Text
HashMap Text Text
attributes :: HashMap Text Text
platformApplicationArn :: Text
$sel:attributes:SetPlatformApplicationAttributes' :: SetPlatformApplicationAttributes -> HashMap Text Text
$sel:platformApplicationArn:SetPlatformApplicationAttributes' :: SetPlatformApplicationAttributes -> Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
platformApplicationArn
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` HashMap Text Text
attributes

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

instance
  Data.ToHeaders
    SetPlatformApplicationAttributes
  where
  toHeaders :: SetPlatformApplicationAttributes -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance
  Data.ToQuery
    SetPlatformApplicationAttributes
  where
  toQuery :: SetPlatformApplicationAttributes -> QueryString
toQuery SetPlatformApplicationAttributes' {Text
HashMap Text Text
attributes :: HashMap Text Text
platformApplicationArn :: Text
$sel:attributes:SetPlatformApplicationAttributes' :: SetPlatformApplicationAttributes -> HashMap Text Text
$sel:platformApplicationArn:SetPlatformApplicationAttributes' :: SetPlatformApplicationAttributes -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"SetPlatformApplicationAttributes" ::
                      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,
        ByteString
"Attributes"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall k v.
(ToQuery k, ToQuery v) =>
ByteString
-> ByteString -> ByteString -> HashMap k v -> QueryString
Data.toQueryMap ByteString
"entry" ByteString
"key" ByteString
"value" HashMap Text Text
attributes
      ]

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

-- |
-- Create a value of 'SetPlatformApplicationAttributesResponse' 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.
newSetPlatformApplicationAttributesResponse ::
  SetPlatformApplicationAttributesResponse
newSetPlatformApplicationAttributesResponse :: SetPlatformApplicationAttributesResponse
newSetPlatformApplicationAttributesResponse =
  SetPlatformApplicationAttributesResponse
SetPlatformApplicationAttributesResponse'

instance
  Prelude.NFData
    SetPlatformApplicationAttributesResponse
  where
  rnf :: SetPlatformApplicationAttributesResponse -> ()
rnf SetPlatformApplicationAttributesResponse
_ = ()