{-# 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 #-}
module Amazonka.Pinpoint.GetChannels
(
GetChannels (..),
newGetChannels,
getChannels_applicationId,
GetChannelsResponse (..),
newGetChannelsResponse,
getChannelsResponse_httpStatus,
getChannelsResponse_channelsResponse,
)
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
data GetChannels = GetChannels'
{
GetChannels -> Text
applicationId :: Prelude.Text
}
deriving (GetChannels -> GetChannels -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetChannels -> GetChannels -> Bool
$c/= :: GetChannels -> GetChannels -> Bool
== :: GetChannels -> GetChannels -> Bool
$c== :: GetChannels -> GetChannels -> Bool
Prelude.Eq, ReadPrec [GetChannels]
ReadPrec GetChannels
Int -> ReadS GetChannels
ReadS [GetChannels]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetChannels]
$creadListPrec :: ReadPrec [GetChannels]
readPrec :: ReadPrec GetChannels
$creadPrec :: ReadPrec GetChannels
readList :: ReadS [GetChannels]
$creadList :: ReadS [GetChannels]
readsPrec :: Int -> ReadS GetChannels
$creadsPrec :: Int -> ReadS GetChannels
Prelude.Read, Int -> GetChannels -> ShowS
[GetChannels] -> ShowS
GetChannels -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetChannels] -> ShowS
$cshowList :: [GetChannels] -> ShowS
show :: GetChannels -> String
$cshow :: GetChannels -> String
showsPrec :: Int -> GetChannels -> ShowS
$cshowsPrec :: Int -> GetChannels -> ShowS
Prelude.Show, forall x. Rep GetChannels x -> GetChannels
forall x. GetChannels -> Rep GetChannels x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetChannels x -> GetChannels
$cfrom :: forall x. GetChannels -> Rep GetChannels x
Prelude.Generic)
newGetChannels ::
Prelude.Text ->
GetChannels
newGetChannels :: Text -> GetChannels
newGetChannels Text
pApplicationId_ =
GetChannels' {$sel:applicationId:GetChannels' :: Text
applicationId = Text
pApplicationId_}
getChannels_applicationId :: Lens.Lens' GetChannels Prelude.Text
getChannels_applicationId :: Lens' GetChannels Text
getChannels_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetChannels' {Text
applicationId :: Text
$sel:applicationId:GetChannels' :: GetChannels -> Text
applicationId} -> Text
applicationId) (\s :: GetChannels
s@GetChannels' {} Text
a -> GetChannels
s {$sel:applicationId:GetChannels' :: Text
applicationId = Text
a} :: GetChannels)
instance Core.AWSRequest GetChannels where
type AWSResponse GetChannels = GetChannelsResponse
request :: (Service -> Service) -> GetChannels -> Request GetChannels
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 GetChannels
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetChannels)))
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 -> ChannelsResponse -> GetChannelsResponse
GetChannelsResponse'
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 GetChannels where
hashWithSalt :: Int -> GetChannels -> Int
hashWithSalt Int
_salt GetChannels' {Text
applicationId :: Text
$sel:applicationId:GetChannels' :: GetChannels -> Text
..} =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId
instance Prelude.NFData GetChannels where
rnf :: GetChannels -> ()
rnf GetChannels' {Text
applicationId :: Text
$sel:applicationId:GetChannels' :: GetChannels -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId
instance Data.ToHeaders GetChannels where
toHeaders :: GetChannels -> 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 GetChannels where
toPath :: GetChannels -> ByteString
toPath GetChannels' {Text
applicationId :: Text
$sel:applicationId:GetChannels' :: GetChannels -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ByteString
"/v1/apps/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId, ByteString
"/channels"]
instance Data.ToQuery GetChannels where
toQuery :: GetChannels -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data GetChannelsResponse = GetChannelsResponse'
{
GetChannelsResponse -> Int
httpStatus :: Prelude.Int,
GetChannelsResponse -> ChannelsResponse
channelsResponse :: ChannelsResponse
}
deriving (GetChannelsResponse -> GetChannelsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetChannelsResponse -> GetChannelsResponse -> Bool
$c/= :: GetChannelsResponse -> GetChannelsResponse -> Bool
== :: GetChannelsResponse -> GetChannelsResponse -> Bool
$c== :: GetChannelsResponse -> GetChannelsResponse -> Bool
Prelude.Eq, ReadPrec [GetChannelsResponse]
ReadPrec GetChannelsResponse
Int -> ReadS GetChannelsResponse
ReadS [GetChannelsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetChannelsResponse]
$creadListPrec :: ReadPrec [GetChannelsResponse]
readPrec :: ReadPrec GetChannelsResponse
$creadPrec :: ReadPrec GetChannelsResponse
readList :: ReadS [GetChannelsResponse]
$creadList :: ReadS [GetChannelsResponse]
readsPrec :: Int -> ReadS GetChannelsResponse
$creadsPrec :: Int -> ReadS GetChannelsResponse
Prelude.Read, Int -> GetChannelsResponse -> ShowS
[GetChannelsResponse] -> ShowS
GetChannelsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetChannelsResponse] -> ShowS
$cshowList :: [GetChannelsResponse] -> ShowS
show :: GetChannelsResponse -> String
$cshow :: GetChannelsResponse -> String
showsPrec :: Int -> GetChannelsResponse -> ShowS
$cshowsPrec :: Int -> GetChannelsResponse -> ShowS
Prelude.Show, forall x. Rep GetChannelsResponse x -> GetChannelsResponse
forall x. GetChannelsResponse -> Rep GetChannelsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetChannelsResponse x -> GetChannelsResponse
$cfrom :: forall x. GetChannelsResponse -> Rep GetChannelsResponse x
Prelude.Generic)
newGetChannelsResponse ::
Prelude.Int ->
ChannelsResponse ->
GetChannelsResponse
newGetChannelsResponse :: Int -> ChannelsResponse -> GetChannelsResponse
newGetChannelsResponse
Int
pHttpStatus_
ChannelsResponse
pChannelsResponse_ =
GetChannelsResponse'
{ $sel:httpStatus:GetChannelsResponse' :: Int
httpStatus = Int
pHttpStatus_,
$sel:channelsResponse:GetChannelsResponse' :: ChannelsResponse
channelsResponse = ChannelsResponse
pChannelsResponse_
}
getChannelsResponse_httpStatus :: Lens.Lens' GetChannelsResponse Prelude.Int
getChannelsResponse_httpStatus :: Lens' GetChannelsResponse Int
getChannelsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetChannelsResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetChannelsResponse' :: GetChannelsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetChannelsResponse
s@GetChannelsResponse' {} Int
a -> GetChannelsResponse
s {$sel:httpStatus:GetChannelsResponse' :: Int
httpStatus = Int
a} :: GetChannelsResponse)
getChannelsResponse_channelsResponse :: Lens.Lens' GetChannelsResponse ChannelsResponse
getChannelsResponse_channelsResponse :: Lens' GetChannelsResponse ChannelsResponse
getChannelsResponse_channelsResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetChannelsResponse' {ChannelsResponse
channelsResponse :: ChannelsResponse
$sel:channelsResponse:GetChannelsResponse' :: GetChannelsResponse -> ChannelsResponse
channelsResponse} -> ChannelsResponse
channelsResponse) (\s :: GetChannelsResponse
s@GetChannelsResponse' {} ChannelsResponse
a -> GetChannelsResponse
s {$sel:channelsResponse:GetChannelsResponse' :: ChannelsResponse
channelsResponse = ChannelsResponse
a} :: GetChannelsResponse)
instance Prelude.NFData GetChannelsResponse where
rnf :: GetChannelsResponse -> ()
rnf GetChannelsResponse' {Int
ChannelsResponse
channelsResponse :: ChannelsResponse
httpStatus :: Int
$sel:channelsResponse:GetChannelsResponse' :: GetChannelsResponse -> ChannelsResponse
$sel:httpStatus:GetChannelsResponse' :: GetChannelsResponse -> 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 ChannelsResponse
channelsResponse