{-# 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.GetCampaign
(
GetCampaign (..),
newGetCampaign,
getCampaign_campaignId,
getCampaign_applicationId,
GetCampaignResponse (..),
newGetCampaignResponse,
getCampaignResponse_httpStatus,
getCampaignResponse_campaignResponse,
)
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 GetCampaign = GetCampaign'
{
GetCampaign -> Text
campaignId :: Prelude.Text,
GetCampaign -> Text
applicationId :: Prelude.Text
}
deriving (GetCampaign -> GetCampaign -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCampaign -> GetCampaign -> Bool
$c/= :: GetCampaign -> GetCampaign -> Bool
== :: GetCampaign -> GetCampaign -> Bool
$c== :: GetCampaign -> GetCampaign -> Bool
Prelude.Eq, ReadPrec [GetCampaign]
ReadPrec GetCampaign
Int -> ReadS GetCampaign
ReadS [GetCampaign]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCampaign]
$creadListPrec :: ReadPrec [GetCampaign]
readPrec :: ReadPrec GetCampaign
$creadPrec :: ReadPrec GetCampaign
readList :: ReadS [GetCampaign]
$creadList :: ReadS [GetCampaign]
readsPrec :: Int -> ReadS GetCampaign
$creadsPrec :: Int -> ReadS GetCampaign
Prelude.Read, Int -> GetCampaign -> ShowS
[GetCampaign] -> ShowS
GetCampaign -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCampaign] -> ShowS
$cshowList :: [GetCampaign] -> ShowS
show :: GetCampaign -> String
$cshow :: GetCampaign -> String
showsPrec :: Int -> GetCampaign -> ShowS
$cshowsPrec :: Int -> GetCampaign -> ShowS
Prelude.Show, forall x. Rep GetCampaign x -> GetCampaign
forall x. GetCampaign -> Rep GetCampaign x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCampaign x -> GetCampaign
$cfrom :: forall x. GetCampaign -> Rep GetCampaign x
Prelude.Generic)
newGetCampaign ::
Prelude.Text ->
Prelude.Text ->
GetCampaign
newGetCampaign :: Text -> Text -> GetCampaign
newGetCampaign Text
pCampaignId_ Text
pApplicationId_ =
GetCampaign'
{ $sel:campaignId:GetCampaign' :: Text
campaignId = Text
pCampaignId_,
$sel:applicationId:GetCampaign' :: Text
applicationId = Text
pApplicationId_
}
getCampaign_campaignId :: Lens.Lens' GetCampaign Prelude.Text
getCampaign_campaignId :: Lens' GetCampaign Text
getCampaign_campaignId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCampaign' {Text
campaignId :: Text
$sel:campaignId:GetCampaign' :: GetCampaign -> Text
campaignId} -> Text
campaignId) (\s :: GetCampaign
s@GetCampaign' {} Text
a -> GetCampaign
s {$sel:campaignId:GetCampaign' :: Text
campaignId = Text
a} :: GetCampaign)
getCampaign_applicationId :: Lens.Lens' GetCampaign Prelude.Text
getCampaign_applicationId :: Lens' GetCampaign Text
getCampaign_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCampaign' {Text
applicationId :: Text
$sel:applicationId:GetCampaign' :: GetCampaign -> Text
applicationId} -> Text
applicationId) (\s :: GetCampaign
s@GetCampaign' {} Text
a -> GetCampaign
s {$sel:applicationId:GetCampaign' :: Text
applicationId = Text
a} :: GetCampaign)
instance Core.AWSRequest GetCampaign where
type AWSResponse GetCampaign = GetCampaignResponse
request :: (Service -> Service) -> GetCampaign -> Request GetCampaign
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 GetCampaign
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetCampaign)))
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 -> CampaignResponse -> GetCampaignResponse
GetCampaignResponse'
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 GetCampaign where
hashWithSalt :: Int -> GetCampaign -> Int
hashWithSalt Int
_salt GetCampaign' {Text
applicationId :: Text
campaignId :: Text
$sel:applicationId:GetCampaign' :: GetCampaign -> Text
$sel:campaignId:GetCampaign' :: GetCampaign -> Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
campaignId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId
instance Prelude.NFData GetCampaign where
rnf :: GetCampaign -> ()
rnf GetCampaign' {Text
applicationId :: Text
campaignId :: Text
$sel:applicationId:GetCampaign' :: GetCampaign -> Text
$sel:campaignId:GetCampaign' :: GetCampaign -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
campaignId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId
instance Data.ToHeaders GetCampaign where
toHeaders :: GetCampaign -> 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 GetCampaign where
toPath :: GetCampaign -> ByteString
toPath GetCampaign' {Text
applicationId :: Text
campaignId :: Text
$sel:applicationId:GetCampaign' :: GetCampaign -> Text
$sel:campaignId:GetCampaign' :: GetCampaign -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"/v1/apps/",
forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
ByteString
"/campaigns/",
forall a. ToByteString a => a -> ByteString
Data.toBS Text
campaignId
]
instance Data.ToQuery GetCampaign where
toQuery :: GetCampaign -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data GetCampaignResponse = GetCampaignResponse'
{
GetCampaignResponse -> Int
httpStatus :: Prelude.Int,
GetCampaignResponse -> CampaignResponse
campaignResponse :: CampaignResponse
}
deriving (GetCampaignResponse -> GetCampaignResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCampaignResponse -> GetCampaignResponse -> Bool
$c/= :: GetCampaignResponse -> GetCampaignResponse -> Bool
== :: GetCampaignResponse -> GetCampaignResponse -> Bool
$c== :: GetCampaignResponse -> GetCampaignResponse -> Bool
Prelude.Eq, ReadPrec [GetCampaignResponse]
ReadPrec GetCampaignResponse
Int -> ReadS GetCampaignResponse
ReadS [GetCampaignResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCampaignResponse]
$creadListPrec :: ReadPrec [GetCampaignResponse]
readPrec :: ReadPrec GetCampaignResponse
$creadPrec :: ReadPrec GetCampaignResponse
readList :: ReadS [GetCampaignResponse]
$creadList :: ReadS [GetCampaignResponse]
readsPrec :: Int -> ReadS GetCampaignResponse
$creadsPrec :: Int -> ReadS GetCampaignResponse
Prelude.Read, Int -> GetCampaignResponse -> ShowS
[GetCampaignResponse] -> ShowS
GetCampaignResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCampaignResponse] -> ShowS
$cshowList :: [GetCampaignResponse] -> ShowS
show :: GetCampaignResponse -> String
$cshow :: GetCampaignResponse -> String
showsPrec :: Int -> GetCampaignResponse -> ShowS
$cshowsPrec :: Int -> GetCampaignResponse -> ShowS
Prelude.Show, forall x. Rep GetCampaignResponse x -> GetCampaignResponse
forall x. GetCampaignResponse -> Rep GetCampaignResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCampaignResponse x -> GetCampaignResponse
$cfrom :: forall x. GetCampaignResponse -> Rep GetCampaignResponse x
Prelude.Generic)
newGetCampaignResponse ::
Prelude.Int ->
CampaignResponse ->
GetCampaignResponse
newGetCampaignResponse :: Int -> CampaignResponse -> GetCampaignResponse
newGetCampaignResponse
Int
pHttpStatus_
CampaignResponse
pCampaignResponse_ =
GetCampaignResponse'
{ $sel:httpStatus:GetCampaignResponse' :: Int
httpStatus = Int
pHttpStatus_,
$sel:campaignResponse:GetCampaignResponse' :: CampaignResponse
campaignResponse = CampaignResponse
pCampaignResponse_
}
getCampaignResponse_httpStatus :: Lens.Lens' GetCampaignResponse Prelude.Int
getCampaignResponse_httpStatus :: Lens' GetCampaignResponse Int
getCampaignResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCampaignResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetCampaignResponse' :: GetCampaignResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetCampaignResponse
s@GetCampaignResponse' {} Int
a -> GetCampaignResponse
s {$sel:httpStatus:GetCampaignResponse' :: Int
httpStatus = Int
a} :: GetCampaignResponse)
getCampaignResponse_campaignResponse :: Lens.Lens' GetCampaignResponse CampaignResponse
getCampaignResponse_campaignResponse :: Lens' GetCampaignResponse CampaignResponse
getCampaignResponse_campaignResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCampaignResponse' {CampaignResponse
campaignResponse :: CampaignResponse
$sel:campaignResponse:GetCampaignResponse' :: GetCampaignResponse -> CampaignResponse
campaignResponse} -> CampaignResponse
campaignResponse) (\s :: GetCampaignResponse
s@GetCampaignResponse' {} CampaignResponse
a -> GetCampaignResponse
s {$sel:campaignResponse:GetCampaignResponse' :: CampaignResponse
campaignResponse = CampaignResponse
a} :: GetCampaignResponse)
instance Prelude.NFData GetCampaignResponse where
rnf :: GetCampaignResponse -> ()
rnf GetCampaignResponse' {Int
CampaignResponse
campaignResponse :: CampaignResponse
httpStatus :: Int
$sel:campaignResponse:GetCampaignResponse' :: GetCampaignResponse -> CampaignResponse
$sel:httpStatus:GetCampaignResponse' :: GetCampaignResponse -> 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 CampaignResponse
campaignResponse