{-# 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.DeleteBaiduChannel
-- 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 Baidu channel for an application and deletes any existing
-- settings for the channel.
module Amazonka.Pinpoint.DeleteBaiduChannel
  ( -- * Creating a Request
    DeleteBaiduChannel (..),
    newDeleteBaiduChannel,

    -- * Request Lenses
    deleteBaiduChannel_applicationId,

    -- * Destructuring the Response
    DeleteBaiduChannelResponse (..),
    newDeleteBaiduChannelResponse,

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

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

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

instance Core.AWSRequest DeleteBaiduChannel where
  type
    AWSResponse DeleteBaiduChannel =
      DeleteBaiduChannelResponse
  request :: (Service -> Service)
-> DeleteBaiduChannel -> Request DeleteBaiduChannel
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 DeleteBaiduChannel
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteBaiduChannel)))
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 -> BaiduChannelResponse -> DeleteBaiduChannelResponse
DeleteBaiduChannelResponse'
            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 DeleteBaiduChannel where
  hashWithSalt :: Int -> DeleteBaiduChannel -> Int
hashWithSalt Int
_salt DeleteBaiduChannel' {Text
applicationId :: Text
$sel:applicationId:DeleteBaiduChannel' :: DeleteBaiduChannel -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId

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

instance Data.ToHeaders DeleteBaiduChannel where
  toHeaders :: DeleteBaiduChannel -> 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 DeleteBaiduChannel where
  toPath :: DeleteBaiduChannel -> ByteString
toPath DeleteBaiduChannel' {Text
applicationId :: Text
$sel:applicationId:DeleteBaiduChannel' :: DeleteBaiduChannel -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/apps/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
        ByteString
"/channels/baidu"
      ]

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

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

-- |
-- Create a value of 'DeleteBaiduChannelResponse' 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', 'deleteBaiduChannelResponse_httpStatus' - The response's http status code.
--
-- 'baiduChannelResponse', 'deleteBaiduChannelResponse_baiduChannelResponse' - Undocumented member.
newDeleteBaiduChannelResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'baiduChannelResponse'
  BaiduChannelResponse ->
  DeleteBaiduChannelResponse
newDeleteBaiduChannelResponse :: Int -> BaiduChannelResponse -> DeleteBaiduChannelResponse
newDeleteBaiduChannelResponse
  Int
pHttpStatus_
  BaiduChannelResponse
pBaiduChannelResponse_ =
    DeleteBaiduChannelResponse'
      { $sel:httpStatus:DeleteBaiduChannelResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:baiduChannelResponse:DeleteBaiduChannelResponse' :: BaiduChannelResponse
baiduChannelResponse = BaiduChannelResponse
pBaiduChannelResponse_
      }

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

-- | Undocumented member.
deleteBaiduChannelResponse_baiduChannelResponse :: Lens.Lens' DeleteBaiduChannelResponse BaiduChannelResponse
deleteBaiduChannelResponse_baiduChannelResponse :: Lens' DeleteBaiduChannelResponse BaiduChannelResponse
deleteBaiduChannelResponse_baiduChannelResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBaiduChannelResponse' {BaiduChannelResponse
baiduChannelResponse :: BaiduChannelResponse
$sel:baiduChannelResponse:DeleteBaiduChannelResponse' :: DeleteBaiduChannelResponse -> BaiduChannelResponse
baiduChannelResponse} -> BaiduChannelResponse
baiduChannelResponse) (\s :: DeleteBaiduChannelResponse
s@DeleteBaiduChannelResponse' {} BaiduChannelResponse
a -> DeleteBaiduChannelResponse
s {$sel:baiduChannelResponse:DeleteBaiduChannelResponse' :: BaiduChannelResponse
baiduChannelResponse = BaiduChannelResponse
a} :: DeleteBaiduChannelResponse)

instance Prelude.NFData DeleteBaiduChannelResponse where
  rnf :: DeleteBaiduChannelResponse -> ()
rnf DeleteBaiduChannelResponse' {Int
BaiduChannelResponse
baiduChannelResponse :: BaiduChannelResponse
httpStatus :: Int
$sel:baiduChannelResponse:DeleteBaiduChannelResponse' :: DeleteBaiduChannelResponse -> BaiduChannelResponse
$sel:httpStatus:DeleteBaiduChannelResponse' :: DeleteBaiduChannelResponse -> 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 BaiduChannelResponse
baiduChannelResponse