{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies    #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Aws.DynamoDb.Commands.GetItem
-- Copyright   :  Soostone Inc
-- License     :  BSD3
--
-- Maintainer  :  Ozgun Ataman <ozgun.ataman@soostone.com>
-- Stability   :  experimental
--
--
----------------------------------------------------------------------------

module Aws.DynamoDb.Commands.GetItem 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
-------------------------------------------------------------------------------


-- | A GetItem query that fetches a specific object from DDB.
--
-- See: @http://docs.aws.amazon.com/amazondynamodb/latest/developerguide/API_GetItem.html@
data GetItem = GetItem {
      GetItem -> Text
giTableName  :: T.Text
    , GetItem -> PrimaryKey
giKey        :: PrimaryKey
    , GetItem -> Maybe [Text]
giAttrs      :: Maybe [T.Text]
    -- ^ Attributes to get. 'Nothing' grabs everything.
    , GetItem -> Bool
giConsistent :: Bool
    -- ^ Whether to issue a consistent read.
    , GetItem -> ReturnConsumption
giRetCons    :: ReturnConsumption
    -- ^ Whether to return consumption stats.
    } deriving (GetItem -> GetItem -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetItem -> GetItem -> Bool
$c/= :: GetItem -> GetItem -> Bool
== :: GetItem -> GetItem -> Bool
$c== :: GetItem -> GetItem -> Bool
Eq,Int -> GetItem -> ShowS
[GetItem] -> ShowS
GetItem -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetItem] -> ShowS
$cshowList :: [GetItem] -> ShowS
show :: GetItem -> String
$cshow :: GetItem -> String
showsPrec :: Int -> GetItem -> ShowS
$cshowsPrec :: Int -> GetItem -> ShowS
Show,ReadPrec [GetItem]
ReadPrec GetItem
Int -> ReadS GetItem
ReadS [GetItem]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetItem]
$creadListPrec :: ReadPrec [GetItem]
readPrec :: ReadPrec GetItem
$creadPrec :: ReadPrec GetItem
readList :: ReadS [GetItem]
$creadList :: ReadS [GetItem]
readsPrec :: Int -> ReadS GetItem
$creadsPrec :: Int -> ReadS GetItem
Read,Eq GetItem
GetItem -> GetItem -> Bool
GetItem -> GetItem -> Ordering
GetItem -> GetItem -> GetItem
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 :: GetItem -> GetItem -> GetItem
$cmin :: GetItem -> GetItem -> GetItem
max :: GetItem -> GetItem -> GetItem
$cmax :: GetItem -> GetItem -> GetItem
>= :: GetItem -> GetItem -> Bool
$c>= :: GetItem -> GetItem -> Bool
> :: GetItem -> GetItem -> Bool
$c> :: GetItem -> GetItem -> Bool
<= :: GetItem -> GetItem -> Bool
$c<= :: GetItem -> GetItem -> Bool
< :: GetItem -> GetItem -> Bool
$c< :: GetItem -> GetItem -> Bool
compare :: GetItem -> GetItem -> Ordering
$ccompare :: GetItem -> GetItem -> Ordering
Ord)


-------------------------------------------------------------------------------
-- | Construct a minimal 'GetItem' request.
getItem
    :: T.Text                   -- ^ Table name
    -> PrimaryKey               -- ^ Primary key
    -> GetItem
getItem :: Text -> PrimaryKey -> GetItem
getItem Text
tn PrimaryKey
k = Text
-> PrimaryKey
-> Maybe [Text]
-> Bool
-> ReturnConsumption
-> GetItem
GetItem Text
tn PrimaryKey
k forall a. Maybe a
Nothing Bool
False forall a. Default a => a
def


-- | Response to a 'GetItem' query.
data GetItemResponse = GetItemResponse {
      GetItemResponse -> Maybe Item
girItem     :: Maybe Item
    , GetItemResponse -> Maybe ConsumedCapacity
girConsumed :: Maybe ConsumedCapacity
    } deriving (GetItemResponse -> GetItemResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetItemResponse -> GetItemResponse -> Bool
$c/= :: GetItemResponse -> GetItemResponse -> Bool
== :: GetItemResponse -> GetItemResponse -> Bool
$c== :: GetItemResponse -> GetItemResponse -> Bool
Eq,Int -> GetItemResponse -> ShowS
[GetItemResponse] -> ShowS
GetItemResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetItemResponse] -> ShowS
$cshowList :: [GetItemResponse] -> ShowS
show :: GetItemResponse -> String
$cshow :: GetItemResponse -> String
showsPrec :: Int -> GetItemResponse -> ShowS
$cshowsPrec :: Int -> GetItemResponse -> ShowS
Show,ReadPrec [GetItemResponse]
ReadPrec GetItemResponse
Int -> ReadS GetItemResponse
ReadS [GetItemResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetItemResponse]
$creadListPrec :: ReadPrec [GetItemResponse]
readPrec :: ReadPrec GetItemResponse
$creadPrec :: ReadPrec GetItemResponse
readList :: ReadS [GetItemResponse]
$creadList :: ReadS [GetItemResponse]
readsPrec :: Int -> ReadS GetItemResponse
$creadsPrec :: Int -> ReadS GetItemResponse
Read,Eq GetItemResponse
GetItemResponse -> GetItemResponse -> Bool
GetItemResponse -> GetItemResponse -> Ordering
GetItemResponse -> GetItemResponse -> GetItemResponse
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 :: GetItemResponse -> GetItemResponse -> GetItemResponse
$cmin :: GetItemResponse -> GetItemResponse -> GetItemResponse
max :: GetItemResponse -> GetItemResponse -> GetItemResponse
$cmax :: GetItemResponse -> GetItemResponse -> GetItemResponse
>= :: GetItemResponse -> GetItemResponse -> Bool
$c>= :: GetItemResponse -> GetItemResponse -> Bool
> :: GetItemResponse -> GetItemResponse -> Bool
$c> :: GetItemResponse -> GetItemResponse -> Bool
<= :: GetItemResponse -> GetItemResponse -> Bool
$c<= :: GetItemResponse -> GetItemResponse -> Bool
< :: GetItemResponse -> GetItemResponse -> Bool
$c< :: GetItemResponse -> GetItemResponse -> Bool
compare :: GetItemResponse -> GetItemResponse -> Ordering
$ccompare :: GetItemResponse -> GetItemResponse -> Ordering
Ord)


instance Transaction GetItem GetItemResponse


instance ToJSON GetItem where
    toJSON :: GetItem -> Value
toJSON GetItem{Bool
Maybe [Text]
Text
ReturnConsumption
PrimaryKey
giRetCons :: ReturnConsumption
giConsistent :: Bool
giAttrs :: Maybe [Text]
giKey :: PrimaryKey
giTableName :: Text
giRetCons :: GetItem -> ReturnConsumption
giConsistent :: GetItem -> Bool
giAttrs :: GetItem -> Maybe [Text]
giKey :: GetItem -> PrimaryKey
giTableName :: GetItem -> Text
..} = [Pair] -> Value
object forall a b. (a -> b) -> a -> b
$
        forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key
"AttributesToGet" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.=)) Maybe [Text]
giAttrs forall a. [a] -> [a] -> [a]
++
        [ Key
"TableName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
giTableName
        , Key
"Key" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PrimaryKey
giKey
        , Key
"ConsistentRead" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
giConsistent
        , Key
"ReturnConsumedCapacity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ReturnConsumption
giRetCons
        ]


instance SignQuery GetItem where
    type ServiceConfiguration GetItem = DdbConfiguration
    signQuery :: forall queryType.
GetItem
-> ServiceConfiguration GetItem queryType
-> SignatureData
-> SignedQuery
signQuery GetItem
gi = forall a qt.
ToJSON a =>
ByteString
-> a -> DdbConfiguration qt -> SignatureData -> SignedQuery
ddbSignQuery ByteString
"GetItem" GetItem
gi



instance FromJSON GetItemResponse where
    parseJSON :: Value -> Parser GetItemResponse
parseJSON (Object Object
v) = Maybe Item -> Maybe ConsumedCapacity -> GetItemResponse
GetItemResponse
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"Item"
        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"
    parseJSON Value
_ = forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"GetItemResponse must be an object."


instance ResponseConsumer r GetItemResponse where
    type ResponseMetadata GetItemResponse = DdbResponse
    responseConsumer :: Request
-> r
-> IORef (ResponseMetadata GetItemResponse)
-> HTTPResponseConsumer GetItemResponse
responseConsumer Request
_ r
_ IORef (ResponseMetadata GetItemResponse)
ref Response (ConduitM () ByteString (ResourceT IO) ())
resp = forall a. FromJSON a => IORef DdbResponse -> HTTPResponseConsumer a
ddbResponseConsumer IORef (ResponseMetadata GetItemResponse)
ref Response (ConduitM () ByteString (ResourceT IO) ())
resp


instance AsMemoryResponse GetItemResponse where
    type MemoryResponse GetItemResponse = GetItemResponse
    loadToMemory :: GetItemResponse -> ResourceT IO (MemoryResponse GetItemResponse)
loadToMemory = forall (m :: * -> *) a. Monad m => a -> m a
return