{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
module Aws.DynamoDb.Commands.Scan
( Scan (..)
, scan
, ScanResponse (..)
) where
import Control.Applicative
import Data.Aeson
import Data.Default
import Data.Maybe
import qualified Data.Text as T
import Data.Typeable
import qualified Data.Vector as V
import Aws.Core
import Aws.DynamoDb.Core
data Scan = Scan {
Scan -> Text
sTableName :: T.Text
, Scan -> Bool
sConsistentRead :: Bool
, Scan -> Conditions
sFilter :: Conditions
, Scan -> Maybe [Attribute]
sStartKey :: Maybe [Attribute]
, Scan -> Maybe Int
sLimit :: Maybe Int
, Scan -> Maybe Text
sIndex :: Maybe T.Text
, Scan -> QuerySelect
sSelect :: QuerySelect
, Scan -> ReturnConsumption
sRetCons :: ReturnConsumption
, Scan -> Int
sSegment :: Int
, Scan -> Int
sTotalSegments :: Int
} deriving (Scan -> Scan -> Bool
(Scan -> Scan -> Bool) -> (Scan -> Scan -> Bool) -> Eq Scan
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Scan -> Scan -> Bool
== :: Scan -> Scan -> Bool
$c/= :: Scan -> Scan -> Bool
/= :: Scan -> Scan -> Bool
Eq,Int -> Scan -> ShowS
[Scan] -> ShowS
Scan -> String
(Int -> Scan -> ShowS)
-> (Scan -> String) -> ([Scan] -> ShowS) -> Show Scan
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Scan -> ShowS
showsPrec :: Int -> Scan -> ShowS
$cshow :: Scan -> String
show :: Scan -> String
$cshowList :: [Scan] -> ShowS
showList :: [Scan] -> ShowS
Show,ReadPrec [Scan]
ReadPrec Scan
Int -> ReadS Scan
ReadS [Scan]
(Int -> ReadS Scan)
-> ReadS [Scan] -> ReadPrec Scan -> ReadPrec [Scan] -> Read Scan
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Scan
readsPrec :: Int -> ReadS Scan
$creadList :: ReadS [Scan]
readList :: ReadS [Scan]
$creadPrec :: ReadPrec Scan
readPrec :: ReadPrec Scan
$creadListPrec :: ReadPrec [Scan]
readListPrec :: ReadPrec [Scan]
Read,Eq Scan
Eq Scan =>
(Scan -> Scan -> Ordering)
-> (Scan -> Scan -> Bool)
-> (Scan -> Scan -> Bool)
-> (Scan -> Scan -> Bool)
-> (Scan -> Scan -> Bool)
-> (Scan -> Scan -> Scan)
-> (Scan -> Scan -> Scan)
-> Ord Scan
Scan -> Scan -> Bool
Scan -> Scan -> Ordering
Scan -> Scan -> Scan
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
$ccompare :: Scan -> Scan -> Ordering
compare :: Scan -> Scan -> Ordering
$c< :: Scan -> Scan -> Bool
< :: Scan -> Scan -> Bool
$c<= :: Scan -> Scan -> Bool
<= :: Scan -> Scan -> Bool
$c> :: Scan -> Scan -> Bool
> :: Scan -> Scan -> Bool
$c>= :: Scan -> Scan -> Bool
>= :: Scan -> Scan -> Bool
$cmax :: Scan -> Scan -> Scan
max :: Scan -> Scan -> Scan
$cmin :: Scan -> Scan -> Scan
min :: Scan -> Scan -> Scan
Ord,Typeable)
scan :: T.Text
-> Scan
scan :: Text -> Scan
scan Text
tn = Text
-> Bool
-> Conditions
-> Maybe [Attribute]
-> Maybe Int
-> Maybe Text
-> QuerySelect
-> ReturnConsumption
-> Int
-> Int
-> Scan
Scan Text
tn Bool
False Conditions
forall a. Default a => a
def Maybe [Attribute]
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing QuerySelect
forall a. Default a => a
def ReturnConsumption
forall a. Default a => a
def Int
0 Int
1
data ScanResponse = ScanResponse {
ScanResponse -> Vector Item
srItems :: V.Vector Item
, ScanResponse -> Maybe [Attribute]
srLastKey :: Maybe [Attribute]
, ScanResponse -> Int
srCount :: Int
, ScanResponse -> Int
srScanned :: Int
, ScanResponse -> Maybe ConsumedCapacity
srConsumed :: Maybe ConsumedCapacity
} deriving (ScanResponse -> ScanResponse -> Bool
(ScanResponse -> ScanResponse -> Bool)
-> (ScanResponse -> ScanResponse -> Bool) -> Eq ScanResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ScanResponse -> ScanResponse -> Bool
== :: ScanResponse -> ScanResponse -> Bool
$c/= :: ScanResponse -> ScanResponse -> Bool
/= :: ScanResponse -> ScanResponse -> Bool
Eq,Int -> ScanResponse -> ShowS
[ScanResponse] -> ShowS
ScanResponse -> String
(Int -> ScanResponse -> ShowS)
-> (ScanResponse -> String)
-> ([ScanResponse] -> ShowS)
-> Show ScanResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScanResponse -> ShowS
showsPrec :: Int -> ScanResponse -> ShowS
$cshow :: ScanResponse -> String
show :: ScanResponse -> String
$cshowList :: [ScanResponse] -> ShowS
showList :: [ScanResponse] -> ShowS
Show,ReadPrec [ScanResponse]
ReadPrec ScanResponse
Int -> ReadS ScanResponse
ReadS [ScanResponse]
(Int -> ReadS ScanResponse)
-> ReadS [ScanResponse]
-> ReadPrec ScanResponse
-> ReadPrec [ScanResponse]
-> Read ScanResponse
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ScanResponse
readsPrec :: Int -> ReadS ScanResponse
$creadList :: ReadS [ScanResponse]
readList :: ReadS [ScanResponse]
$creadPrec :: ReadPrec ScanResponse
readPrec :: ReadPrec ScanResponse
$creadListPrec :: ReadPrec [ScanResponse]
readListPrec :: ReadPrec [ScanResponse]
Read,Eq ScanResponse
Eq ScanResponse =>
(ScanResponse -> ScanResponse -> Ordering)
-> (ScanResponse -> ScanResponse -> Bool)
-> (ScanResponse -> ScanResponse -> Bool)
-> (ScanResponse -> ScanResponse -> Bool)
-> (ScanResponse -> ScanResponse -> Bool)
-> (ScanResponse -> ScanResponse -> ScanResponse)
-> (ScanResponse -> ScanResponse -> ScanResponse)
-> Ord ScanResponse
ScanResponse -> ScanResponse -> Bool
ScanResponse -> ScanResponse -> Ordering
ScanResponse -> ScanResponse -> ScanResponse
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
$ccompare :: ScanResponse -> ScanResponse -> Ordering
compare :: ScanResponse -> ScanResponse -> Ordering
$c< :: ScanResponse -> ScanResponse -> Bool
< :: ScanResponse -> ScanResponse -> Bool
$c<= :: ScanResponse -> ScanResponse -> Bool
<= :: ScanResponse -> ScanResponse -> Bool
$c> :: ScanResponse -> ScanResponse -> Bool
> :: ScanResponse -> ScanResponse -> Bool
$c>= :: ScanResponse -> ScanResponse -> Bool
>= :: ScanResponse -> ScanResponse -> Bool
$cmax :: ScanResponse -> ScanResponse -> ScanResponse
max :: ScanResponse -> ScanResponse -> ScanResponse
$cmin :: ScanResponse -> ScanResponse -> ScanResponse
min :: ScanResponse -> ScanResponse -> ScanResponse
Ord)
instance ToJSON Scan where
toJSON :: Scan -> Value
toJSON Scan{Bool
Int
Maybe Int
Maybe [Attribute]
Maybe Text
Text
QuerySelect
ReturnConsumption
Conditions
sTableName :: Scan -> Text
sConsistentRead :: Scan -> Bool
sFilter :: Scan -> Conditions
sStartKey :: Scan -> Maybe [Attribute]
sLimit :: Scan -> Maybe Int
sIndex :: Scan -> Maybe Text
sSelect :: Scan -> QuerySelect
sRetCons :: Scan -> ReturnConsumption
sSegment :: Scan -> Int
sTotalSegments :: Scan -> Int
sTableName :: Text
sConsistentRead :: Bool
sFilter :: Conditions
sStartKey :: Maybe [Attribute]
sLimit :: Maybe Int
sIndex :: Maybe Text
sSelect :: QuerySelect
sRetCons :: ReturnConsumption
sSegment :: Int
sTotalSegments :: Int
..} = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
catMaybes
[ ((Key
"ExclusiveStartKey" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= ) (Value -> Pair) -> ([Attribute] -> Value) -> [Attribute] -> Pair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Attribute] -> Value
attributesJson) ([Attribute] -> Pair) -> Maybe [Attribute] -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [Attribute]
sStartKey
, (Key
"Limit" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= ) (Int -> Pair) -> Maybe Int -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
sLimit
, (Key
"IndexName" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= ) (Text -> Pair) -> Maybe Text -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
sIndex
] [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++
Text -> Conditions -> [Pair]
conditionsJson Text
"ScanFilter" Conditions
sFilter [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++
QuerySelect -> [Pair]
forall t. KeyValue Value t => QuerySelect -> [t]
querySelectJson QuerySelect
sSelect [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++
[ Key
"TableName"Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Text
sTableName
, Key
"ReturnConsumedCapacity" Key -> ReturnConsumption -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= ReturnConsumption
sRetCons
, Key
"Segment" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
sSegment
, Key
"TotalSegments" Key -> Int -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Int
sTotalSegments
, Key
"ConsistentRead" Key -> Bool -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Bool
sConsistentRead
]
instance FromJSON ScanResponse where
parseJSON :: Value -> Parser ScanResponse
parseJSON (Object Object
v) = Vector Item
-> Maybe [Attribute]
-> Int
-> Int
-> Maybe ConsumedCapacity
-> ScanResponse
ScanResponse
(Vector Item
-> Maybe [Attribute]
-> Int
-> Int
-> Maybe ConsumedCapacity
-> ScanResponse)
-> Parser (Vector Item)
-> Parser
(Maybe [Attribute]
-> Int -> Int -> Maybe ConsumedCapacity -> ScanResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser (Maybe (Vector Item))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"Items" Parser (Maybe (Vector Item)) -> Vector Item -> Parser (Vector Item)
forall a. Parser (Maybe a) -> a -> Parser a
.!= Vector Item
forall a. Vector a
V.empty
Parser
(Maybe [Attribute]
-> Int -> Int -> Maybe ConsumedCapacity -> ScanResponse)
-> Parser (Maybe [Attribute])
-> Parser (Int -> Int -> Maybe ConsumedCapacity -> ScanResponse)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((do Value
o <- Object
v Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"LastEvaluatedKey"
[Attribute] -> Maybe [Attribute]
forall a. a -> Maybe a
Just ([Attribute] -> Maybe [Attribute])
-> Parser [Attribute] -> Parser (Maybe [Attribute])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [Attribute]
parseAttributeJson Value
o)
Parser (Maybe [Attribute])
-> Parser (Maybe [Attribute]) -> Parser (Maybe [Attribute])
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe [Attribute] -> Parser (Maybe [Attribute])
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe [Attribute]
forall a. Maybe a
Nothing)
Parser (Int -> Int -> Maybe ConsumedCapacity -> ScanResponse)
-> Parser Int
-> Parser (Int -> Maybe ConsumedCapacity -> ScanResponse)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"Count"
Parser (Int -> Maybe ConsumedCapacity -> ScanResponse)
-> Parser Int -> Parser (Maybe ConsumedCapacity -> ScanResponse)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"ScannedCount"
Parser (Maybe ConsumedCapacity -> ScanResponse)
-> Parser (Maybe ConsumedCapacity) -> Parser ScanResponse
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe ConsumedCapacity)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"ConsumedCapacity"
parseJSON Value
_ = String -> Parser ScanResponse
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"ScanResponse must be an object."
instance Transaction Scan ScanResponse
instance SignQuery Scan where
type ServiceConfiguration Scan = DdbConfiguration
signQuery :: forall queryType.
Scan
-> ServiceConfiguration Scan queryType
-> SignatureData
-> SignedQuery
signQuery Scan
gi = ByteString
-> Scan
-> DdbConfiguration queryType
-> SignatureData
-> SignedQuery
forall a qt.
ToJSON a =>
ByteString
-> a -> DdbConfiguration qt -> SignatureData -> SignedQuery
ddbSignQuery ByteString
"Scan" Scan
gi
instance ResponseConsumer r ScanResponse where
type ResponseMetadata ScanResponse = DdbResponse
responseConsumer :: Request
-> r
-> IORef (ResponseMetadata ScanResponse)
-> HTTPResponseConsumer ScanResponse
responseConsumer Request
_ r
_ IORef (ResponseMetadata ScanResponse)
ref Response (ConduitM () ByteString (ResourceT IO) ())
resp = IORef DdbResponse -> HTTPResponseConsumer ScanResponse
forall a. FromJSON a => IORef DdbResponse -> HTTPResponseConsumer a
ddbResponseConsumer IORef (ResponseMetadata ScanResponse)
IORef DdbResponse
ref Response (ConduitM () ByteString (ResourceT IO) ())
resp
instance AsMemoryResponse ScanResponse where
type MemoryResponse ScanResponse = ScanResponse
loadToMemory :: ScanResponse -> ResourceT IO (MemoryResponse ScanResponse)
loadToMemory = ScanResponse -> ResourceT IO (MemoryResponse ScanResponse)
ScanResponse -> ResourceT IO ScanResponse
forall a. a -> ResourceT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
instance ListResponse ScanResponse Item where
listResponse :: ScanResponse -> [Item]
listResponse = Vector Item -> [Item]
forall a. Vector a -> [a]
V.toList (Vector Item -> [Item])
-> (ScanResponse -> Vector Item) -> ScanResponse -> [Item]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScanResponse -> Vector Item
srItems
instance IteratedTransaction Scan ScanResponse where
nextIteratedRequest :: Scan -> ScanResponse -> Maybe Scan
nextIteratedRequest Scan
request ScanResponse
response =
case ScanResponse -> Maybe [Attribute]
srLastKey ScanResponse
response of
Maybe [Attribute]
Nothing -> Maybe Scan
forall a. Maybe a
Nothing
Maybe [Attribute]
key -> Scan -> Maybe Scan
forall a. a -> Maybe a
Just Scan
request { sStartKey = key }