{-# 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.SendOTPMessage
(
SendOTPMessage (..),
newSendOTPMessage,
sendOTPMessage_applicationId,
sendOTPMessage_sendOTPMessageRequestParameters,
SendOTPMessageResponse (..),
newSendOTPMessageResponse,
sendOTPMessageResponse_httpStatus,
sendOTPMessageResponse_messageResponse,
)
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 SendOTPMessage = SendOTPMessage'
{
SendOTPMessage -> Text
applicationId :: Prelude.Text,
SendOTPMessage -> SendOTPMessageRequestParameters
sendOTPMessageRequestParameters :: SendOTPMessageRequestParameters
}
deriving (SendOTPMessage -> SendOTPMessage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendOTPMessage -> SendOTPMessage -> Bool
$c/= :: SendOTPMessage -> SendOTPMessage -> Bool
== :: SendOTPMessage -> SendOTPMessage -> Bool
$c== :: SendOTPMessage -> SendOTPMessage -> Bool
Prelude.Eq, ReadPrec [SendOTPMessage]
ReadPrec SendOTPMessage
Int -> ReadS SendOTPMessage
ReadS [SendOTPMessage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SendOTPMessage]
$creadListPrec :: ReadPrec [SendOTPMessage]
readPrec :: ReadPrec SendOTPMessage
$creadPrec :: ReadPrec SendOTPMessage
readList :: ReadS [SendOTPMessage]
$creadList :: ReadS [SendOTPMessage]
readsPrec :: Int -> ReadS SendOTPMessage
$creadsPrec :: Int -> ReadS SendOTPMessage
Prelude.Read, Int -> SendOTPMessage -> ShowS
[SendOTPMessage] -> ShowS
SendOTPMessage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendOTPMessage] -> ShowS
$cshowList :: [SendOTPMessage] -> ShowS
show :: SendOTPMessage -> String
$cshow :: SendOTPMessage -> String
showsPrec :: Int -> SendOTPMessage -> ShowS
$cshowsPrec :: Int -> SendOTPMessage -> ShowS
Prelude.Show, forall x. Rep SendOTPMessage x -> SendOTPMessage
forall x. SendOTPMessage -> Rep SendOTPMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendOTPMessage x -> SendOTPMessage
$cfrom :: forall x. SendOTPMessage -> Rep SendOTPMessage x
Prelude.Generic)
newSendOTPMessage ::
Prelude.Text ->
SendOTPMessageRequestParameters ->
SendOTPMessage
newSendOTPMessage :: Text -> SendOTPMessageRequestParameters -> SendOTPMessage
newSendOTPMessage
Text
pApplicationId_
SendOTPMessageRequestParameters
pSendOTPMessageRequestParameters_ =
SendOTPMessage'
{ $sel:applicationId:SendOTPMessage' :: Text
applicationId = Text
pApplicationId_,
$sel:sendOTPMessageRequestParameters:SendOTPMessage' :: SendOTPMessageRequestParameters
sendOTPMessageRequestParameters =
SendOTPMessageRequestParameters
pSendOTPMessageRequestParameters_
}
sendOTPMessage_applicationId :: Lens.Lens' SendOTPMessage Prelude.Text
sendOTPMessage_applicationId :: Lens' SendOTPMessage Text
sendOTPMessage_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendOTPMessage' {Text
applicationId :: Text
$sel:applicationId:SendOTPMessage' :: SendOTPMessage -> Text
applicationId} -> Text
applicationId) (\s :: SendOTPMessage
s@SendOTPMessage' {} Text
a -> SendOTPMessage
s {$sel:applicationId:SendOTPMessage' :: Text
applicationId = Text
a} :: SendOTPMessage)
sendOTPMessage_sendOTPMessageRequestParameters :: Lens.Lens' SendOTPMessage SendOTPMessageRequestParameters
sendOTPMessage_sendOTPMessageRequestParameters :: Lens' SendOTPMessage SendOTPMessageRequestParameters
sendOTPMessage_sendOTPMessageRequestParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendOTPMessage' {SendOTPMessageRequestParameters
sendOTPMessageRequestParameters :: SendOTPMessageRequestParameters
$sel:sendOTPMessageRequestParameters:SendOTPMessage' :: SendOTPMessage -> SendOTPMessageRequestParameters
sendOTPMessageRequestParameters} -> SendOTPMessageRequestParameters
sendOTPMessageRequestParameters) (\s :: SendOTPMessage
s@SendOTPMessage' {} SendOTPMessageRequestParameters
a -> SendOTPMessage
s {$sel:sendOTPMessageRequestParameters:SendOTPMessage' :: SendOTPMessageRequestParameters
sendOTPMessageRequestParameters = SendOTPMessageRequestParameters
a} :: SendOTPMessage)
instance Core.AWSRequest SendOTPMessage where
type
AWSResponse SendOTPMessage =
SendOTPMessageResponse
request :: (Service -> Service) -> SendOTPMessage -> Request SendOTPMessage
request Service -> Service
overrides =
forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy SendOTPMessage
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse SendOTPMessage)))
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 -> MessageResponse -> SendOTPMessageResponse
SendOTPMessageResponse'
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 SendOTPMessage where
hashWithSalt :: Int -> SendOTPMessage -> Int
hashWithSalt Int
_salt SendOTPMessage' {Text
SendOTPMessageRequestParameters
sendOTPMessageRequestParameters :: SendOTPMessageRequestParameters
applicationId :: Text
$sel:sendOTPMessageRequestParameters:SendOTPMessage' :: SendOTPMessage -> SendOTPMessageRequestParameters
$sel:applicationId:SendOTPMessage' :: SendOTPMessage -> Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` SendOTPMessageRequestParameters
sendOTPMessageRequestParameters
instance Prelude.NFData SendOTPMessage where
rnf :: SendOTPMessage -> ()
rnf SendOTPMessage' {Text
SendOTPMessageRequestParameters
sendOTPMessageRequestParameters :: SendOTPMessageRequestParameters
applicationId :: Text
$sel:sendOTPMessageRequestParameters:SendOTPMessage' :: SendOTPMessage -> SendOTPMessageRequestParameters
$sel:applicationId:SendOTPMessage' :: SendOTPMessage -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf SendOTPMessageRequestParameters
sendOTPMessageRequestParameters
instance Data.ToHeaders SendOTPMessage where
toHeaders :: SendOTPMessage -> 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.ToJSON SendOTPMessage where
toJSON :: SendOTPMessage -> Value
toJSON SendOTPMessage' {Text
SendOTPMessageRequestParameters
sendOTPMessageRequestParameters :: SendOTPMessageRequestParameters
applicationId :: Text
$sel:sendOTPMessageRequestParameters:SendOTPMessage' :: SendOTPMessage -> SendOTPMessageRequestParameters
$sel:applicationId:SendOTPMessage' :: SendOTPMessage -> Text
..} =
forall a. ToJSON a => a -> Value
Data.toJSON SendOTPMessageRequestParameters
sendOTPMessageRequestParameters
instance Data.ToPath SendOTPMessage where
toPath :: SendOTPMessage -> ByteString
toPath SendOTPMessage' {Text
SendOTPMessageRequestParameters
sendOTPMessageRequestParameters :: SendOTPMessageRequestParameters
applicationId :: Text
$sel:sendOTPMessageRequestParameters:SendOTPMessage' :: SendOTPMessage -> SendOTPMessageRequestParameters
$sel:applicationId:SendOTPMessage' :: SendOTPMessage -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ByteString
"/v1/apps/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId, ByteString
"/otp"]
instance Data.ToQuery SendOTPMessage where
toQuery :: SendOTPMessage -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data SendOTPMessageResponse = SendOTPMessageResponse'
{
SendOTPMessageResponse -> Int
httpStatus :: Prelude.Int,
SendOTPMessageResponse -> MessageResponse
messageResponse :: MessageResponse
}
deriving (SendOTPMessageResponse -> SendOTPMessageResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendOTPMessageResponse -> SendOTPMessageResponse -> Bool
$c/= :: SendOTPMessageResponse -> SendOTPMessageResponse -> Bool
== :: SendOTPMessageResponse -> SendOTPMessageResponse -> Bool
$c== :: SendOTPMessageResponse -> SendOTPMessageResponse -> Bool
Prelude.Eq, ReadPrec [SendOTPMessageResponse]
ReadPrec SendOTPMessageResponse
Int -> ReadS SendOTPMessageResponse
ReadS [SendOTPMessageResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SendOTPMessageResponse]
$creadListPrec :: ReadPrec [SendOTPMessageResponse]
readPrec :: ReadPrec SendOTPMessageResponse
$creadPrec :: ReadPrec SendOTPMessageResponse
readList :: ReadS [SendOTPMessageResponse]
$creadList :: ReadS [SendOTPMessageResponse]
readsPrec :: Int -> ReadS SendOTPMessageResponse
$creadsPrec :: Int -> ReadS SendOTPMessageResponse
Prelude.Read, Int -> SendOTPMessageResponse -> ShowS
[SendOTPMessageResponse] -> ShowS
SendOTPMessageResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendOTPMessageResponse] -> ShowS
$cshowList :: [SendOTPMessageResponse] -> ShowS
show :: SendOTPMessageResponse -> String
$cshow :: SendOTPMessageResponse -> String
showsPrec :: Int -> SendOTPMessageResponse -> ShowS
$cshowsPrec :: Int -> SendOTPMessageResponse -> ShowS
Prelude.Show, forall x. Rep SendOTPMessageResponse x -> SendOTPMessageResponse
forall x. SendOTPMessageResponse -> Rep SendOTPMessageResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendOTPMessageResponse x -> SendOTPMessageResponse
$cfrom :: forall x. SendOTPMessageResponse -> Rep SendOTPMessageResponse x
Prelude.Generic)
newSendOTPMessageResponse ::
Prelude.Int ->
MessageResponse ->
SendOTPMessageResponse
newSendOTPMessageResponse :: Int -> MessageResponse -> SendOTPMessageResponse
newSendOTPMessageResponse
Int
pHttpStatus_
MessageResponse
pMessageResponse_ =
SendOTPMessageResponse'
{ $sel:httpStatus:SendOTPMessageResponse' :: Int
httpStatus = Int
pHttpStatus_,
$sel:messageResponse:SendOTPMessageResponse' :: MessageResponse
messageResponse = MessageResponse
pMessageResponse_
}
sendOTPMessageResponse_httpStatus :: Lens.Lens' SendOTPMessageResponse Prelude.Int
sendOTPMessageResponse_httpStatus :: Lens' SendOTPMessageResponse Int
sendOTPMessageResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendOTPMessageResponse' {Int
httpStatus :: Int
$sel:httpStatus:SendOTPMessageResponse' :: SendOTPMessageResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: SendOTPMessageResponse
s@SendOTPMessageResponse' {} Int
a -> SendOTPMessageResponse
s {$sel:httpStatus:SendOTPMessageResponse' :: Int
httpStatus = Int
a} :: SendOTPMessageResponse)
sendOTPMessageResponse_messageResponse :: Lens.Lens' SendOTPMessageResponse MessageResponse
sendOTPMessageResponse_messageResponse :: Lens' SendOTPMessageResponse MessageResponse
sendOTPMessageResponse_messageResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendOTPMessageResponse' {MessageResponse
messageResponse :: MessageResponse
$sel:messageResponse:SendOTPMessageResponse' :: SendOTPMessageResponse -> MessageResponse
messageResponse} -> MessageResponse
messageResponse) (\s :: SendOTPMessageResponse
s@SendOTPMessageResponse' {} MessageResponse
a -> SendOTPMessageResponse
s {$sel:messageResponse:SendOTPMessageResponse' :: MessageResponse
messageResponse = MessageResponse
a} :: SendOTPMessageResponse)
instance Prelude.NFData SendOTPMessageResponse where
rnf :: SendOTPMessageResponse -> ()
rnf SendOTPMessageResponse' {Int
MessageResponse
messageResponse :: MessageResponse
httpStatus :: Int
$sel:messageResponse:SendOTPMessageResponse' :: SendOTPMessageResponse -> MessageResponse
$sel:httpStatus:SendOTPMessageResponse' :: SendOTPMessageResponse -> 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 MessageResponse
messageResponse