File: DynamoDb.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 (134 lines) | stat: -rw-r--r-- 4,161 bytes parent folder | download
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
{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-}

module Main where

-------------------------------------------------------------------------------
import           Aws
import           Aws.DynamoDb.Commands
import           Aws.DynamoDb.Core
import           Control.Concurrent
import           Control.Monad
import           Control.Monad.Catch
import           Control.Monad.Trans.Resource
import           Control.Applicative
import           Data.Conduit
import           Data.Maybe
import qualified Data.Conduit.List     as C
import qualified Data.Text             as T
import           Network.HTTP.Conduit  (newManager, tlsManagerSettings)
-------------------------------------------------------------------------------

createTableAndWait :: IO ()
createTableAndWait = do
  let req0 = createTable "devel-1"
        [AttributeDefinition "name" AttrString]
        (HashOnly "name")
        (ProvisionedThroughput 1 1)
  resp0 <- runCommand req0
  print resp0

  print "Waiting for table to be created"
  threadDelay (30 * 1000000)

  let req1 = DescribeTable "devel-1"
  resp1 <- runCommand req1
  print resp1

data ExampleItem = ExampleItem {
      name :: T.Text
    , class_ :: T.Text
    , boolAttr :: Bool
    , oldBoolAttr :: Bool
    }
    deriving (Show)

instance ToDynItem ExampleItem where
    toItem (ExampleItem name class_ boolAttr oldBoolAttr) =
        item [ attr "name" name
             , attr "class" class_
             , attr "boolattr" boolAttr
             , attr "oldboolattr" (OldBool oldBoolAttr)
             ]

instance FromDynItem ExampleItem where
    parseItem x = ExampleItem <$> getAttr "name" x <*> getAttr "class" x <*> getAttr "boolattr" x <*> getAttr "oldboolattr" x

main :: IO ()
main = do
  cfg <- Aws.baseConfiguration

  createTableAndWait `catch` (\DdbError{} -> putStrLn "Table already exists")

  putStrLn "Putting an item..."

  let x = ExampleItem { name = "josh", class_ = "not-so-awesome",
                        boolAttr = False, oldBoolAttr = True }

  let req1 = (putItem "devel-1" (toItem x)) { piReturn = URAllOld
                                    , piRetCons =  RCTotal
                                    , piRetMet = RICMSize
                                    }


  resp1 <- runCommand req1
  print resp1

  putStrLn "Getting the item back..."

  let req2 = getItem "devel-1" (hk "name" "josh")
  resp2 <- runCommand req2
  print resp2

  let y = fromItem (fromMaybe (item []) $ girItem resp2) :: Either String ExampleItem
  print y

  print =<< runCommand
    (updateItem "devel-1" (hk "name" "josh") [au (Attribute "class" "awesome")])

  echo "Updating with false conditional."
  (print =<< runCommand
    (updateItem "devel-1" (hk "name" "josh") [au (Attribute "class" "awesomer")])
      { uiExpect = Conditions CondAnd [Condition "name" (DEq "john")] })
    `catch` (\ (e :: DdbError) -> echo ("Eating exception: " ++ show e))

  echo "Getting the item back..."
  print =<< runCommand req2


  echo "Updating with true conditional"
  print =<< runCommand
    (updateItem "devel-1" (hk "name" "josh") [au (Attribute "class" "awesomer"), au (attr "oldboolattr" False)])
      { uiExpect = Conditions CondAnd [Condition "name" (DEq "josh")] }

  echo "Getting the item back..."
  print =<< runCommand req2

  echo "Running a Query command..."
  print =<< runCommand (query "devel-1" (Slice (Attribute "name" "josh") Nothing))

  echo "Running a Scan command..."
  print =<< runCommand (scan "devel-1")

  echo "Filling table with several items..."
  forM_ [0..30] $ \ i -> do
    threadDelay 50000
    runCommand $ putItem "devel-1" $
      item [Attribute "name" (toValue $ T.pack ("lots-" ++ show i)), attrAs int "val" i]

  echo "Now paginating in increments of 5..."
  let q0 = (scan "devel-1") { sLimit = Just 5 }

  mgr <- newManager tlsManagerSettings
  xs <- runResourceT $ awsIteratedList cfg debugServiceConfig mgr q0 `connect` C.consume
  echo ("Pagination returned " ++ show (length xs) ++ " items")


runCommand r = do
    cfg <- Aws.baseConfiguration
    Aws.simpleAws cfg debugServiceConfig r

echo = putStrLn