{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Aws.DynamoDb.Commands.PutItem where
import Control.Applicative
import Data.Aeson
import Data.Default
import qualified Data.Text as T
import Prelude
import Aws.Core
import Aws.DynamoDb.Core
data PutItem = PutItem {
PutItem -> Text
piTable :: T.Text
, PutItem -> Item
piItem :: Item
, PutItem -> Conditions
piExpect :: Conditions
, PutItem -> UpdateReturn
piReturn :: UpdateReturn
, PutItem -> ReturnConsumption
piRetCons :: ReturnConsumption
, PutItem -> ReturnItemCollectionMetrics
piRetMet :: ReturnItemCollectionMetrics
} deriving (PutItem -> PutItem -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutItem -> PutItem -> Bool
$c/= :: PutItem -> PutItem -> Bool
== :: PutItem -> PutItem -> Bool
$c== :: PutItem -> PutItem -> Bool
Eq,Int -> PutItem -> ShowS
[PutItem] -> ShowS
PutItem -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutItem] -> ShowS
$cshowList :: [PutItem] -> ShowS
show :: PutItem -> String
$cshow :: PutItem -> String
showsPrec :: Int -> PutItem -> ShowS
$cshowsPrec :: Int -> PutItem -> ShowS
Show,ReadPrec [PutItem]
ReadPrec PutItem
Int -> ReadS PutItem
ReadS [PutItem]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutItem]
$creadListPrec :: ReadPrec [PutItem]
readPrec :: ReadPrec PutItem
$creadPrec :: ReadPrec PutItem
readList :: ReadS [PutItem]
$creadList :: ReadS [PutItem]
readsPrec :: Int -> ReadS PutItem
$creadsPrec :: Int -> ReadS PutItem
Read,Eq PutItem
PutItem -> PutItem -> Bool
PutItem -> PutItem -> Ordering
PutItem -> PutItem -> PutItem
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PutItem -> PutItem -> PutItem
$cmin :: PutItem -> PutItem -> PutItem
max :: PutItem -> PutItem -> PutItem
$cmax :: PutItem -> PutItem -> PutItem
>= :: PutItem -> PutItem -> Bool
$c>= :: PutItem -> PutItem -> Bool
> :: PutItem -> PutItem -> Bool
$c> :: PutItem -> PutItem -> Bool
<= :: PutItem -> PutItem -> Bool
$c<= :: PutItem -> PutItem -> Bool
< :: PutItem -> PutItem -> Bool
$c< :: PutItem -> PutItem -> Bool
compare :: PutItem -> PutItem -> Ordering
$ccompare :: PutItem -> PutItem -> Ordering
Ord)
putItem :: T.Text
-> Item
-> PutItem
putItem :: Text -> Item -> PutItem
putItem Text
tn Item
it = Text
-> Item
-> Conditions
-> UpdateReturn
-> ReturnConsumption
-> ReturnItemCollectionMetrics
-> PutItem
PutItem Text
tn Item
it forall a. Default a => a
def forall a. Default a => a
def forall a. Default a => a
def forall a. Default a => a
def
instance ToJSON PutItem where
toJSON :: PutItem -> Value
toJSON PutItem{Text
Item
UpdateReturn
ReturnItemCollectionMetrics
ReturnConsumption
Conditions
piRetMet :: ReturnItemCollectionMetrics
piRetCons :: ReturnConsumption
piReturn :: UpdateReturn
piExpect :: Conditions
piItem :: Item
piTable :: Text
piRetMet :: PutItem -> ReturnItemCollectionMetrics
piRetCons :: PutItem -> ReturnConsumption
piReturn :: PutItem -> UpdateReturn
piExpect :: PutItem -> Conditions
piItem :: PutItem -> Item
piTable :: PutItem -> Text
..} =
[Pair] -> Value
object forall a b. (a -> b) -> a -> b
$ Conditions -> [Pair]
expectsJson Conditions
piExpect forall a. [a] -> [a] -> [a]
++
[ Key
"TableName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
piTable
, Key
"Item" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Item
piItem
, Key
"ReturnValues" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= UpdateReturn
piReturn
, Key
"ReturnConsumedCapacity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ReturnConsumption
piRetCons
, Key
"ReturnItemCollectionMetrics" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ReturnItemCollectionMetrics
piRetMet
]
data PutItemResponse = PutItemResponse {
PutItemResponse -> Maybe Item
pirAttrs :: Maybe Item
, PutItemResponse -> Maybe ConsumedCapacity
pirConsumed :: Maybe ConsumedCapacity
, PutItemResponse -> Maybe ItemCollectionMetrics
pirColMet :: Maybe ItemCollectionMetrics
} deriving (PutItemResponse -> PutItemResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutItemResponse -> PutItemResponse -> Bool
$c/= :: PutItemResponse -> PutItemResponse -> Bool
== :: PutItemResponse -> PutItemResponse -> Bool
$c== :: PutItemResponse -> PutItemResponse -> Bool
Eq,Int -> PutItemResponse -> ShowS
[PutItemResponse] -> ShowS
PutItemResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutItemResponse] -> ShowS
$cshowList :: [PutItemResponse] -> ShowS
show :: PutItemResponse -> String
$cshow :: PutItemResponse -> String
showsPrec :: Int -> PutItemResponse -> ShowS
$cshowsPrec :: Int -> PutItemResponse -> ShowS
Show,ReadPrec [PutItemResponse]
ReadPrec PutItemResponse
Int -> ReadS PutItemResponse
ReadS [PutItemResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutItemResponse]
$creadListPrec :: ReadPrec [PutItemResponse]
readPrec :: ReadPrec PutItemResponse
$creadPrec :: ReadPrec PutItemResponse
readList :: ReadS [PutItemResponse]
$creadList :: ReadS [PutItemResponse]
readsPrec :: Int -> ReadS PutItemResponse
$creadsPrec :: Int -> ReadS PutItemResponse
Read,Eq PutItemResponse
PutItemResponse -> PutItemResponse -> Bool
PutItemResponse -> PutItemResponse -> Ordering
PutItemResponse -> PutItemResponse -> PutItemResponse
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PutItemResponse -> PutItemResponse -> PutItemResponse
$cmin :: PutItemResponse -> PutItemResponse -> PutItemResponse
max :: PutItemResponse -> PutItemResponse -> PutItemResponse
$cmax :: PutItemResponse -> PutItemResponse -> PutItemResponse
>= :: PutItemResponse -> PutItemResponse -> Bool
$c>= :: PutItemResponse -> PutItemResponse -> Bool
> :: PutItemResponse -> PutItemResponse -> Bool
$c> :: PutItemResponse -> PutItemResponse -> Bool
<= :: PutItemResponse -> PutItemResponse -> Bool
$c<= :: PutItemResponse -> PutItemResponse -> Bool
< :: PutItemResponse -> PutItemResponse -> Bool
$c< :: PutItemResponse -> PutItemResponse -> Bool
compare :: PutItemResponse -> PutItemResponse -> Ordering
$ccompare :: PutItemResponse -> PutItemResponse -> Ordering
Ord)
instance Transaction PutItem PutItemResponse
instance SignQuery PutItem where
type ServiceConfiguration PutItem = DdbConfiguration
signQuery :: forall queryType.
PutItem
-> ServiceConfiguration PutItem queryType
-> SignatureData
-> SignedQuery
signQuery PutItem
gi = forall a qt.
ToJSON a =>
ByteString
-> a -> DdbConfiguration qt -> SignatureData -> SignedQuery
ddbSignQuery ByteString
"PutItem" PutItem
gi
instance FromJSON PutItemResponse where
parseJSON :: Value -> Parser PutItemResponse
parseJSON (Object Object
v) = Maybe Item
-> Maybe ConsumedCapacity
-> Maybe ItemCollectionMetrics
-> PutItemResponse
PutItemResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"Attributes"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"ConsumedCapacity"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"ItemCollectionMetrics"
parseJSON Value
_ = forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"PutItemResponse must be an object."
instance ResponseConsumer r PutItemResponse where
type ResponseMetadata PutItemResponse = DdbResponse
responseConsumer :: Request
-> r
-> IORef (ResponseMetadata PutItemResponse)
-> HTTPResponseConsumer PutItemResponse
responseConsumer Request
_ r
_ IORef (ResponseMetadata PutItemResponse)
ref Response (ConduitM () ByteString (ResourceT IO) ())
resp = forall a. FromJSON a => IORef DdbResponse -> HTTPResponseConsumer a
ddbResponseConsumer IORef (ResponseMetadata PutItemResponse)
ref Response (ConduitM () ByteString (ResourceT IO) ())
resp
instance AsMemoryResponse PutItemResponse where
type MemoryResponse PutItemResponse = PutItemResponse
loadToMemory :: PutItemResponse -> ResourceT IO (MemoryResponse PutItemResponse)
loadToMemory = forall (m :: * -> *) a. Monad m => a -> m a
return