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

    -- * Request Lenses
    getApnsVoipChannel_applicationId,

    -- * Destructuring the Response
    GetApnsVoipChannelResponse (..),
    newGetApnsVoipChannelResponse,

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

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

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

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

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

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

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

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

-- |
-- Create a value of 'GetApnsVoipChannelResponse' 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', 'getApnsVoipChannelResponse_httpStatus' - The response's http status code.
--
-- 'aPNSVoipChannelResponse', 'getApnsVoipChannelResponse_aPNSVoipChannelResponse' - Undocumented member.
newGetApnsVoipChannelResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'aPNSVoipChannelResponse'
  APNSVoipChannelResponse ->
  GetApnsVoipChannelResponse
newGetApnsVoipChannelResponse :: Int -> APNSVoipChannelResponse -> GetApnsVoipChannelResponse
newGetApnsVoipChannelResponse
  Int
pHttpStatus_
  APNSVoipChannelResponse
pAPNSVoipChannelResponse_ =
    GetApnsVoipChannelResponse'
      { $sel:httpStatus:GetApnsVoipChannelResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:aPNSVoipChannelResponse:GetApnsVoipChannelResponse' :: APNSVoipChannelResponse
aPNSVoipChannelResponse =
          APNSVoipChannelResponse
pAPNSVoipChannelResponse_
      }

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

-- | Undocumented member.
getApnsVoipChannelResponse_aPNSVoipChannelResponse :: Lens.Lens' GetApnsVoipChannelResponse APNSVoipChannelResponse
getApnsVoipChannelResponse_aPNSVoipChannelResponse :: Lens' GetApnsVoipChannelResponse APNSVoipChannelResponse
getApnsVoipChannelResponse_aPNSVoipChannelResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApnsVoipChannelResponse' {APNSVoipChannelResponse
aPNSVoipChannelResponse :: APNSVoipChannelResponse
$sel:aPNSVoipChannelResponse:GetApnsVoipChannelResponse' :: GetApnsVoipChannelResponse -> APNSVoipChannelResponse
aPNSVoipChannelResponse} -> APNSVoipChannelResponse
aPNSVoipChannelResponse) (\s :: GetApnsVoipChannelResponse
s@GetApnsVoipChannelResponse' {} APNSVoipChannelResponse
a -> GetApnsVoipChannelResponse
s {$sel:aPNSVoipChannelResponse:GetApnsVoipChannelResponse' :: APNSVoipChannelResponse
aPNSVoipChannelResponse = APNSVoipChannelResponse
a} :: GetApnsVoipChannelResponse)

instance Prelude.NFData GetApnsVoipChannelResponse where
  rnf :: GetApnsVoipChannelResponse -> ()
rnf GetApnsVoipChannelResponse' {Int
APNSVoipChannelResponse
aPNSVoipChannelResponse :: APNSVoipChannelResponse
httpStatus :: Int
$sel:aPNSVoipChannelResponse:GetApnsVoipChannelResponse' :: GetApnsVoipChannelResponse -> APNSVoipChannelResponse
$sel:httpStatus:GetApnsVoipChannelResponse' :: GetApnsVoipChannelResponse -> 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 APNSVoipChannelResponse
aPNSVoipChannelResponse