File: Table.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 (473 lines) | stat: -rw-r--r-- 18,888 bytes parent folder | download | duplicates (2)
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
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeFamilies               #-}

module Aws.DynamoDb.Commands.Table
    ( -- * Commands
      CreateTable(..)
    , createTable
    , CreateTableResult(..)
    , DescribeTable(..)
    , DescribeTableResult(..)
    , UpdateTable(..)
    , UpdateTableResult(..)
    , DeleteTable(..)
    , DeleteTableResult(..)
    , ListTables(..)
    , ListTablesResult(..)

    -- * Data passed in the commands
    , AttributeType(..)
    , AttributeDefinition(..)
    , KeySchema(..)
    , Projection(..)
    , LocalSecondaryIndex(..)
    , LocalSecondaryIndexStatus(..)
    , ProvisionedThroughput(..)
    , ProvisionedThroughputStatus(..)
    , GlobalSecondaryIndex(..)
    , GlobalSecondaryIndexStatus(..)
    , GlobalSecondaryIndexUpdate(..)
    , TableDescription(..)
    ) where

-------------------------------------------------------------------------------
import           Control.Applicative
import           Data.Aeson            ((.!=), (.:), (.:?), (.=))
import qualified Data.Aeson            as A
import qualified Data.Aeson.KeyMap     as KM
import qualified Data.Aeson.Types      as A
import           Data.Char             (toUpper)
import           Data.Scientific       (Scientific)
import qualified Data.Text             as T
import           Data.Time
import           Data.Time.Clock.POSIX
import           Data.Typeable
import qualified Data.Vector           as V
import           GHC.Generics          (Generic)
import           Prelude
-------------------------------------------------------------------------------
import           Aws.Core
import           Aws.DynamoDb.Core
-------------------------------------------------------------------------------


capitalizeOpt :: A.Options
capitalizeOpt = A.defaultOptions
    { A.fieldLabelModifier = \x -> case x of
                                     (c:cs) -> toUpper c : cs
                                     [] -> []
    }


dropOpt :: Int -> A.Options
dropOpt d = A.defaultOptions { A.fieldLabelModifier = drop d }


convertToUTCTime :: Scientific -> UTCTime
convertToUTCTime = posixSecondsToUTCTime . fromInteger . round


-- | The type of a key attribute that appears in the table key or as a
-- key in one of the indices.
data AttributeType = AttrString | AttrNumber | AttrBinary
    deriving (Show, Read, Ord, Typeable, Eq, Enum, Bounded, Generic)

instance A.ToJSON AttributeType where
    toJSON AttrString = A.String "S"
    toJSON AttrNumber = A.String "N"
    toJSON AttrBinary = A.String "B"

instance A.FromJSON AttributeType where
    parseJSON (A.String str) =
        case str of
            "S" -> return AttrString
            "N" -> return AttrNumber
            "B" -> return AttrBinary
            _   -> fail $ "Invalid attribute type " ++ T.unpack str
    parseJSON _ = fail "Attribute type must be a string"

-- | A key attribute that appears in the table key or as a key in one of the indices.
data AttributeDefinition = AttributeDefinition {
      attributeName :: T.Text
    , attributeType :: AttributeType
    } deriving (Eq,Read,Ord,Show,Typeable,Generic)

instance A.ToJSON AttributeDefinition where
    toJSON = A.genericToJSON capitalizeOpt

instance A.FromJSON AttributeDefinition where
    parseJSON = A.genericParseJSON capitalizeOpt

-- | The key schema can either be a hash of a single attribute name or a hash attribute name
-- and a range attribute name.
data KeySchema = HashOnly T.Text
               | HashAndRange T.Text T.Text
    deriving (Eq,Read,Show,Ord,Typeable,Generic)


instance A.ToJSON KeySchema where
    toJSON (HashOnly a)
        = A.Array $ V.fromList [ A.object [ "AttributeName" .= a
                                          , "KeyType" .= (A.String "HASH")
                                          ]
                               ]

    toJSON (HashAndRange hash range)
        = A.Array $ V.fromList [ A.object [ "AttributeName" .= hash
                                          , "KeyType" .= (A.String "HASH")
                                          ]
                               , A.object [ "AttributeName" .= range
                                          , "KeyType" .= (A.String "RANGE")
                                          ]
                               ]

instance A.FromJSON KeySchema where
    parseJSON (A.Array v) =
        case V.length v of
            1 -> do obj <- A.parseJSON (v V.! 0)
                    kt <- obj .: "KeyType"
                    if kt /= ("HASH" :: T.Text)
                        then fail "With only one key, the type must be HASH"
                        else HashOnly <$> obj .: "AttributeName"

            2 -> do hash <- A.parseJSON (v V.! 0)
                    range <- A.parseJSON (v V.! 1)
                    hkt <- hash .: "KeyType"
                    rkt <- range .: "KeyType"
                    if hkt /= ("HASH" :: T.Text) || rkt /= ("RANGE" :: T.Text)
                        then fail "With two keys, one must be HASH and the other RANGE"
                        else HashAndRange <$> hash .: "AttributeName"
                                          <*> range .: "AttributeName"
            _ -> fail "Key schema must have one or two entries"
    parseJSON _ = fail "Key schema must be an array"

-- | This determines which attributes are projected into a secondary index.
data Projection = ProjectKeysOnly
                | ProjectAll
                | ProjectInclude [T.Text]
    deriving Show
instance A.ToJSON Projection where
    toJSON ProjectKeysOnly    = A.object [ "ProjectionType" .= ("KEYS_ONLY" :: T.Text) ]
    toJSON ProjectAll         = A.object [ "ProjectionType" .= ("ALL" :: T.Text) ]
    toJSON (ProjectInclude a) = A.object [ "ProjectionType" .= ("INCLUDE" :: T.Text)
                                         , "NonKeyAttributes" .= a
                                         ]
instance A.FromJSON Projection where
    parseJSON (A.Object o) = do
        ty <- (o .: "ProjectionType") :: A.Parser T.Text
        case ty of
            "KEYS_ONLY" -> return ProjectKeysOnly
            "ALL" -> return ProjectAll
            "INCLUDE" -> ProjectInclude <$> o .: "NonKeyAttributes"
            _ -> fail "Invalid projection type"
    parseJSON _ = fail "Projection must be an object"

-- | Describes a single local secondary index. The KeySchema MUST
-- share the same hash key attribute as the parent table, only the
-- range key can differ.
data LocalSecondaryIndex
    = LocalSecondaryIndex {
        localIndexName  :: T.Text
      , localKeySchema  :: KeySchema
      , localProjection :: Projection
      }
    deriving (Show, Generic)
instance A.ToJSON LocalSecondaryIndex where
    toJSON = A.genericToJSON $ dropOpt 5
instance A.FromJSON LocalSecondaryIndex where
    parseJSON = A.genericParseJSON $ dropOpt 5

-- | This is returned by AWS to describe the local secondary index.
data LocalSecondaryIndexStatus
    = LocalSecondaryIndexStatus {
        locStatusIndexName      :: T.Text
      , locStatusIndexSizeBytes :: Integer
      , locStatusItemCount      :: Integer
      , locStatusKeySchema      :: KeySchema
      , locStatusProjection     :: Projection
      }
    deriving (Show, Generic)
instance A.FromJSON LocalSecondaryIndexStatus where
    parseJSON = A.genericParseJSON $ dropOpt 9

-- | The target provisioned throughput you are requesting for the table or global secondary index.
data ProvisionedThroughput
    = ProvisionedThroughput {
        readCapacityUnits  :: Int
      , writeCapacityUnits :: Int
      }
    deriving (Show, Generic)
instance A.ToJSON ProvisionedThroughput where
    toJSON = A.genericToJSON capitalizeOpt
instance A.FromJSON ProvisionedThroughput where
    parseJSON = A.genericParseJSON capitalizeOpt

-- | This is returned by AWS as the status of the throughput for a table or global secondary index.
data ProvisionedThroughputStatus
    = ProvisionedThroughputStatus {
        statusLastDecreaseDateTime   :: UTCTime
      , statusLastIncreaseDateTime   :: UTCTime
      , statusNumberOfDecreasesToday :: Int
      , statusReadCapacityUnits      :: Int
      , statusWriteCapacityUnits     :: Int
      }
    deriving (Show, Generic)
instance A.FromJSON ProvisionedThroughputStatus where
    parseJSON = A.withObject "Throughput status must be an object" $ \o ->
        ProvisionedThroughputStatus
            <$> (convertToUTCTime <$> o .:? "LastDecreaseDateTime" .!= 0)
            <*> (convertToUTCTime <$> o .:? "LastIncreaseDateTime" .!= 0)
            <*> o .:? "NumberOfDecreasesToday" .!= 0
            <*> o .: "ReadCapacityUnits"
            <*> o .: "WriteCapacityUnits"

-- | Describes a global secondary index.
data GlobalSecondaryIndex
    = GlobalSecondaryIndex {
        globalIndexName             :: T.Text
      , globalKeySchema             :: KeySchema
      , globalProjection            :: Projection
      , globalProvisionedThroughput :: ProvisionedThroughput
      }
    deriving (Show, Generic)
instance A.ToJSON GlobalSecondaryIndex where
    toJSON = A.genericToJSON $ dropOpt 6
instance A.FromJSON GlobalSecondaryIndex where
    parseJSON = A.genericParseJSON $ dropOpt 6

-- | This is returned by AWS to describe the status of a global secondary index.
data GlobalSecondaryIndexStatus
    = GlobalSecondaryIndexStatus {
        gStatusIndexName             :: T.Text
      , gStatusIndexSizeBytes        :: Integer
      , gStatusIndexStatus           :: T.Text
      , gStatusItemCount             :: Integer
      , gStatusKeySchema             :: KeySchema
      , gStatusProjection            :: Projection
      , gStatusProvisionedThroughput :: ProvisionedThroughputStatus
      }
    deriving (Show, Generic)
instance A.FromJSON GlobalSecondaryIndexStatus where
    parseJSON = A.genericParseJSON $ dropOpt 7

-- | This is used to request a change in the provisioned throughput of
-- a global secondary index as part of an 'UpdateTable' operation.
data GlobalSecondaryIndexUpdate
    = GlobalSecondaryIndexUpdate {
        gUpdateIndexName             :: T.Text
      , gUpdateProvisionedThroughput :: ProvisionedThroughput
      }
    deriving (Show, Generic)
instance A.ToJSON GlobalSecondaryIndexUpdate where
    toJSON gi = A.object ["Update" .= A.genericToJSON (dropOpt 7) gi]

-- | This describes the table and is the return value from AWS for all
-- the table-related commands.
data TableDescription
    = TableDescription {
        rTableName              :: T.Text
      , rTableSizeBytes         :: Integer
      , rTableStatus            :: T.Text -- ^ one of CREATING, UPDATING, DELETING, ACTIVE
      , rCreationDateTime       :: Maybe UTCTime
      , rItemCount              :: Integer
      , rAttributeDefinitions   :: [AttributeDefinition]
      , rKeySchema              :: Maybe KeySchema
      , rProvisionedThroughput  :: ProvisionedThroughputStatus
      , rLocalSecondaryIndexes  :: [LocalSecondaryIndexStatus]
      , rGlobalSecondaryIndexes :: [GlobalSecondaryIndexStatus]
      }
    deriving (Show, Generic)

instance A.FromJSON TableDescription where
    parseJSON = A.withObject "Table must be an object" $ \o -> do
        t <- case (KM.lookup "Table" o, KM.lookup "TableDescription" o) of
                (Just (A.Object t), _) -> return t
                (_, Just (A.Object t)) -> return t
                _ -> fail "Table description must have key 'Table' or 'TableDescription'"
        TableDescription <$> t .: "TableName"
                         <*> t .: "TableSizeBytes"
                         <*> t .: "TableStatus"
                         <*> (fmap convertToUTCTime <$> t .:? "CreationDateTime")
                         <*> t .: "ItemCount"
                         <*> t .:? "AttributeDefinitions" .!= []
                         <*> t .:? "KeySchema"
                         <*> t .: "ProvisionedThroughput"
                         <*> t .:? "LocalSecondaryIndexes" .!= []
                         <*> t .:? "GlobalSecondaryIndexes" .!= []

{- Can't derive these instances onto the return values
instance ResponseConsumer r TableDescription where
    type ResponseMetadata TableDescription = DyMetadata
    responseConsumer _ _ _ = ddbResponseConsumer
instance AsMemoryResponse TableDescription where
    type MemoryResponse TableDescription = TableDescription
    loadToMemory = return
-}

-------------------------------------------------------------------------------
--- Commands
-------------------------------------------------------------------------------

data CreateTable = CreateTable {
      createTableName              :: T.Text
    , createAttributeDefinitions   :: [AttributeDefinition]
    -- ^ only attributes appearing in a key must be listed here
    , createKeySchema              :: KeySchema
    , createProvisionedThroughput  :: ProvisionedThroughput
    , createLocalSecondaryIndexes  :: [LocalSecondaryIndex]
    -- ^ at most 5 local secondary indices are allowed
    , createGlobalSecondaryIndexes :: [GlobalSecondaryIndex]
    } deriving (Show, Generic)

createTable :: T.Text -- ^ Table name
            -> [AttributeDefinition]
            -> KeySchema
            -> ProvisionedThroughput
            -> CreateTable
createTable tn ad ks p = CreateTable tn ad ks p [] []

instance A.ToJSON CreateTable where
    toJSON ct = A.object $ m ++ lindex ++ gindex
        where
            m = [ "TableName" .= createTableName ct
                , "AttributeDefinitions" .= createAttributeDefinitions ct
                , "KeySchema" .= createKeySchema ct
                , "ProvisionedThroughput" .= createProvisionedThroughput ct
                ]
            -- AWS will error with 500 if (LocalSecondaryIndexes : []) is present in the JSON
            lindex = if null (createLocalSecondaryIndexes ct)
                        then []
                        else [ "LocalSecondaryIndexes" .= createLocalSecondaryIndexes ct ]
            gindex = if null (createGlobalSecondaryIndexes ct)
                        then []
                        else [ "GlobalSecondaryIndexes" .= createGlobalSecondaryIndexes ct ]

--instance A.ToJSON CreateTable where
--    toJSON = A.genericToJSON $ dropOpt 6


-- | ServiceConfiguration: 'DdbConfiguration'
instance SignQuery CreateTable where
    type ServiceConfiguration CreateTable = DdbConfiguration
    signQuery = ddbSignQuery "CreateTable"

newtype CreateTableResult = CreateTableResult { ctStatus :: TableDescription }
    deriving (Show, A.FromJSON)
-- ResponseConsumer and AsMemoryResponse can't be derived
instance ResponseConsumer r CreateTableResult where
    type ResponseMetadata CreateTableResult = DdbResponse
    responseConsumer _ _ = ddbResponseConsumer
instance AsMemoryResponse CreateTableResult where
    type MemoryResponse CreateTableResult = TableDescription
    loadToMemory = return . ctStatus

instance Transaction CreateTable CreateTableResult

data DescribeTable
    = DescribeTable {
        dTableName :: T.Text
      }
    deriving (Show, Generic)
instance A.ToJSON DescribeTable where
    toJSON = A.genericToJSON $ dropOpt 1

-- | ServiceConfiguration: 'DdbConfiguration'
instance SignQuery DescribeTable where
    type ServiceConfiguration DescribeTable = DdbConfiguration
    signQuery = ddbSignQuery "DescribeTable"

newtype DescribeTableResult = DescribeTableResult { dtStatus :: TableDescription }
    deriving (Show, A.FromJSON)
-- ResponseConsumer can't be derived
instance ResponseConsumer r DescribeTableResult where
    type ResponseMetadata DescribeTableResult = DdbResponse
    responseConsumer _ _ = ddbResponseConsumer
instance AsMemoryResponse DescribeTableResult where
    type MemoryResponse DescribeTableResult = TableDescription
    loadToMemory = return . dtStatus

instance Transaction DescribeTable DescribeTableResult

data UpdateTable
    = UpdateTable {
        updateTableName                   :: T.Text
      , updateProvisionedThroughput       :: ProvisionedThroughput
      , updateGlobalSecondaryIndexUpdates :: [GlobalSecondaryIndexUpdate]
      }
    deriving (Show, Generic)
instance A.ToJSON UpdateTable where
    toJSON a = A.object
        $ "TableName" .= updateTableName a
        : "ProvisionedThroughput" .= updateProvisionedThroughput a
        : case updateGlobalSecondaryIndexUpdates a of
            [] -> []
            l -> [ "GlobalSecondaryIndexUpdates" .= l ]

-- | ServiceConfiguration: 'DdbConfiguration'
instance SignQuery UpdateTable where
    type ServiceConfiguration UpdateTable = DdbConfiguration
    signQuery = ddbSignQuery "UpdateTable"

newtype UpdateTableResult = UpdateTableResult { uStatus :: TableDescription }
    deriving (Show, A.FromJSON)
-- ResponseConsumer can't be derived
instance ResponseConsumer r UpdateTableResult where
    type ResponseMetadata UpdateTableResult = DdbResponse
    responseConsumer _ _ = ddbResponseConsumer
instance AsMemoryResponse UpdateTableResult where
    type MemoryResponse UpdateTableResult = TableDescription
    loadToMemory = return . uStatus

instance Transaction UpdateTable UpdateTableResult

data DeleteTable
    = DeleteTable {
        deleteTableName :: T.Text
      }
    deriving (Show, Generic)
instance A.ToJSON DeleteTable where
    toJSON = A.genericToJSON $ dropOpt 6

-- | ServiceConfiguration: 'DdbConfiguration'
instance SignQuery DeleteTable where
    type ServiceConfiguration DeleteTable = DdbConfiguration
    signQuery = ddbSignQuery "DeleteTable"

newtype DeleteTableResult = DeleteTableResult { dStatus :: TableDescription }
    deriving (Show, A.FromJSON)
-- ResponseConsumer can't be derived
instance ResponseConsumer r DeleteTableResult where
    type ResponseMetadata DeleteTableResult = DdbResponse
    responseConsumer _ _ = ddbResponseConsumer
instance AsMemoryResponse DeleteTableResult where
    type MemoryResponse DeleteTableResult = TableDescription
    loadToMemory = return . dStatus

instance Transaction DeleteTable DeleteTableResult

-- | TODO: currently this does not support restarting a cutoff query because of size.
data ListTables = ListTables
    deriving (Show)
instance A.ToJSON ListTables where
    toJSON _ = A.object []
-- | ServiceConfiguration: 'DdbConfiguration'
instance SignQuery ListTables where
    type ServiceConfiguration ListTables = DdbConfiguration
    signQuery = ddbSignQuery "ListTables"

newtype ListTablesResult
    = ListTablesResult {
        tableNames :: [T.Text]
      }
    deriving (Show, Generic)
instance A.FromJSON ListTablesResult where
    parseJSON = A.genericParseJSON capitalizeOpt
instance ResponseConsumer r ListTablesResult where
    type ResponseMetadata ListTablesResult = DdbResponse
    responseConsumer _ _ = ddbResponseConsumer
instance AsMemoryResponse ListTablesResult where
    type MemoryResponse ListTablesResult = [T.Text]
    loadToMemory = return . tableNames

instance Transaction ListTables ListTablesResult