{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies    #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Aws.DynamoDb.Commands.Scan
-- Copyright   :  Soostone Inc
-- License     :  BSD3
--
-- Maintainer  :  Ozgun Ataman <ozgun.ataman@soostone.com>
-- Stability   :  experimental
--
-- Implementation of Amazon DynamoDb Scan command.
--
-- See: @http:\/\/docs.aws.amazon.com\/amazondynamodb\/latest\/APIReference\/API_Scan.html@
----------------------------------------------------------------------------

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
-------------------------------------------------------------------------------


-- | A Scan command that uses primary keys for an expedient scan.
data Scan = Scan {
      Scan -> Text
sTableName      :: T.Text
    -- ^ Required.
    , Scan -> Bool
sConsistentRead :: Bool
    -- ^ Whether to require a consistent read
    , Scan -> Conditions
sFilter         :: Conditions
    -- ^ Whether to filter results before returning to client
    , Scan -> Maybe [Attribute]
sStartKey       :: Maybe [Attribute]
    -- ^ Exclusive start key to resume a previous query.
    , Scan -> Maybe Int
sLimit          :: Maybe Int
    -- ^ Whether to limit result set size
    , Scan -> Maybe Text
sIndex          :: Maybe T.Text
    -- ^ Optional. Index to 'Scan'
    , Scan -> QuerySelect
sSelect         :: QuerySelect
    -- ^ What to return from 'Scan'
    , Scan -> ReturnConsumption
sRetCons        :: ReturnConsumption
    , Scan -> Int
sSegment        :: Int
    -- ^ Segment number, starting at 0, for parallel queries.
    , Scan -> Int
sTotalSegments  :: Int
    -- ^ Total number of parallel segments. 1 means sequential scan.
    } deriving (Scan -> Scan -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Scan -> Scan -> Bool
$c/= :: Scan -> Scan -> Bool
== :: Scan -> Scan -> Bool
$c== :: Scan -> Scan -> Bool
Eq,Int -> Scan -> ShowS
[Scan] -> ShowS
Scan -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Scan] -> ShowS
$cshowList :: [Scan] -> ShowS
show :: Scan -> String
$cshow :: Scan -> String
showsPrec :: Int -> Scan -> ShowS
$cshowsPrec :: Int -> Scan -> ShowS
Show,ReadPrec [Scan]
ReadPrec Scan
Int -> ReadS Scan
ReadS [Scan]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Scan]
$creadListPrec :: ReadPrec [Scan]
readPrec :: ReadPrec Scan
$creadPrec :: ReadPrec Scan
readList :: ReadS [Scan]
$creadList :: ReadS [Scan]
readsPrec :: Int -> ReadS Scan
$creadsPrec :: Int -> ReadS Scan
Read,Eq 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
min :: Scan -> Scan -> Scan
$cmin :: Scan -> Scan -> Scan
max :: Scan -> Scan -> Scan
$cmax :: Scan -> Scan -> Scan
>= :: Scan -> Scan -> Bool
$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
compare :: Scan -> Scan -> Ordering
$ccompare :: Scan -> Scan -> Ordering
Ord,Typeable)


-- | Construct a minimal 'Scan' request.
scan :: T.Text                   -- ^ Table name
     -> 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 forall a. Default a => a
def forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Default a => a
def forall a. Default a => a
def Int
0 Int
1


-- | Response to a 'Scan' query.
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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScanResponse -> ScanResponse -> Bool
$c/= :: ScanResponse -> ScanResponse -> Bool
== :: ScanResponse -> ScanResponse -> Bool
$c== :: ScanResponse -> ScanResponse -> Bool
Eq,Int -> ScanResponse -> ShowS
[ScanResponse] -> ShowS
ScanResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScanResponse] -> ShowS
$cshowList :: [ScanResponse] -> ShowS
show :: ScanResponse -> String
$cshow :: ScanResponse -> String
showsPrec :: Int -> ScanResponse -> ShowS
$cshowsPrec :: Int -> ScanResponse -> ShowS
Show,ReadPrec [ScanResponse]
ReadPrec ScanResponse
Int -> ReadS ScanResponse
ReadS [ScanResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ScanResponse]
$creadListPrec :: ReadPrec [ScanResponse]
readPrec :: ReadPrec ScanResponse
$creadPrec :: ReadPrec ScanResponse
readList :: ReadS [ScanResponse]
$creadList :: ReadS [ScanResponse]
readsPrec :: Int -> ReadS ScanResponse
$creadsPrec :: Int -> ReadS ScanResponse
Read,Eq 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
min :: ScanResponse -> ScanResponse -> ScanResponse
$cmin :: ScanResponse -> ScanResponse -> ScanResponse
max :: ScanResponse -> ScanResponse -> ScanResponse
$cmax :: ScanResponse -> ScanResponse -> ScanResponse
>= :: ScanResponse -> ScanResponse -> Bool
$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
compare :: ScanResponse -> ScanResponse -> Ordering
$ccompare :: ScanResponse -> ScanResponse -> Ordering
Ord)


-------------------------------------------------------------------------------
instance ToJSON Scan where
    toJSON :: Scan -> Value
toJSON Scan{Bool
Int
Maybe Int
Maybe [Attribute]
Maybe Text
Text
QuerySelect
ReturnConsumption
Conditions
sTotalSegments :: Int
sSegment :: Int
sRetCons :: ReturnConsumption
sSelect :: QuerySelect
sIndex :: Maybe Text
sLimit :: Maybe Int
sStartKey :: Maybe [Attribute]
sFilter :: Conditions
sConsistentRead :: Bool
sTableName :: Text
sTotalSegments :: Scan -> Int
sSegment :: Scan -> Int
sRetCons :: Scan -> ReturnConsumption
sSelect :: Scan -> QuerySelect
sIndex :: Scan -> Maybe Text
sLimit :: Scan -> Maybe Int
sStartKey :: Scan -> Maybe [Attribute]
sFilter :: Scan -> Conditions
sConsistentRead :: Scan -> Bool
sTableName :: Scan -> Text
..} = [Pair] -> Value
object forall a b. (a -> b) -> a -> b
$
      forall a. [Maybe a] -> [a]
catMaybes
        [ ((Key
"ExclusiveStartKey" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ) forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Attribute] -> Value
attributesJson) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [Attribute]
sStartKey
        , (Key
"Limit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
sLimit
        , (Key
"IndexName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
sIndex
        ] forall a. [a] -> [a] -> [a]
++
      Text -> Conditions -> [Pair]
conditionsJson Text
"ScanFilter" Conditions
sFilter forall a. [a] -> [a] -> [a]
++
      forall t. KeyValue t => QuerySelect -> [t]
querySelectJson QuerySelect
sSelect forall a. [a] -> [a] -> [a]
++
      [ Key
"TableName"forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
sTableName
      , Key
"ReturnConsumedCapacity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ReturnConsumption
sRetCons
      , Key
"Segment" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
sSegment
      , Key
"TotalSegments" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Int
sTotalSegments
      , Key
"ConsistentRead" forall kv v. (KeyValue 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
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:?  Key
"Items" forall a. Parser (Maybe a) -> a -> Parser a
.!= forall a. Vector a
V.empty
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((do Value
o <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"LastEvaluatedKey"
                 forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [Attribute]
parseAttributeJson Value
o)
             forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing)
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.:  Key
"Count"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.:  Key
"ScannedCount"
        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
"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 = 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 = forall a. FromJSON a => IORef DdbResponse -> HTTPResponseConsumer a
ddbResponseConsumer IORef (ResponseMetadata ScanResponse)
ref Response (ConduitM () ByteString (ResourceT IO) ())
resp


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

instance ListResponse ScanResponse Item where
    listResponse :: ScanResponse -> [Item]
listResponse = forall a. Vector a -> [a]
V.toList 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 -> forall a. Maybe a
Nothing
            Maybe [Attribute]
key -> forall a. a -> Maybe a
Just Scan
request { sStartKey :: Maybe [Attribute]
sStartKey = Maybe [Attribute]
key }