File: Attributes.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 (204 lines) | stat: -rw-r--r-- 8,479 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
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
module Aws.SimpleDb.Commands.Attributes where

import           Aws.Core
import           Aws.SimpleDb.Core
import           Control.Applicative
import           Control.Monad
import           Data.Maybe
import           Prelude
import           Text.XML.Cursor            (($//), (&|))
import qualified Data.Text                  as T
import qualified Data.Text.Encoding         as T
import qualified Text.XML.Cursor            as Cu

data GetAttributes
    = GetAttributes {
        gaItemName :: T.Text
      , gaAttributeName :: Maybe T.Text
      , gaConsistentRead :: Bool
      , gaDomainName :: T.Text
      }
    deriving (Show)

data GetAttributesResponse
    = GetAttributesResponse {
        garAttributes :: [Attribute T.Text]
      }
    deriving (Show)

getAttributes :: T.Text -> T.Text -> GetAttributes
getAttributes item domain = GetAttributes { gaItemName = item, gaAttributeName = Nothing, gaConsistentRead = False, gaDomainName = domain }

-- | ServiceConfiguration: 'SdbConfiguration'
instance SignQuery GetAttributes where
    type ServiceConfiguration GetAttributes = SdbConfiguration
    signQuery GetAttributes{..}
        = sdbSignQuery $
            [("Action", "GetAttributes"), ("ItemName", T.encodeUtf8 gaItemName), ("DomainName", T.encodeUtf8 gaDomainName)] ++
            maybeToList (("AttributeName",) <$> T.encodeUtf8 <$> gaAttributeName) ++
            (guard gaConsistentRead >> [("ConsistentRead", awsTrue)])

instance ResponseConsumer r GetAttributesResponse where
    type ResponseMetadata GetAttributesResponse = SdbMetadata
    responseConsumer _ _
        = sdbResponseConsumer parse
        where parse cursor = do
                sdbCheckResponseType () "GetAttributesResponse" cursor
                attributes <- sequence $ cursor $// Cu.laxElement "Attribute" &| readAttribute
                return $ GetAttributesResponse attributes

instance Transaction GetAttributes GetAttributesResponse

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

data PutAttributes
    = PutAttributes {
        paItemName :: T.Text
      , paAttributes :: [Attribute SetAttribute]
      , paExpected :: [Attribute ExpectedAttribute]
      , paDomainName :: T.Text
      }
    deriving (Show)

data PutAttributesResponse
    = PutAttributesResponse
    deriving (Show)
             
putAttributes :: T.Text -> [Attribute SetAttribute] -> T.Text -> PutAttributes
putAttributes item attributes domain = PutAttributes { 
                                         paItemName = item
                                       , paAttributes = attributes
                                       , paExpected = []
                                       , paDomainName = domain 
                                       }
                                       
-- | ServiceConfiguration: 'SdbConfiguration'
instance SignQuery PutAttributes where
    type ServiceConfiguration PutAttributes = SdbConfiguration
    signQuery PutAttributes{..}
        = sdbSignQuery $ 
            [("Action", "PutAttributes"), ("ItemName", T.encodeUtf8 paItemName), ("DomainName", T.encodeUtf8 paDomainName)] ++
            queryList (attributeQuery setAttributeQuery) "Attribute" paAttributes ++
            queryList (attributeQuery expectedAttributeQuery) "Expected" paExpected

instance ResponseConsumer r PutAttributesResponse where
    type ResponseMetadata PutAttributesResponse = SdbMetadata
    responseConsumer _ _
        = sdbResponseConsumer $ sdbCheckResponseType PutAttributesResponse "PutAttributesResponse"

instance Transaction PutAttributes PutAttributesResponse

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

data DeleteAttributes
    = DeleteAttributes {
        daItemName :: T.Text
      , daAttributes :: [Attribute DeleteAttribute]
      , daExpected :: [Attribute ExpectedAttribute]
      , daDomainName :: T.Text
      }
    deriving (Show)

data DeleteAttributesResponse
    = DeleteAttributesResponse
    deriving (Show)
             
deleteAttributes :: T.Text -> [Attribute DeleteAttribute] -> T.Text -> DeleteAttributes
deleteAttributes item attributes domain = DeleteAttributes { 
                                         daItemName = item
                                       , daAttributes = attributes
                                       , daExpected = []
                                       , daDomainName = domain 
                                       }
                                       
-- | ServiceConfiguration: 'SdbConfiguration'
instance SignQuery DeleteAttributes where
    type ServiceConfiguration DeleteAttributes = SdbConfiguration
    signQuery DeleteAttributes{..}
        = sdbSignQuery $ 
            [("Action", "DeleteAttributes"), ("ItemName", T.encodeUtf8 daItemName), ("DomainName", T.encodeUtf8 daDomainName)] ++
            queryList (attributeQuery deleteAttributeQuery) "Attribute" daAttributes ++
            queryList (attributeQuery expectedAttributeQuery) "Expected" daExpected

instance ResponseConsumer r DeleteAttributesResponse where
    type ResponseMetadata DeleteAttributesResponse = SdbMetadata
    responseConsumer _ _
        = sdbResponseConsumer $ sdbCheckResponseType DeleteAttributesResponse "DeleteAttributesResponse"

instance Transaction DeleteAttributes DeleteAttributesResponse

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

data BatchPutAttributes
    = BatchPutAttributes {
        bpaItems :: [Item [Attribute SetAttribute]]
      , bpaDomainName :: T.Text
      }
    deriving (Show)

data BatchPutAttributesResponse
    = BatchPutAttributesResponse
    deriving (Show)
             
batchPutAttributes :: [Item [Attribute SetAttribute]] -> T.Text -> BatchPutAttributes
batchPutAttributes items domain = BatchPutAttributes { bpaItems = items, bpaDomainName = domain }

-- | ServiceConfiguration: 'SdbConfiguration'
instance SignQuery BatchPutAttributes where
    type ServiceConfiguration BatchPutAttributes = SdbConfiguration
    signQuery BatchPutAttributes{..}
        = sdbSignQuery $ 
            [("Action", "BatchPutAttributes")
            , ("DomainName", T.encodeUtf8 bpaDomainName)] ++
            queryList (itemQuery $ queryList (attributeQuery setAttributeQuery) "Attribute") "Item" bpaItems

instance ResponseConsumer r BatchPutAttributesResponse where
    type ResponseMetadata BatchPutAttributesResponse = SdbMetadata
    responseConsumer _ _
        = sdbResponseConsumer $ sdbCheckResponseType BatchPutAttributesResponse "BatchPutAttributesResponse"

instance Transaction BatchPutAttributes BatchPutAttributesResponse

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

data BatchDeleteAttributes
    = BatchDeleteAttributes {
        bdaItems :: [Item [Attribute DeleteAttribute]]
      , bdaDomainName :: T.Text
      }
    deriving (Show)

data BatchDeleteAttributesResponse
    = BatchDeleteAttributesResponse
    deriving (Show)
             
batchDeleteAttributes :: [Item [Attribute DeleteAttribute]] -> T.Text -> BatchDeleteAttributes
batchDeleteAttributes items domain = BatchDeleteAttributes { bdaItems = items, bdaDomainName = domain }

-- | ServiceConfiguration: 'SdbConfiguration'
instance SignQuery BatchDeleteAttributes where
    type ServiceConfiguration BatchDeleteAttributes = SdbConfiguration
    signQuery BatchDeleteAttributes{..}
        = sdbSignQuery $ 
            [("Action", "BatchDeleteAttributes")
            , ("DomainName", T.encodeUtf8 bdaDomainName)] ++
            queryList (itemQuery $ queryList (attributeQuery deleteAttributeQuery) "Attribute") "Item" bdaItems

instance ResponseConsumer r BatchDeleteAttributesResponse where
    type ResponseMetadata BatchDeleteAttributesResponse = SdbMetadata
    responseConsumer _ _
        = sdbResponseConsumer $ sdbCheckResponseType BatchDeleteAttributesResponse "BatchDeleteAttributesResponse"

instance Transaction BatchDeleteAttributes BatchDeleteAttributesResponse

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