module Aws.DynamoDb.Commands.UpdateItem
( UpdateItem(..)
, updateItem
, AttributeUpdate(..)
, au
, UpdateAction(..)
, UpdateItemResponse(..)
) 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 UpdateItem = UpdateItem {
uiTable :: T.Text
, uiKey :: PrimaryKey
, uiUpdates :: [AttributeUpdate]
, uiExpect :: Conditions
, uiReturn :: UpdateReturn
, uiRetCons :: ReturnConsumption
, uiRetMet :: ReturnItemCollectionMetrics
} deriving (Eq,Show,Read,Ord)
updateItem
:: T.Text
-> PrimaryKey
-> [AttributeUpdate]
-> UpdateItem
updateItem tn key ups = UpdateItem tn key ups def def def def
newtype AttributeUpdates = AttributeUpdates {
getAttributeUpdates :: [AttributeUpdate]
}
data AttributeUpdate = AttributeUpdate {
auAttr :: Attribute
, auAction :: UpdateAction
} deriving (Eq,Show,Read,Ord)
instance DynSize AttributeUpdate where
dynSize (AttributeUpdate a _) = dynSize a
au :: Attribute -> AttributeUpdate
au a = AttributeUpdate a def
instance ToJSON AttributeUpdates where
toJSON = object . map mk . getAttributeUpdates
where
mk AttributeUpdate { auAction = UDelete, auAttr = auAttr } =
(attrName auAttr) .= object
["Action" .= UDelete]
mk AttributeUpdate { .. } = (attrName auAttr) .= object
["Value" .= (attrVal auAttr), "Action" .= auAction]
data UpdateAction
= UPut
| UAdd
| UDelete
deriving (Eq,Show,Read,Ord)
instance ToJSON UpdateAction where
toJSON UPut = String "PUT"
toJSON UAdd = String "ADD"
toJSON UDelete = String "DELETE"
instance Default UpdateAction where
def = UPut
instance ToJSON UpdateItem where
toJSON UpdateItem{..} =
object $ expectsJson uiExpect ++
[ "TableName" .= uiTable
, "Key" .= uiKey
, "AttributeUpdates" .= AttributeUpdates uiUpdates
, "ReturnValues" .= uiReturn
, "ReturnConsumedCapacity" .= uiRetCons
, "ReturnItemCollectionMetrics" .= uiRetMet
]
data UpdateItemResponse = UpdateItemResponse {
uirAttrs :: Maybe Item
, uirConsumed :: Maybe ConsumedCapacity
} deriving (Eq,Show,Read,Ord)
instance Transaction UpdateItem UpdateItemResponse
instance SignQuery UpdateItem where
type ServiceConfiguration UpdateItem = DdbConfiguration
signQuery gi = ddbSignQuery "UpdateItem" gi
instance FromJSON UpdateItemResponse where
parseJSON (Object v) = UpdateItemResponse
<$> v .:? "Attributes"
<*> v .:? "ConsumedCapacity"
parseJSON _ = fail "UpdateItemResponse expected a JSON object"
instance ResponseConsumer r UpdateItemResponse where
type ResponseMetadata UpdateItemResponse = DdbResponse
responseConsumer _ _ ref resp = ddbResponseConsumer ref resp
instance AsMemoryResponse UpdateItemResponse where
type MemoryResponse UpdateItemResponse = UpdateItemResponse
loadToMemory = return