{-# 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.Firehose.PutRecord
(
PutRecord (..),
newPutRecord,
putRecord_deliveryStreamName,
putRecord_record,
PutRecordResponse (..),
newPutRecordResponse,
putRecordResponse_encrypted,
putRecordResponse_httpStatus,
putRecordResponse_recordId,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Firehose.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data PutRecord = PutRecord'
{
PutRecord -> Text
deliveryStreamName :: Prelude.Text,
PutRecord -> Record
record :: Record
}
deriving (PutRecord -> PutRecord -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutRecord -> PutRecord -> Bool
$c/= :: PutRecord -> PutRecord -> Bool
== :: PutRecord -> PutRecord -> Bool
$c== :: PutRecord -> PutRecord -> Bool
Prelude.Eq, ReadPrec [PutRecord]
ReadPrec PutRecord
Int -> ReadS PutRecord
ReadS [PutRecord]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutRecord]
$creadListPrec :: ReadPrec [PutRecord]
readPrec :: ReadPrec PutRecord
$creadPrec :: ReadPrec PutRecord
readList :: ReadS [PutRecord]
$creadList :: ReadS [PutRecord]
readsPrec :: Int -> ReadS PutRecord
$creadsPrec :: Int -> ReadS PutRecord
Prelude.Read, Int -> PutRecord -> ShowS
[PutRecord] -> ShowS
PutRecord -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutRecord] -> ShowS
$cshowList :: [PutRecord] -> ShowS
show :: PutRecord -> String
$cshow :: PutRecord -> String
showsPrec :: Int -> PutRecord -> ShowS
$cshowsPrec :: Int -> PutRecord -> ShowS
Prelude.Show, forall x. Rep PutRecord x -> PutRecord
forall x. PutRecord -> Rep PutRecord x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutRecord x -> PutRecord
$cfrom :: forall x. PutRecord -> Rep PutRecord x
Prelude.Generic)
newPutRecord ::
Prelude.Text ->
Record ->
PutRecord
newPutRecord :: Text -> Record -> PutRecord
newPutRecord Text
pDeliveryStreamName_ Record
pRecord_ =
PutRecord'
{ $sel:deliveryStreamName:PutRecord' :: Text
deliveryStreamName =
Text
pDeliveryStreamName_,
$sel:record:PutRecord' :: Record
record = Record
pRecord_
}
putRecord_deliveryStreamName :: Lens.Lens' PutRecord Prelude.Text
putRecord_deliveryStreamName :: Lens' PutRecord Text
putRecord_deliveryStreamName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutRecord' {Text
deliveryStreamName :: Text
$sel:deliveryStreamName:PutRecord' :: PutRecord -> Text
deliveryStreamName} -> Text
deliveryStreamName) (\s :: PutRecord
s@PutRecord' {} Text
a -> PutRecord
s {$sel:deliveryStreamName:PutRecord' :: Text
deliveryStreamName = Text
a} :: PutRecord)
putRecord_record :: Lens.Lens' PutRecord Record
putRecord_record :: Lens' PutRecord Record
putRecord_record = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutRecord' {Record
record :: Record
$sel:record:PutRecord' :: PutRecord -> Record
record} -> Record
record) (\s :: PutRecord
s@PutRecord' {} Record
a -> PutRecord
s {$sel:record:PutRecord' :: Record
record = Record
a} :: PutRecord)
instance Core.AWSRequest PutRecord where
type AWSResponse PutRecord = PutRecordResponse
request :: (Service -> Service) -> PutRecord -> Request PutRecord
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 PutRecord
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse PutRecord)))
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 Bool -> Int -> Text -> PutRecordResponse
PutRecordResponse'
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
"Encrypted")
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))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"RecordId")
)
instance Prelude.Hashable PutRecord where
hashWithSalt :: Int -> PutRecord -> Int
hashWithSalt Int
_salt PutRecord' {Text
Record
record :: Record
deliveryStreamName :: Text
$sel:record:PutRecord' :: PutRecord -> Record
$sel:deliveryStreamName:PutRecord' :: PutRecord -> Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
deliveryStreamName
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Record
record
instance Prelude.NFData PutRecord where
rnf :: PutRecord -> ()
rnf PutRecord' {Text
Record
record :: Record
deliveryStreamName :: Text
$sel:record:PutRecord' :: PutRecord -> Record
$sel:deliveryStreamName:PutRecord' :: PutRecord -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
deliveryStreamName
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Record
record
instance Data.ToHeaders PutRecord where
toHeaders :: PutRecord -> 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
"Firehose_20150804.PutRecord" ::
Prelude.ByteString
),
HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToJSON PutRecord where
toJSON :: PutRecord -> Value
toJSON PutRecord' {Text
Record
record :: Record
deliveryStreamName :: Text
$sel:record:PutRecord' :: PutRecord -> Record
$sel:deliveryStreamName:PutRecord' :: PutRecord -> Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ forall a. a -> Maybe a
Prelude.Just
(Key
"DeliveryStreamName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
deliveryStreamName),
forall a. a -> Maybe a
Prelude.Just (Key
"Record" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Record
record)
]
)
instance Data.ToPath PutRecord where
toPath :: PutRecord -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery PutRecord where
toQuery :: PutRecord -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data PutRecordResponse = PutRecordResponse'
{
PutRecordResponse -> Maybe Bool
encrypted :: Prelude.Maybe Prelude.Bool,
PutRecordResponse -> Int
httpStatus :: Prelude.Int,
PutRecordResponse -> Text
recordId :: Prelude.Text
}
deriving (PutRecordResponse -> PutRecordResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutRecordResponse -> PutRecordResponse -> Bool
$c/= :: PutRecordResponse -> PutRecordResponse -> Bool
== :: PutRecordResponse -> PutRecordResponse -> Bool
$c== :: PutRecordResponse -> PutRecordResponse -> Bool
Prelude.Eq, ReadPrec [PutRecordResponse]
ReadPrec PutRecordResponse
Int -> ReadS PutRecordResponse
ReadS [PutRecordResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutRecordResponse]
$creadListPrec :: ReadPrec [PutRecordResponse]
readPrec :: ReadPrec PutRecordResponse
$creadPrec :: ReadPrec PutRecordResponse
readList :: ReadS [PutRecordResponse]
$creadList :: ReadS [PutRecordResponse]
readsPrec :: Int -> ReadS PutRecordResponse
$creadsPrec :: Int -> ReadS PutRecordResponse
Prelude.Read, Int -> PutRecordResponse -> ShowS
[PutRecordResponse] -> ShowS
PutRecordResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutRecordResponse] -> ShowS
$cshowList :: [PutRecordResponse] -> ShowS
show :: PutRecordResponse -> String
$cshow :: PutRecordResponse -> String
showsPrec :: Int -> PutRecordResponse -> ShowS
$cshowsPrec :: Int -> PutRecordResponse -> ShowS
Prelude.Show, forall x. Rep PutRecordResponse x -> PutRecordResponse
forall x. PutRecordResponse -> Rep PutRecordResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutRecordResponse x -> PutRecordResponse
$cfrom :: forall x. PutRecordResponse -> Rep PutRecordResponse x
Prelude.Generic)
newPutRecordResponse ::
Prelude.Int ->
Prelude.Text ->
PutRecordResponse
newPutRecordResponse :: Int -> Text -> PutRecordResponse
newPutRecordResponse Int
pHttpStatus_ Text
pRecordId_ =
PutRecordResponse'
{ $sel:encrypted:PutRecordResponse' :: Maybe Bool
encrypted = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:PutRecordResponse' :: Int
httpStatus = Int
pHttpStatus_,
$sel:recordId:PutRecordResponse' :: Text
recordId = Text
pRecordId_
}
putRecordResponse_encrypted :: Lens.Lens' PutRecordResponse (Prelude.Maybe Prelude.Bool)
putRecordResponse_encrypted :: Lens' PutRecordResponse (Maybe Bool)
putRecordResponse_encrypted = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutRecordResponse' {Maybe Bool
encrypted :: Maybe Bool
$sel:encrypted:PutRecordResponse' :: PutRecordResponse -> Maybe Bool
encrypted} -> Maybe Bool
encrypted) (\s :: PutRecordResponse
s@PutRecordResponse' {} Maybe Bool
a -> PutRecordResponse
s {$sel:encrypted:PutRecordResponse' :: Maybe Bool
encrypted = Maybe Bool
a} :: PutRecordResponse)
putRecordResponse_httpStatus :: Lens.Lens' PutRecordResponse Prelude.Int
putRecordResponse_httpStatus :: Lens' PutRecordResponse Int
putRecordResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutRecordResponse' {Int
httpStatus :: Int
$sel:httpStatus:PutRecordResponse' :: PutRecordResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: PutRecordResponse
s@PutRecordResponse' {} Int
a -> PutRecordResponse
s {$sel:httpStatus:PutRecordResponse' :: Int
httpStatus = Int
a} :: PutRecordResponse)
putRecordResponse_recordId :: Lens.Lens' PutRecordResponse Prelude.Text
putRecordResponse_recordId :: Lens' PutRecordResponse Text
putRecordResponse_recordId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutRecordResponse' {Text
recordId :: Text
$sel:recordId:PutRecordResponse' :: PutRecordResponse -> Text
recordId} -> Text
recordId) (\s :: PutRecordResponse
s@PutRecordResponse' {} Text
a -> PutRecordResponse
s {$sel:recordId:PutRecordResponse' :: Text
recordId = Text
a} :: PutRecordResponse)
instance Prelude.NFData PutRecordResponse where
rnf :: PutRecordResponse -> ()
rnf PutRecordResponse' {Int
Maybe Bool
Text
recordId :: Text
httpStatus :: Int
encrypted :: Maybe Bool
$sel:recordId:PutRecordResponse' :: PutRecordResponse -> Text
$sel:httpStatus:PutRecordResponse' :: PutRecordResponse -> Int
$sel:encrypted:PutRecordResponse' :: PutRecordResponse -> Maybe Bool
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
encrypted
seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
recordId