File: Scan.hs

package info (click to toggle)
haskell-aws 0.24.1-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 868 kB
  • sloc: haskell: 9,593; makefile: 2
file content (131 lines) | stat: -rw-r--r-- 4,300 bytes parent folder | download | duplicates (4)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
{-# 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 {
      sTableName      :: T.Text
    -- ^ Required.
    , sConsistentRead :: Bool
    -- ^ Whether to require a consistent read
    , sFilter         :: Conditions
    -- ^ Whether to filter results before returning to client
    , sStartKey       :: Maybe [Attribute]
    -- ^ Exclusive start key to resume a previous query.
    , sLimit          :: Maybe Int
    -- ^ Whether to limit result set size
    , sIndex          :: Maybe T.Text
    -- ^ Optional. Index to 'Scan'
    , sSelect         :: QuerySelect
    -- ^ What to return from 'Scan'
    , sRetCons        :: ReturnConsumption
    , sSegment        :: Int
    -- ^ Segment number, starting at 0, for parallel queries.
    , sTotalSegments  :: Int
    -- ^ Total number of parallel segments. 1 means sequential scan.
    } deriving (Eq,Show,Read,Ord,Typeable)


-- | Construct a minimal 'Scan' request.
scan :: T.Text                   -- ^ Table name
     -> Scan
scan tn = Scan tn False def Nothing Nothing Nothing def def 0 1


-- | Response to a 'Scan' query.
data ScanResponse = ScanResponse {
      srItems    :: V.Vector Item
    , srLastKey  :: Maybe [Attribute]
    , srCount    :: Int
    , srScanned  :: Int
    , srConsumed :: Maybe ConsumedCapacity
    } deriving (Eq,Show,Read,Ord)


-------------------------------------------------------------------------------
instance ToJSON Scan where
    toJSON Scan{..} = object $
      catMaybes
        [ (("ExclusiveStartKey" .= ) . attributesJson) <$> sStartKey
        , ("Limit" .= ) <$> sLimit
        , ("IndexName" .= ) <$> sIndex
        ] ++
      conditionsJson "ScanFilter" sFilter ++
      querySelectJson sSelect ++
      [ "TableName".= sTableName
      , "ReturnConsumedCapacity" .= sRetCons
      , "Segment" .= sSegment
      , "TotalSegments" .= sTotalSegments
      , "ConsistentRead" .= sConsistentRead
      ]


instance FromJSON ScanResponse where
    parseJSON (Object v) = ScanResponse
        <$> v .:?  "Items" .!= V.empty
        <*> ((do o <- v .: "LastEvaluatedKey"
                 Just <$> parseAttributeJson o)
             <|> pure Nothing)
        <*> v .:  "Count"
        <*> v .:  "ScannedCount"
        <*> v .:? "ConsumedCapacity"
    parseJSON _ = fail "ScanResponse must be an object."


instance Transaction Scan ScanResponse


instance SignQuery Scan where
    type ServiceConfiguration Scan = DdbConfiguration
    signQuery gi = ddbSignQuery "Scan" gi


instance ResponseConsumer r ScanResponse where
    type ResponseMetadata ScanResponse = DdbResponse
    responseConsumer _ _ ref resp = ddbResponseConsumer ref resp


instance AsMemoryResponse ScanResponse where
    type MemoryResponse ScanResponse = ScanResponse
    loadToMemory = return

instance ListResponse ScanResponse Item where
    listResponse = V.toList . srItems

instance IteratedTransaction Scan ScanResponse where
    nextIteratedRequest request response =
        case srLastKey response of
            Nothing -> Nothing
            key -> Just request { sStartKey = key }