{-# 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.Pinpoint.UpdateApnsSandboxChannel
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Enables the APNs sandbox channel for an application or updates the
-- status and settings of the APNs sandbox channel for an application.
module Amazonka.Pinpoint.UpdateApnsSandboxChannel
  ( -- * Creating a Request
    UpdateApnsSandboxChannel (..),
    newUpdateApnsSandboxChannel,

    -- * Request Lenses
    updateApnsSandboxChannel_applicationId,
    updateApnsSandboxChannel_aPNSSandboxChannelRequest,

    -- * Destructuring the Response
    UpdateApnsSandboxChannelResponse (..),
    newUpdateApnsSandboxChannelResponse,

    -- * Response Lenses
    updateApnsSandboxChannelResponse_httpStatus,
    updateApnsSandboxChannelResponse_aPNSSandboxChannelResponse,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Pinpoint.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateApnsSandboxChannel' smart constructor.
data UpdateApnsSandboxChannel = UpdateApnsSandboxChannel'
  { -- | The unique identifier for the application. This identifier is displayed
    -- as the __Project ID__ on the Amazon Pinpoint console.
    UpdateApnsSandboxChannel -> Text
applicationId :: Prelude.Text,
    UpdateApnsSandboxChannel -> APNSSandboxChannelRequest
aPNSSandboxChannelRequest :: APNSSandboxChannelRequest
  }
  deriving (UpdateApnsSandboxChannel -> UpdateApnsSandboxChannel -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateApnsSandboxChannel -> UpdateApnsSandboxChannel -> Bool
$c/= :: UpdateApnsSandboxChannel -> UpdateApnsSandboxChannel -> Bool
== :: UpdateApnsSandboxChannel -> UpdateApnsSandboxChannel -> Bool
$c== :: UpdateApnsSandboxChannel -> UpdateApnsSandboxChannel -> Bool
Prelude.Eq, ReadPrec [UpdateApnsSandboxChannel]
ReadPrec UpdateApnsSandboxChannel
Int -> ReadS UpdateApnsSandboxChannel
ReadS [UpdateApnsSandboxChannel]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateApnsSandboxChannel]
$creadListPrec :: ReadPrec [UpdateApnsSandboxChannel]
readPrec :: ReadPrec UpdateApnsSandboxChannel
$creadPrec :: ReadPrec UpdateApnsSandboxChannel
readList :: ReadS [UpdateApnsSandboxChannel]
$creadList :: ReadS [UpdateApnsSandboxChannel]
readsPrec :: Int -> ReadS UpdateApnsSandboxChannel
$creadsPrec :: Int -> ReadS UpdateApnsSandboxChannel
Prelude.Read, Int -> UpdateApnsSandboxChannel -> ShowS
[UpdateApnsSandboxChannel] -> ShowS
UpdateApnsSandboxChannel -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateApnsSandboxChannel] -> ShowS
$cshowList :: [UpdateApnsSandboxChannel] -> ShowS
show :: UpdateApnsSandboxChannel -> String
$cshow :: UpdateApnsSandboxChannel -> String
showsPrec :: Int -> UpdateApnsSandboxChannel -> ShowS
$cshowsPrec :: Int -> UpdateApnsSandboxChannel -> ShowS
Prelude.Show, forall x.
Rep UpdateApnsSandboxChannel x -> UpdateApnsSandboxChannel
forall x.
UpdateApnsSandboxChannel -> Rep UpdateApnsSandboxChannel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateApnsSandboxChannel x -> UpdateApnsSandboxChannel
$cfrom :: forall x.
UpdateApnsSandboxChannel -> Rep UpdateApnsSandboxChannel x
Prelude.Generic)

-- |
-- Create a value of 'UpdateApnsSandboxChannel' 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:
--
-- 'applicationId', 'updateApnsSandboxChannel_applicationId' - The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
--
-- 'aPNSSandboxChannelRequest', 'updateApnsSandboxChannel_aPNSSandboxChannelRequest' - Undocumented member.
newUpdateApnsSandboxChannel ::
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'aPNSSandboxChannelRequest'
  APNSSandboxChannelRequest ->
  UpdateApnsSandboxChannel
newUpdateApnsSandboxChannel :: Text -> APNSSandboxChannelRequest -> UpdateApnsSandboxChannel
newUpdateApnsSandboxChannel
  Text
pApplicationId_
  APNSSandboxChannelRequest
pAPNSSandboxChannelRequest_ =
    UpdateApnsSandboxChannel'
      { $sel:applicationId:UpdateApnsSandboxChannel' :: Text
applicationId =
          Text
pApplicationId_,
        $sel:aPNSSandboxChannelRequest:UpdateApnsSandboxChannel' :: APNSSandboxChannelRequest
aPNSSandboxChannelRequest =
          APNSSandboxChannelRequest
pAPNSSandboxChannelRequest_
      }

-- | The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
updateApnsSandboxChannel_applicationId :: Lens.Lens' UpdateApnsSandboxChannel Prelude.Text
updateApnsSandboxChannel_applicationId :: Lens' UpdateApnsSandboxChannel Text
updateApnsSandboxChannel_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateApnsSandboxChannel' {Text
applicationId :: Text
$sel:applicationId:UpdateApnsSandboxChannel' :: UpdateApnsSandboxChannel -> Text
applicationId} -> Text
applicationId) (\s :: UpdateApnsSandboxChannel
s@UpdateApnsSandboxChannel' {} Text
a -> UpdateApnsSandboxChannel
s {$sel:applicationId:UpdateApnsSandboxChannel' :: Text
applicationId = Text
a} :: UpdateApnsSandboxChannel)

-- | Undocumented member.
updateApnsSandboxChannel_aPNSSandboxChannelRequest :: Lens.Lens' UpdateApnsSandboxChannel APNSSandboxChannelRequest
updateApnsSandboxChannel_aPNSSandboxChannelRequest :: Lens' UpdateApnsSandboxChannel APNSSandboxChannelRequest
updateApnsSandboxChannel_aPNSSandboxChannelRequest = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateApnsSandboxChannel' {APNSSandboxChannelRequest
aPNSSandboxChannelRequest :: APNSSandboxChannelRequest
$sel:aPNSSandboxChannelRequest:UpdateApnsSandboxChannel' :: UpdateApnsSandboxChannel -> APNSSandboxChannelRequest
aPNSSandboxChannelRequest} -> APNSSandboxChannelRequest
aPNSSandboxChannelRequest) (\s :: UpdateApnsSandboxChannel
s@UpdateApnsSandboxChannel' {} APNSSandboxChannelRequest
a -> UpdateApnsSandboxChannel
s {$sel:aPNSSandboxChannelRequest:UpdateApnsSandboxChannel' :: APNSSandboxChannelRequest
aPNSSandboxChannelRequest = APNSSandboxChannelRequest
a} :: UpdateApnsSandboxChannel)

instance Core.AWSRequest UpdateApnsSandboxChannel where
  type
    AWSResponse UpdateApnsSandboxChannel =
      UpdateApnsSandboxChannelResponse
  request :: (Service -> Service)
-> UpdateApnsSandboxChannel -> Request UpdateApnsSandboxChannel
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateApnsSandboxChannel
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateApnsSandboxChannel)))
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 ->
          Int
-> APNSSandboxChannelResponse -> UpdateApnsSandboxChannelResponse
UpdateApnsSandboxChannelResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)
      )

instance Prelude.Hashable UpdateApnsSandboxChannel where
  hashWithSalt :: Int -> UpdateApnsSandboxChannel -> Int
hashWithSalt Int
_salt UpdateApnsSandboxChannel' {Text
APNSSandboxChannelRequest
aPNSSandboxChannelRequest :: APNSSandboxChannelRequest
applicationId :: Text
$sel:aPNSSandboxChannelRequest:UpdateApnsSandboxChannel' :: UpdateApnsSandboxChannel -> APNSSandboxChannelRequest
$sel:applicationId:UpdateApnsSandboxChannel' :: UpdateApnsSandboxChannel -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` APNSSandboxChannelRequest
aPNSSandboxChannelRequest

instance Prelude.NFData UpdateApnsSandboxChannel where
  rnf :: UpdateApnsSandboxChannel -> ()
rnf UpdateApnsSandboxChannel' {Text
APNSSandboxChannelRequest
aPNSSandboxChannelRequest :: APNSSandboxChannelRequest
applicationId :: Text
$sel:aPNSSandboxChannelRequest:UpdateApnsSandboxChannel' :: UpdateApnsSandboxChannel -> APNSSandboxChannelRequest
$sel:applicationId:UpdateApnsSandboxChannel' :: UpdateApnsSandboxChannel -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf APNSSandboxChannelRequest
aPNSSandboxChannelRequest

instance Data.ToHeaders UpdateApnsSandboxChannel where
  toHeaders :: UpdateApnsSandboxChannel -> 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 UpdateApnsSandboxChannel where
  toJSON :: UpdateApnsSandboxChannel -> Value
toJSON UpdateApnsSandboxChannel' {Text
APNSSandboxChannelRequest
aPNSSandboxChannelRequest :: APNSSandboxChannelRequest
applicationId :: Text
$sel:aPNSSandboxChannelRequest:UpdateApnsSandboxChannel' :: UpdateApnsSandboxChannel -> APNSSandboxChannelRequest
$sel:applicationId:UpdateApnsSandboxChannel' :: UpdateApnsSandboxChannel -> Text
..} =
    forall a. ToJSON a => a -> Value
Data.toJSON APNSSandboxChannelRequest
aPNSSandboxChannelRequest

instance Data.ToPath UpdateApnsSandboxChannel where
  toPath :: UpdateApnsSandboxChannel -> ByteString
toPath UpdateApnsSandboxChannel' {Text
APNSSandboxChannelRequest
aPNSSandboxChannelRequest :: APNSSandboxChannelRequest
applicationId :: Text
$sel:aPNSSandboxChannelRequest:UpdateApnsSandboxChannel' :: UpdateApnsSandboxChannel -> APNSSandboxChannelRequest
$sel:applicationId:UpdateApnsSandboxChannel' :: UpdateApnsSandboxChannel -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/apps/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
        ByteString
"/channels/apns_sandbox"
      ]

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

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

-- |
-- Create a value of 'UpdateApnsSandboxChannelResponse' 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:
--
-- 'httpStatus', 'updateApnsSandboxChannelResponse_httpStatus' - The response's http status code.
--
-- 'aPNSSandboxChannelResponse', 'updateApnsSandboxChannelResponse_aPNSSandboxChannelResponse' - Undocumented member.
newUpdateApnsSandboxChannelResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'aPNSSandboxChannelResponse'
  APNSSandboxChannelResponse ->
  UpdateApnsSandboxChannelResponse
newUpdateApnsSandboxChannelResponse :: Int
-> APNSSandboxChannelResponse -> UpdateApnsSandboxChannelResponse
newUpdateApnsSandboxChannelResponse
  Int
pHttpStatus_
  APNSSandboxChannelResponse
pAPNSSandboxChannelResponse_ =
    UpdateApnsSandboxChannelResponse'
      { $sel:httpStatus:UpdateApnsSandboxChannelResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:aPNSSandboxChannelResponse:UpdateApnsSandboxChannelResponse' :: APNSSandboxChannelResponse
aPNSSandboxChannelResponse =
          APNSSandboxChannelResponse
pAPNSSandboxChannelResponse_
      }

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

-- | Undocumented member.
updateApnsSandboxChannelResponse_aPNSSandboxChannelResponse :: Lens.Lens' UpdateApnsSandboxChannelResponse APNSSandboxChannelResponse
updateApnsSandboxChannelResponse_aPNSSandboxChannelResponse :: Lens' UpdateApnsSandboxChannelResponse APNSSandboxChannelResponse
updateApnsSandboxChannelResponse_aPNSSandboxChannelResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateApnsSandboxChannelResponse' {APNSSandboxChannelResponse
aPNSSandboxChannelResponse :: APNSSandboxChannelResponse
$sel:aPNSSandboxChannelResponse:UpdateApnsSandboxChannelResponse' :: UpdateApnsSandboxChannelResponse -> APNSSandboxChannelResponse
aPNSSandboxChannelResponse} -> APNSSandboxChannelResponse
aPNSSandboxChannelResponse) (\s :: UpdateApnsSandboxChannelResponse
s@UpdateApnsSandboxChannelResponse' {} APNSSandboxChannelResponse
a -> UpdateApnsSandboxChannelResponse
s {$sel:aPNSSandboxChannelResponse:UpdateApnsSandboxChannelResponse' :: APNSSandboxChannelResponse
aPNSSandboxChannelResponse = APNSSandboxChannelResponse
a} :: UpdateApnsSandboxChannelResponse)

instance
  Prelude.NFData
    UpdateApnsSandboxChannelResponse
  where
  rnf :: UpdateApnsSandboxChannelResponse -> ()
rnf UpdateApnsSandboxChannelResponse' {Int
APNSSandboxChannelResponse
aPNSSandboxChannelResponse :: APNSSandboxChannelResponse
httpStatus :: Int
$sel:aPNSSandboxChannelResponse:UpdateApnsSandboxChannelResponse' :: UpdateApnsSandboxChannelResponse -> APNSSandboxChannelResponse
$sel:httpStatus:UpdateApnsSandboxChannelResponse' :: UpdateApnsSandboxChannelResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf APNSSandboxChannelResponse
aPNSSandboxChannelResponse