{-# 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.PinpointSmsVoiceV2.SendVoiceMessage
(
SendVoiceMessage (..),
newSendVoiceMessage,
sendVoiceMessage_configurationSetName,
sendVoiceMessage_context,
sendVoiceMessage_dryRun,
sendVoiceMessage_maxPricePerMinute,
sendVoiceMessage_messageBody,
sendVoiceMessage_messageBodyTextType,
sendVoiceMessage_timeToLive,
sendVoiceMessage_voiceId,
sendVoiceMessage_destinationPhoneNumber,
sendVoiceMessage_originationIdentity,
SendVoiceMessageResponse (..),
newSendVoiceMessageResponse,
sendVoiceMessageResponse_messageId,
sendVoiceMessageResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.PinpointSmsVoiceV2.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data SendVoiceMessage = SendVoiceMessage'
{
SendVoiceMessage -> Maybe Text
configurationSetName :: Prelude.Maybe Prelude.Text,
SendVoiceMessage -> Maybe (HashMap Text Text)
context :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
SendVoiceMessage -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
SendVoiceMessage -> Maybe Text
maxPricePerMinute :: Prelude.Maybe Prelude.Text,
SendVoiceMessage -> Maybe Text
messageBody :: Prelude.Maybe Prelude.Text,
SendVoiceMessage -> Maybe VoiceMessageBodyTextType
messageBodyTextType :: Prelude.Maybe VoiceMessageBodyTextType,
SendVoiceMessage -> Maybe Natural
timeToLive :: Prelude.Maybe Prelude.Natural,
SendVoiceMessage -> Maybe VoiceId
voiceId :: Prelude.Maybe VoiceId,
SendVoiceMessage -> Text
destinationPhoneNumber :: Prelude.Text,
SendVoiceMessage -> Text
originationIdentity :: Prelude.Text
}
deriving (SendVoiceMessage -> SendVoiceMessage -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendVoiceMessage -> SendVoiceMessage -> Bool
$c/= :: SendVoiceMessage -> SendVoiceMessage -> Bool
== :: SendVoiceMessage -> SendVoiceMessage -> Bool
$c== :: SendVoiceMessage -> SendVoiceMessage -> Bool
Prelude.Eq, ReadPrec [SendVoiceMessage]
ReadPrec SendVoiceMessage
Int -> ReadS SendVoiceMessage
ReadS [SendVoiceMessage]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SendVoiceMessage]
$creadListPrec :: ReadPrec [SendVoiceMessage]
readPrec :: ReadPrec SendVoiceMessage
$creadPrec :: ReadPrec SendVoiceMessage
readList :: ReadS [SendVoiceMessage]
$creadList :: ReadS [SendVoiceMessage]
readsPrec :: Int -> ReadS SendVoiceMessage
$creadsPrec :: Int -> ReadS SendVoiceMessage
Prelude.Read, Int -> SendVoiceMessage -> ShowS
[SendVoiceMessage] -> ShowS
SendVoiceMessage -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendVoiceMessage] -> ShowS
$cshowList :: [SendVoiceMessage] -> ShowS
show :: SendVoiceMessage -> String
$cshow :: SendVoiceMessage -> String
showsPrec :: Int -> SendVoiceMessage -> ShowS
$cshowsPrec :: Int -> SendVoiceMessage -> ShowS
Prelude.Show, forall x. Rep SendVoiceMessage x -> SendVoiceMessage
forall x. SendVoiceMessage -> Rep SendVoiceMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendVoiceMessage x -> SendVoiceMessage
$cfrom :: forall x. SendVoiceMessage -> Rep SendVoiceMessage x
Prelude.Generic)
newSendVoiceMessage ::
Prelude.Text ->
Prelude.Text ->
SendVoiceMessage
newSendVoiceMessage :: Text -> Text -> SendVoiceMessage
newSendVoiceMessage
Text
pDestinationPhoneNumber_
Text
pOriginationIdentity_ =
SendVoiceMessage'
{ $sel:configurationSetName:SendVoiceMessage' :: Maybe Text
configurationSetName =
forall a. Maybe a
Prelude.Nothing,
$sel:context:SendVoiceMessage' :: Maybe (HashMap Text Text)
context = forall a. Maybe a
Prelude.Nothing,
$sel:dryRun:SendVoiceMessage' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
$sel:maxPricePerMinute:SendVoiceMessage' :: Maybe Text
maxPricePerMinute = forall a. Maybe a
Prelude.Nothing,
$sel:messageBody:SendVoiceMessage' :: Maybe Text
messageBody = forall a. Maybe a
Prelude.Nothing,
$sel:messageBodyTextType:SendVoiceMessage' :: Maybe VoiceMessageBodyTextType
messageBodyTextType = forall a. Maybe a
Prelude.Nothing,
$sel:timeToLive:SendVoiceMessage' :: Maybe Natural
timeToLive = forall a. Maybe a
Prelude.Nothing,
$sel:voiceId:SendVoiceMessage' :: Maybe VoiceId
voiceId = forall a. Maybe a
Prelude.Nothing,
$sel:destinationPhoneNumber:SendVoiceMessage' :: Text
destinationPhoneNumber = Text
pDestinationPhoneNumber_,
$sel:originationIdentity:SendVoiceMessage' :: Text
originationIdentity = Text
pOriginationIdentity_
}
sendVoiceMessage_configurationSetName :: Lens.Lens' SendVoiceMessage (Prelude.Maybe Prelude.Text)
sendVoiceMessage_configurationSetName :: Lens' SendVoiceMessage (Maybe Text)
sendVoiceMessage_configurationSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendVoiceMessage' {Maybe Text
configurationSetName :: Maybe Text
$sel:configurationSetName:SendVoiceMessage' :: SendVoiceMessage -> Maybe Text
configurationSetName} -> Maybe Text
configurationSetName) (\s :: SendVoiceMessage
s@SendVoiceMessage' {} Maybe Text
a -> SendVoiceMessage
s {$sel:configurationSetName:SendVoiceMessage' :: Maybe Text
configurationSetName = Maybe Text
a} :: SendVoiceMessage)
sendVoiceMessage_context :: Lens.Lens' SendVoiceMessage (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
sendVoiceMessage_context :: Lens' SendVoiceMessage (Maybe (HashMap Text Text))
sendVoiceMessage_context = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendVoiceMessage' {Maybe (HashMap Text Text)
context :: Maybe (HashMap Text Text)
$sel:context:SendVoiceMessage' :: SendVoiceMessage -> Maybe (HashMap Text Text)
context} -> Maybe (HashMap Text Text)
context) (\s :: SendVoiceMessage
s@SendVoiceMessage' {} Maybe (HashMap Text Text)
a -> SendVoiceMessage
s {$sel:context:SendVoiceMessage' :: Maybe (HashMap Text Text)
context = Maybe (HashMap Text Text)
a} :: SendVoiceMessage) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
sendVoiceMessage_dryRun :: Lens.Lens' SendVoiceMessage (Prelude.Maybe Prelude.Bool)
sendVoiceMessage_dryRun :: Lens' SendVoiceMessage (Maybe Bool)
sendVoiceMessage_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendVoiceMessage' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:SendVoiceMessage' :: SendVoiceMessage -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: SendVoiceMessage
s@SendVoiceMessage' {} Maybe Bool
a -> SendVoiceMessage
s {$sel:dryRun:SendVoiceMessage' :: Maybe Bool
dryRun = Maybe Bool
a} :: SendVoiceMessage)
sendVoiceMessage_maxPricePerMinute :: Lens.Lens' SendVoiceMessage (Prelude.Maybe Prelude.Text)
sendVoiceMessage_maxPricePerMinute :: Lens' SendVoiceMessage (Maybe Text)
sendVoiceMessage_maxPricePerMinute = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendVoiceMessage' {Maybe Text
maxPricePerMinute :: Maybe Text
$sel:maxPricePerMinute:SendVoiceMessage' :: SendVoiceMessage -> Maybe Text
maxPricePerMinute} -> Maybe Text
maxPricePerMinute) (\s :: SendVoiceMessage
s@SendVoiceMessage' {} Maybe Text
a -> SendVoiceMessage
s {$sel:maxPricePerMinute:SendVoiceMessage' :: Maybe Text
maxPricePerMinute = Maybe Text
a} :: SendVoiceMessage)
sendVoiceMessage_messageBody :: Lens.Lens' SendVoiceMessage (Prelude.Maybe Prelude.Text)
sendVoiceMessage_messageBody :: Lens' SendVoiceMessage (Maybe Text)
sendVoiceMessage_messageBody = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendVoiceMessage' {Maybe Text
messageBody :: Maybe Text
$sel:messageBody:SendVoiceMessage' :: SendVoiceMessage -> Maybe Text
messageBody} -> Maybe Text
messageBody) (\s :: SendVoiceMessage
s@SendVoiceMessage' {} Maybe Text
a -> SendVoiceMessage
s {$sel:messageBody:SendVoiceMessage' :: Maybe Text
messageBody = Maybe Text
a} :: SendVoiceMessage)
sendVoiceMessage_messageBodyTextType :: Lens.Lens' SendVoiceMessage (Prelude.Maybe VoiceMessageBodyTextType)
sendVoiceMessage_messageBodyTextType :: Lens' SendVoiceMessage (Maybe VoiceMessageBodyTextType)
sendVoiceMessage_messageBodyTextType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendVoiceMessage' {Maybe VoiceMessageBodyTextType
messageBodyTextType :: Maybe VoiceMessageBodyTextType
$sel:messageBodyTextType:SendVoiceMessage' :: SendVoiceMessage -> Maybe VoiceMessageBodyTextType
messageBodyTextType} -> Maybe VoiceMessageBodyTextType
messageBodyTextType) (\s :: SendVoiceMessage
s@SendVoiceMessage' {} Maybe VoiceMessageBodyTextType
a -> SendVoiceMessage
s {$sel:messageBodyTextType:SendVoiceMessage' :: Maybe VoiceMessageBodyTextType
messageBodyTextType = Maybe VoiceMessageBodyTextType
a} :: SendVoiceMessage)
sendVoiceMessage_timeToLive :: Lens.Lens' SendVoiceMessage (Prelude.Maybe Prelude.Natural)
sendVoiceMessage_timeToLive :: Lens' SendVoiceMessage (Maybe Natural)
sendVoiceMessage_timeToLive = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendVoiceMessage' {Maybe Natural
timeToLive :: Maybe Natural
$sel:timeToLive:SendVoiceMessage' :: SendVoiceMessage -> Maybe Natural
timeToLive} -> Maybe Natural
timeToLive) (\s :: SendVoiceMessage
s@SendVoiceMessage' {} Maybe Natural
a -> SendVoiceMessage
s {$sel:timeToLive:SendVoiceMessage' :: Maybe Natural
timeToLive = Maybe Natural
a} :: SendVoiceMessage)
sendVoiceMessage_voiceId :: Lens.Lens' SendVoiceMessage (Prelude.Maybe VoiceId)
sendVoiceMessage_voiceId :: Lens' SendVoiceMessage (Maybe VoiceId)
sendVoiceMessage_voiceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendVoiceMessage' {Maybe VoiceId
voiceId :: Maybe VoiceId
$sel:voiceId:SendVoiceMessage' :: SendVoiceMessage -> Maybe VoiceId
voiceId} -> Maybe VoiceId
voiceId) (\s :: SendVoiceMessage
s@SendVoiceMessage' {} Maybe VoiceId
a -> SendVoiceMessage
s {$sel:voiceId:SendVoiceMessage' :: Maybe VoiceId
voiceId = Maybe VoiceId
a} :: SendVoiceMessage)
sendVoiceMessage_destinationPhoneNumber :: Lens.Lens' SendVoiceMessage Prelude.Text
sendVoiceMessage_destinationPhoneNumber :: Lens' SendVoiceMessage Text
sendVoiceMessage_destinationPhoneNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendVoiceMessage' {Text
destinationPhoneNumber :: Text
$sel:destinationPhoneNumber:SendVoiceMessage' :: SendVoiceMessage -> Text
destinationPhoneNumber} -> Text
destinationPhoneNumber) (\s :: SendVoiceMessage
s@SendVoiceMessage' {} Text
a -> SendVoiceMessage
s {$sel:destinationPhoneNumber:SendVoiceMessage' :: Text
destinationPhoneNumber = Text
a} :: SendVoiceMessage)
sendVoiceMessage_originationIdentity :: Lens.Lens' SendVoiceMessage Prelude.Text
sendVoiceMessage_originationIdentity :: Lens' SendVoiceMessage Text
sendVoiceMessage_originationIdentity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendVoiceMessage' {Text
originationIdentity :: Text
$sel:originationIdentity:SendVoiceMessage' :: SendVoiceMessage -> Text
originationIdentity} -> Text
originationIdentity) (\s :: SendVoiceMessage
s@SendVoiceMessage' {} Text
a -> SendVoiceMessage
s {$sel:originationIdentity:SendVoiceMessage' :: Text
originationIdentity = Text
a} :: SendVoiceMessage)
instance Core.AWSRequest SendVoiceMessage where
type
AWSResponse SendVoiceMessage =
SendVoiceMessageResponse
request :: (Service -> Service)
-> SendVoiceMessage -> Request SendVoiceMessage
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 SendVoiceMessage
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse SendVoiceMessage)))
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 ->
Maybe Text -> Int -> SendVoiceMessageResponse
SendVoiceMessageResponse'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"MessageId")
forall (f :: * -> *) a b. Applicative f => 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))
)
instance Prelude.Hashable SendVoiceMessage where
hashWithSalt :: Int -> SendVoiceMessage -> Int
hashWithSalt Int
_salt SendVoiceMessage' {Maybe Bool
Maybe Natural
Maybe Text
Maybe (HashMap Text Text)
Maybe VoiceId
Maybe VoiceMessageBodyTextType
Text
originationIdentity :: Text
destinationPhoneNumber :: Text
voiceId :: Maybe VoiceId
timeToLive :: Maybe Natural
messageBodyTextType :: Maybe VoiceMessageBodyTextType
messageBody :: Maybe Text
maxPricePerMinute :: Maybe Text
dryRun :: Maybe Bool
context :: Maybe (HashMap Text Text)
configurationSetName :: Maybe Text
$sel:originationIdentity:SendVoiceMessage' :: SendVoiceMessage -> Text
$sel:destinationPhoneNumber:SendVoiceMessage' :: SendVoiceMessage -> Text
$sel:voiceId:SendVoiceMessage' :: SendVoiceMessage -> Maybe VoiceId
$sel:timeToLive:SendVoiceMessage' :: SendVoiceMessage -> Maybe Natural
$sel:messageBodyTextType:SendVoiceMessage' :: SendVoiceMessage -> Maybe VoiceMessageBodyTextType
$sel:messageBody:SendVoiceMessage' :: SendVoiceMessage -> Maybe Text
$sel:maxPricePerMinute:SendVoiceMessage' :: SendVoiceMessage -> Maybe Text
$sel:dryRun:SendVoiceMessage' :: SendVoiceMessage -> Maybe Bool
$sel:context:SendVoiceMessage' :: SendVoiceMessage -> Maybe (HashMap Text Text)
$sel:configurationSetName:SendVoiceMessage' :: SendVoiceMessage -> Maybe Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
configurationSetName
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
context
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
maxPricePerMinute
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
messageBody
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VoiceMessageBodyTextType
messageBodyTextType
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
timeToLive
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VoiceId
voiceId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
destinationPhoneNumber
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
originationIdentity
instance Prelude.NFData SendVoiceMessage where
rnf :: SendVoiceMessage -> ()
rnf SendVoiceMessage' {Maybe Bool
Maybe Natural
Maybe Text
Maybe (HashMap Text Text)
Maybe VoiceId
Maybe VoiceMessageBodyTextType
Text
originationIdentity :: Text
destinationPhoneNumber :: Text
voiceId :: Maybe VoiceId
timeToLive :: Maybe Natural
messageBodyTextType :: Maybe VoiceMessageBodyTextType
messageBody :: Maybe Text
maxPricePerMinute :: Maybe Text
dryRun :: Maybe Bool
context :: Maybe (HashMap Text Text)
configurationSetName :: Maybe Text
$sel:originationIdentity:SendVoiceMessage' :: SendVoiceMessage -> Text
$sel:destinationPhoneNumber:SendVoiceMessage' :: SendVoiceMessage -> Text
$sel:voiceId:SendVoiceMessage' :: SendVoiceMessage -> Maybe VoiceId
$sel:timeToLive:SendVoiceMessage' :: SendVoiceMessage -> Maybe Natural
$sel:messageBodyTextType:SendVoiceMessage' :: SendVoiceMessage -> Maybe VoiceMessageBodyTextType
$sel:messageBody:SendVoiceMessage' :: SendVoiceMessage -> Maybe Text
$sel:maxPricePerMinute:SendVoiceMessage' :: SendVoiceMessage -> Maybe Text
$sel:dryRun:SendVoiceMessage' :: SendVoiceMessage -> Maybe Bool
$sel:context:SendVoiceMessage' :: SendVoiceMessage -> Maybe (HashMap Text Text)
$sel:configurationSetName:SendVoiceMessage' :: SendVoiceMessage -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
configurationSetName
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
context
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
maxPricePerMinute
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
messageBody
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VoiceMessageBodyTextType
messageBodyTextType
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
timeToLive
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VoiceId
voiceId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
destinationPhoneNumber
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
originationIdentity
instance Data.ToHeaders SendVoiceMessage where
toHeaders :: SendVoiceMessage -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"X-Amz-Target"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"PinpointSMSVoiceV2.SendVoiceMessage" ::
Prelude.ByteString
),
HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
Prelude.ByteString
)
]
)
instance Data.ToJSON SendVoiceMessage where
toJSON :: SendVoiceMessage -> Value
toJSON SendVoiceMessage' {Maybe Bool
Maybe Natural
Maybe Text
Maybe (HashMap Text Text)
Maybe VoiceId
Maybe VoiceMessageBodyTextType
Text
originationIdentity :: Text
destinationPhoneNumber :: Text
voiceId :: Maybe VoiceId
timeToLive :: Maybe Natural
messageBodyTextType :: Maybe VoiceMessageBodyTextType
messageBody :: Maybe Text
maxPricePerMinute :: Maybe Text
dryRun :: Maybe Bool
context :: Maybe (HashMap Text Text)
configurationSetName :: Maybe Text
$sel:originationIdentity:SendVoiceMessage' :: SendVoiceMessage -> Text
$sel:destinationPhoneNumber:SendVoiceMessage' :: SendVoiceMessage -> Text
$sel:voiceId:SendVoiceMessage' :: SendVoiceMessage -> Maybe VoiceId
$sel:timeToLive:SendVoiceMessage' :: SendVoiceMessage -> Maybe Natural
$sel:messageBodyTextType:SendVoiceMessage' :: SendVoiceMessage -> Maybe VoiceMessageBodyTextType
$sel:messageBody:SendVoiceMessage' :: SendVoiceMessage -> Maybe Text
$sel:maxPricePerMinute:SendVoiceMessage' :: SendVoiceMessage -> Maybe Text
$sel:dryRun:SendVoiceMessage' :: SendVoiceMessage -> Maybe Bool
$sel:context:SendVoiceMessage' :: SendVoiceMessage -> Maybe (HashMap Text Text)
$sel:configurationSetName:SendVoiceMessage' :: SendVoiceMessage -> Maybe Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"ConfigurationSetName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
configurationSetName,
(Key
"Context" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
context,
(Key
"DryRun" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
dryRun,
(Key
"MaxPricePerMinute" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
maxPricePerMinute,
(Key
"MessageBody" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
messageBody,
(Key
"MessageBodyTextType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe VoiceMessageBodyTextType
messageBodyTextType,
(Key
"TimeToLive" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
timeToLive,
(Key
"VoiceId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe VoiceId
voiceId,
forall a. a -> Maybe a
Prelude.Just
( Key
"DestinationPhoneNumber"
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
destinationPhoneNumber
),
forall a. a -> Maybe a
Prelude.Just
(Key
"OriginationIdentity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
originationIdentity)
]
)
instance Data.ToPath SendVoiceMessage where
toPath :: SendVoiceMessage -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery SendVoiceMessage where
toQuery :: SendVoiceMessage -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data SendVoiceMessageResponse = SendVoiceMessageResponse'
{
SendVoiceMessageResponse -> Maybe Text
messageId :: Prelude.Maybe Prelude.Text,
SendVoiceMessageResponse -> Int
httpStatus :: Prelude.Int
}
deriving (SendVoiceMessageResponse -> SendVoiceMessageResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendVoiceMessageResponse -> SendVoiceMessageResponse -> Bool
$c/= :: SendVoiceMessageResponse -> SendVoiceMessageResponse -> Bool
== :: SendVoiceMessageResponse -> SendVoiceMessageResponse -> Bool
$c== :: SendVoiceMessageResponse -> SendVoiceMessageResponse -> Bool
Prelude.Eq, ReadPrec [SendVoiceMessageResponse]
ReadPrec SendVoiceMessageResponse
Int -> ReadS SendVoiceMessageResponse
ReadS [SendVoiceMessageResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SendVoiceMessageResponse]
$creadListPrec :: ReadPrec [SendVoiceMessageResponse]
readPrec :: ReadPrec SendVoiceMessageResponse
$creadPrec :: ReadPrec SendVoiceMessageResponse
readList :: ReadS [SendVoiceMessageResponse]
$creadList :: ReadS [SendVoiceMessageResponse]
readsPrec :: Int -> ReadS SendVoiceMessageResponse
$creadsPrec :: Int -> ReadS SendVoiceMessageResponse
Prelude.Read, Int -> SendVoiceMessageResponse -> ShowS
[SendVoiceMessageResponse] -> ShowS
SendVoiceMessageResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendVoiceMessageResponse] -> ShowS
$cshowList :: [SendVoiceMessageResponse] -> ShowS
show :: SendVoiceMessageResponse -> String
$cshow :: SendVoiceMessageResponse -> String
showsPrec :: Int -> SendVoiceMessageResponse -> ShowS
$cshowsPrec :: Int -> SendVoiceMessageResponse -> ShowS
Prelude.Show, forall x.
Rep SendVoiceMessageResponse x -> SendVoiceMessageResponse
forall x.
SendVoiceMessageResponse -> Rep SendVoiceMessageResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SendVoiceMessageResponse x -> SendVoiceMessageResponse
$cfrom :: forall x.
SendVoiceMessageResponse -> Rep SendVoiceMessageResponse x
Prelude.Generic)
newSendVoiceMessageResponse ::
Prelude.Int ->
SendVoiceMessageResponse
newSendVoiceMessageResponse :: Int -> SendVoiceMessageResponse
newSendVoiceMessageResponse Int
pHttpStatus_ =
SendVoiceMessageResponse'
{ $sel:messageId:SendVoiceMessageResponse' :: Maybe Text
messageId =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:SendVoiceMessageResponse' :: Int
httpStatus = Int
pHttpStatus_
}
sendVoiceMessageResponse_messageId :: Lens.Lens' SendVoiceMessageResponse (Prelude.Maybe Prelude.Text)
sendVoiceMessageResponse_messageId :: Lens' SendVoiceMessageResponse (Maybe Text)
sendVoiceMessageResponse_messageId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendVoiceMessageResponse' {Maybe Text
messageId :: Maybe Text
$sel:messageId:SendVoiceMessageResponse' :: SendVoiceMessageResponse -> Maybe Text
messageId} -> Maybe Text
messageId) (\s :: SendVoiceMessageResponse
s@SendVoiceMessageResponse' {} Maybe Text
a -> SendVoiceMessageResponse
s {$sel:messageId:SendVoiceMessageResponse' :: Maybe Text
messageId = Maybe Text
a} :: SendVoiceMessageResponse)
sendVoiceMessageResponse_httpStatus :: Lens.Lens' SendVoiceMessageResponse Prelude.Int
sendVoiceMessageResponse_httpStatus :: Lens' SendVoiceMessageResponse Int
sendVoiceMessageResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendVoiceMessageResponse' {Int
httpStatus :: Int
$sel:httpStatus:SendVoiceMessageResponse' :: SendVoiceMessageResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: SendVoiceMessageResponse
s@SendVoiceMessageResponse' {} Int
a -> SendVoiceMessageResponse
s {$sel:httpStatus:SendVoiceMessageResponse' :: Int
httpStatus = Int
a} :: SendVoiceMessageResponse)
instance Prelude.NFData SendVoiceMessageResponse where
rnf :: SendVoiceMessageResponse -> ()
rnf SendVoiceMessageResponse' {Int
Maybe Text
httpStatus :: Int
messageId :: Maybe Text
$sel:httpStatus:SendVoiceMessageResponse' :: SendVoiceMessageResponse -> Int
$sel:messageId:SendVoiceMessageResponse' :: SendVoiceMessageResponse -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
messageId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus