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

    -- * Request Lenses
    deleteVoiceChannel_applicationId,

    -- * Destructuring the Response
    DeleteVoiceChannelResponse (..),
    newDeleteVoiceChannelResponse,

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

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

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

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

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

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

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

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

-- |
-- Create a value of 'DeleteVoiceChannelResponse' 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', 'deleteVoiceChannelResponse_httpStatus' - The response's http status code.
--
-- 'voiceChannelResponse', 'deleteVoiceChannelResponse_voiceChannelResponse' - Undocumented member.
newDeleteVoiceChannelResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'voiceChannelResponse'
  VoiceChannelResponse ->
  DeleteVoiceChannelResponse
newDeleteVoiceChannelResponse :: Int -> VoiceChannelResponse -> DeleteVoiceChannelResponse
newDeleteVoiceChannelResponse
  Int
pHttpStatus_
  VoiceChannelResponse
pVoiceChannelResponse_ =
    DeleteVoiceChannelResponse'
      { $sel:httpStatus:DeleteVoiceChannelResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:voiceChannelResponse:DeleteVoiceChannelResponse' :: VoiceChannelResponse
voiceChannelResponse = VoiceChannelResponse
pVoiceChannelResponse_
      }

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

-- | Undocumented member.
deleteVoiceChannelResponse_voiceChannelResponse :: Lens.Lens' DeleteVoiceChannelResponse VoiceChannelResponse
deleteVoiceChannelResponse_voiceChannelResponse :: Lens' DeleteVoiceChannelResponse VoiceChannelResponse
deleteVoiceChannelResponse_voiceChannelResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVoiceChannelResponse' {VoiceChannelResponse
voiceChannelResponse :: VoiceChannelResponse
$sel:voiceChannelResponse:DeleteVoiceChannelResponse' :: DeleteVoiceChannelResponse -> VoiceChannelResponse
voiceChannelResponse} -> VoiceChannelResponse
voiceChannelResponse) (\s :: DeleteVoiceChannelResponse
s@DeleteVoiceChannelResponse' {} VoiceChannelResponse
a -> DeleteVoiceChannelResponse
s {$sel:voiceChannelResponse:DeleteVoiceChannelResponse' :: VoiceChannelResponse
voiceChannelResponse = VoiceChannelResponse
a} :: DeleteVoiceChannelResponse)

instance Prelude.NFData DeleteVoiceChannelResponse where
  rnf :: DeleteVoiceChannelResponse -> ()
rnf DeleteVoiceChannelResponse' {Int
VoiceChannelResponse
voiceChannelResponse :: VoiceChannelResponse
httpStatus :: Int
$sel:voiceChannelResponse:DeleteVoiceChannelResponse' :: DeleteVoiceChannelResponse -> VoiceChannelResponse
$sel:httpStatus:DeleteVoiceChannelResponse' :: DeleteVoiceChannelResponse -> 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 VoiceChannelResponse
voiceChannelResponse