{-# 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.DeleteApnsChannel
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Disables the APNs channel for an application and deletes any existing
-- settings for the channel.
module Amazonka.Pinpoint.DeleteApnsChannel
  ( -- * Creating a Request
    DeleteApnsChannel (..),
    newDeleteApnsChannel,

    -- * Request Lenses
    deleteApnsChannel_applicationId,

    -- * Destructuring the Response
    DeleteApnsChannelResponse (..),
    newDeleteApnsChannelResponse,

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

-- |
-- Create a value of 'DeleteApnsChannel' 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', 'deleteApnsChannel_applicationId' - The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
newDeleteApnsChannel ::
  -- | 'applicationId'
  Prelude.Text ->
  DeleteApnsChannel
newDeleteApnsChannel :: Text -> DeleteApnsChannel
newDeleteApnsChannel Text
pApplicationId_ =
  DeleteApnsChannel' {$sel:applicationId:DeleteApnsChannel' :: Text
applicationId = Text
pApplicationId_}

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

instance Core.AWSRequest DeleteApnsChannel where
  type
    AWSResponse DeleteApnsChannel =
      DeleteApnsChannelResponse
  request :: (Service -> Service)
-> DeleteApnsChannel -> Request DeleteApnsChannel
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteApnsChannel
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteApnsChannel)))
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 -> APNSChannelResponse -> DeleteApnsChannelResponse
DeleteApnsChannelResponse'
            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 DeleteApnsChannel where
  hashWithSalt :: Int -> DeleteApnsChannel -> Int
hashWithSalt Int
_salt DeleteApnsChannel' {Text
applicationId :: Text
$sel:applicationId:DeleteApnsChannel' :: DeleteApnsChannel -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId

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

instance Data.ToHeaders DeleteApnsChannel where
  toHeaders :: DeleteApnsChannel -> 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 DeleteApnsChannel where
  toPath :: DeleteApnsChannel -> ByteString
toPath DeleteApnsChannel' {Text
applicationId :: Text
$sel:applicationId:DeleteApnsChannel' :: DeleteApnsChannel -> 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"
      ]

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

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

-- |
-- Create a value of 'DeleteApnsChannelResponse' 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', 'deleteApnsChannelResponse_httpStatus' - The response's http status code.
--
-- 'aPNSChannelResponse', 'deleteApnsChannelResponse_aPNSChannelResponse' - Undocumented member.
newDeleteApnsChannelResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'aPNSChannelResponse'
  APNSChannelResponse ->
  DeleteApnsChannelResponse
newDeleteApnsChannelResponse :: Int -> APNSChannelResponse -> DeleteApnsChannelResponse
newDeleteApnsChannelResponse
  Int
pHttpStatus_
  APNSChannelResponse
pAPNSChannelResponse_ =
    DeleteApnsChannelResponse'
      { $sel:httpStatus:DeleteApnsChannelResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:aPNSChannelResponse:DeleteApnsChannelResponse' :: APNSChannelResponse
aPNSChannelResponse = APNSChannelResponse
pAPNSChannelResponse_
      }

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

-- | Undocumented member.
deleteApnsChannelResponse_aPNSChannelResponse :: Lens.Lens' DeleteApnsChannelResponse APNSChannelResponse
deleteApnsChannelResponse_aPNSChannelResponse :: Lens' DeleteApnsChannelResponse APNSChannelResponse
deleteApnsChannelResponse_aPNSChannelResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteApnsChannelResponse' {APNSChannelResponse
aPNSChannelResponse :: APNSChannelResponse
$sel:aPNSChannelResponse:DeleteApnsChannelResponse' :: DeleteApnsChannelResponse -> APNSChannelResponse
aPNSChannelResponse} -> APNSChannelResponse
aPNSChannelResponse) (\s :: DeleteApnsChannelResponse
s@DeleteApnsChannelResponse' {} APNSChannelResponse
a -> DeleteApnsChannelResponse
s {$sel:aPNSChannelResponse:DeleteApnsChannelResponse' :: APNSChannelResponse
aPNSChannelResponse = APNSChannelResponse
a} :: DeleteApnsChannelResponse)

instance Prelude.NFData DeleteApnsChannelResponse where
  rnf :: DeleteApnsChannelResponse -> ()
rnf DeleteApnsChannelResponse' {Int
APNSChannelResponse
aPNSChannelResponse :: APNSChannelResponse
httpStatus :: Int
$sel:aPNSChannelResponse:DeleteApnsChannelResponse' :: DeleteApnsChannelResponse -> APNSChannelResponse
$sel:httpStatus:DeleteApnsChannelResponse' :: DeleteApnsChannelResponse -> 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 APNSChannelResponse
aPNSChannelResponse