blob: 445534cbffc52b102adc1288198c93514fdc76a7 [file] [log] [blame]
Mark Sleeefd37f12007-11-20 05:13:09 +00001SystemOrganization addCategory: #Thrift!
2SystemOrganization addCategory: #'Thrift-Protocol'!
Mark Sleeefd37f12007-11-20 05:13:09 +00003SystemOrganization addCategory: #'Thrift-Transport'!
4
5Error subclass: #TError
6 instanceVariableNames: 'code'
7 classVariableNames: ''
8 poolDictionaries: ''
9 category: 'Thrift'!
10
11!TError class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:28'!
12signalWithCode: anInteger
13 self new code: anInteger; signal! !
14
15!TError methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:28'!
16code
17 ^ code! !
18
19!TError methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:28'!
20code: anInteger
21 code := anInteger! !
22
23TError subclass: #TProtocolError
24 instanceVariableNames: ''
25 classVariableNames: ''
26 poolDictionaries: ''
27 category: 'Thrift-Protocol'!
28
29!TProtocolError class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 18:39'!
30badVersion
31 ^ 4! !
32
33!TProtocolError class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 18:39'!
34invalidData
35 ^ 1! !
36
37!TProtocolError class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 18:39'!
38negativeSize
39 ^ 2! !
40
41!TProtocolError class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 18:40'!
42sizeLimit
43 ^ 3! !
44
45!TProtocolError class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 18:40'!
46unknown
47 ^ 0! !
48
49TError subclass: #TTransportError
50 instanceVariableNames: ''
51 classVariableNames: ''
52 poolDictionaries: ''
53 category: 'Thrift-Transport'!
54
55TTransportError subclass: #TTransportClosedError
56 instanceVariableNames: ''
57 classVariableNames: ''
58 poolDictionaries: ''
59 category: 'Thrift-Transport'!
60
Mark Sleeefd37f12007-11-20 05:13:09 +000061Object subclass: #TClient
62 instanceVariableNames: 'iprot oprot seqid remoteSeqid'
63 classVariableNames: ''
64 poolDictionaries: ''
65 category: 'Thrift'!
66
Mark Sleebd588222007-11-21 08:43:35 +000067!TClient class methodsFor: 'as yet unclassified' stamp: 'pc 11/7/2007 06:00'!
68binaryOnHost: aString port: anInteger
69 | sock |
70 sock := TSocket new host: aString; port: anInteger; open; yourself.
71 ^ self new
72 inProtocol: (TBinaryProtocol new transport: sock);
73 yourself! !
Mark Sleeefd37f12007-11-20 05:13:09 +000074
75!TClient methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 23:03'!
76inProtocol: aProtocol
77 iprot := aProtocol.
78 oprot ifNil: [oprot := aProtocol]! !
79
80!TClient methodsFor: 'as yet unclassified' stamp: 'pc 10/26/2007 04:28'!
81nextSeqid
82 ^ seqid
83 ifNil: [seqid := 0]
84 ifNotNil: [seqid := seqid + 1]! !
85
86!TClient methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:51'!
87outProtocol: aProtocol
88 oprot := aProtocol! !
89
90!TClient methodsFor: 'as yet unclassified' stamp: 'pc 10/28/2007 15:32'!
91validateRemoteMessage: aMsg
92 remoteSeqid
93 ifNil: [remoteSeqid := aMsg seqid]
Mark Sleebd588222007-11-21 08:43:35 +000094 ifNotNil:
Mark Sleeefd37f12007-11-20 05:13:09 +000095 [(remoteSeqid + 1) = aMsg seqid ifFalse:
96 [TProtocolError signal: 'Bad seqid: ', aMsg seqid asString,
97 '; wanted: ', remoteSeqid asString].
98 remoteSeqid := aMsg seqid]! !
99
Mark Sleeefd37f12007-11-20 05:13:09 +0000100Object subclass: #TField
101 instanceVariableNames: 'name type id'
102 classVariableNames: ''
103 poolDictionaries: ''
104 category: 'Thrift-Protocol'!
105
106!TField methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:05'!
107id
108 ^ id ifNil: [0]! !
109
110!TField methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:44'!
111id: anInteger
112 id := anInteger! !
113
114!TField methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:04'!
115name
116 ^ name ifNil: ['']! !
117
118!TField methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:44'!
119name: anObject
120 name := anObject! !
121
122!TField methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:05'!
123type
124 ^ type ifNil: [TType stop]! !
125
126!TField methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:44'!
127type: anInteger
128 type := anInteger! !
129
130Object subclass: #TMessage
131 instanceVariableNames: 'name seqid type'
132 classVariableNames: ''
133 poolDictionaries: ''
134 category: 'Thrift-Protocol'!
135
136TMessage subclass: #TCallMessage
137 instanceVariableNames: ''
138 classVariableNames: ''
139 poolDictionaries: ''
140 category: 'Thrift-Protocol'!
141
142!TCallMessage methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:53'!
143type
144 ^ 1! !
145
146!TMessage methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:05'!
147name
148 ^ name ifNil: ['']! !
149
150!TMessage methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:35'!
151name: aString
152 name := aString! !
153
154!TMessage methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:05'!
155seqid
156 ^ seqid ifNil: [0]! !
157
158!TMessage methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:35'!
159seqid: anInteger
160 seqid := anInteger! !
161
162!TMessage methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:06'!
163type
164 ^ type ifNil: [0]! !
165
166!TMessage methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:35'!
167type: anInteger
168 type := anInteger! !
169
170Object subclass: #TProtocol
171 instanceVariableNames: 'transport'
172 classVariableNames: ''
173 poolDictionaries: ''
174 category: 'Thrift-Protocol'!
175
176TProtocol subclass: #TBinaryProtocol
177 instanceVariableNames: ''
178 classVariableNames: ''
179 poolDictionaries: ''
180 category: 'Thrift-Protocol'!
181
182!TBinaryProtocol methodsFor: 'reading' stamp: 'pc 11/1/2007 04:24'!
183intFromByteArray: buf
184 | vals |
185 vals := Array new: buf size.
186 1 to: buf size do: [:n | vals at: n put: ((buf at: n) bitShift: (buf size - n) * 8)].
187 ^ vals sum! !
188
189!TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 18:46'!
190readBool
191 ^ self readByte isZero not! !
192
193!TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/25/2007 00:02'!
194readByte
195 ^ (self transport read: 1) first! !
196
197!TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/28/2007 16:24'!
198readDouble
199 | val |
200 val := Float new: 2.
201 ^ val basicAt: 1 put: (self readRawInt: 4);
202 basicAt: 2 put: (self readRawInt: 4);
203 yourself! !
204
205!TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 20:02'!
206readFieldBegin
207 | field |
208 field := TField new type: self readByte.
Mark Sleebd588222007-11-21 08:43:35 +0000209
Mark Sleeefd37f12007-11-20 05:13:09 +0000210 ^ field type = TType stop
211 ifTrue: [field]
212 ifFalse: [field id: self readI16; yourself]! !
213
214!TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:15'!
215readI16
216 ^ self readInt: 2! !
217
218!TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:20'!
219readI32
220 ^ self readInt: 4! !
221
222!TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:20'!
223readI64
224 ^ self readInt: 8! !
225
226!TBinaryProtocol methodsFor: 'reading' stamp: 'pc 11/1/2007 02:35'!
227readInt: size
228 | buf val |
229 buf := transport read: size.
230 val := self intFromByteArray: buf.
231 ^ buf first > 16r7F
232 ifTrue: [self unsignedInt: val size: size]
233 ifFalse: [val]! !
234
235!TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:57'!
236readListBegin
237 ^ TList new
238 elemType: self readByte;
239 size: self readI32! !
240
241!TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:58'!
242readMapBegin
243 ^ TMap new
244 keyType: self readByte;
245 valueType: self readByte;
246 size: self readI32! !
247
248!TBinaryProtocol methodsFor: 'reading' stamp: 'pc 11/1/2007 04:22'!
249readMessageBegin
250 | version |
251 version := self readI32.
Mark Sleebd588222007-11-21 08:43:35 +0000252
Mark Sleeefd37f12007-11-20 05:13:09 +0000253 (version bitAnd: self versionMask) = self version1
254 ifFalse: [TProtocolError signalWithCode: TProtocolError badVersion].
Mark Sleebd588222007-11-21 08:43:35 +0000255
Mark Sleeefd37f12007-11-20 05:13:09 +0000256 ^ TMessage new
257 type: (version bitAnd: 16r000000FF);
258 name: self readString;
259 seqid: self readI32! !
260
261!TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/28/2007 16:24'!
262readRawInt: size
263 ^ self intFromByteArray: (transport read: size)! !
264
265!TBinaryProtocol methodsFor: 'reading' stamp: 'pc 11/1/2007 00:59'!
266readSetBegin
267 "element type, size"
268 ^ TSet new
269 elemType: self readByte;
270 size: self readI32! !
271
272!TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/26/2007 04:48'!
273readString
274 ^ (transport read: self readI32) asString! !
275
276!TBinaryProtocol methodsFor: 'reading' stamp: 'pc 11/1/2007 04:22'!
277unsignedInt: val size: size
278 ^ 0 - ((val - 1) bitXor: ((2 raisedTo: (size * 8)) - 1))! !
279
280!TBinaryProtocol methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:13'!
281version1
282 ^ 16r80010000 ! !
283
284!TBinaryProtocol methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 18:01'!
285versionMask
286 ^ 16rFFFF0000! !
287
288!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 18:35'!
289write: aString
290 transport write: aString! !
291
292!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:23'!
293writeBool: bool
294 bool ifTrue: [self writeByte: 1]
295 ifFalse: [self writeByte: 0]! !
296
297!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/26/2007 09:31'!
298writeByte: aNumber
299 aNumber > 16rFF ifTrue: [TError signal: 'writeByte too big'].
300 transport write: (Array with: aNumber)! !
301
302!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/28/2007 16:16'!
303writeDouble: aDouble
304 self writeI32: (aDouble basicAt: 1);
305 writeI32: (aDouble basicAt: 2)! !
306
307!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:56'!
308writeField: aField
309 self writeByte: aField type;
310 writeI16: aField id! !
311
312!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/25/2007 00:01'!
313writeFieldBegin: aField
314 self writeByte: aField type.
315 self writeI16: aField id! !
316
317!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 18:04'!
318writeFieldStop
319 self writeByte: TType stop! !
320
321!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 11/1/2007 02:06'!
322writeI16: i16
323 self writeInt: i16 size: 2! !
324
325!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 11/1/2007 02:06'!
326writeI32: i32
327 self writeInt: i32 size: 4! !
328
329!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 11/1/2007 02:06'!
330writeI64: i64
331 self writeInt: i64 size: 8! !
332
333!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 11/1/2007 04:23'!
334writeInt: val size: size
335 1 to: size do: [:n | self writeByte: ((val bitShift: (size negated + n) * 8) bitAnd: 16rFF)]! !
336
337!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 11/1/2007 00:48'!
338writeListBegin: aList
339 self writeByte: aList elemType; writeI32: aList size! !
340
341!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:55'!
342writeMapBegin: aMap
343 self writeByte: aMap keyType;
344 writeByte: aMap valueType;
345 writeI32: aMap size! !
346
347!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 20:36'!
348writeMessageBegin: msg
349 self writeI32: (self version1 bitOr: msg type);
350 writeString: msg name;
351 writeI32: msg seqid! !
352
353!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 11/1/2007 00:56'!
354writeSetBegin: aSet
355 self writeByte: aSet elemType; writeI32: aSet size! !
356
357!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 18:35'!
358writeString: aString
359 self writeI32: aString size;
360 write: aString! !
361
362!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
363readBool! !
364
365!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
366readByte! !
367
368!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
369readDouble! !
370
371!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
372readFieldBegin! !
373
374!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
375readFieldEnd! !
376
377!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
378readI16! !
379
380!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
381readI32! !
382
383!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
384readI64! !
385
386!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
387readListBegin! !
388
389!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
390readListEnd! !
391
392!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
393readMapBegin! !
394
395!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
396readMapEnd! !
397
398!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:39'!
399readMessageBegin! !
400
401!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:39'!
402readMessageEnd! !
403
404!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
405readSetBegin! !
406
407!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
408readSetEnd! !
409
410!TProtocol methodsFor: 'reading' stamp: 'pc 10/25/2007 16:10'!
411readSimpleType: aType
412 aType = TType bool ifTrue: [^ self readBool].
413 aType = TType byte ifTrue: [^ self readByte].
414 aType = TType double ifTrue: [^ self readDouble].
415 aType = TType i16 ifTrue: [^ self readI16].
416 aType = TType i32 ifTrue: [^ self readI32].
417 aType = TType i64 ifTrue: [^ self readI64].
418 aType = TType list ifTrue: [^ self readBool].! !
419
420!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
421readString! !
422
423!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
424readStructBegin
425 ! !
426
427!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
428readStructEnd! !
429
430!TProtocol methodsFor: 'reading' stamp: 'pc 10/26/2007 21:34'!
431skip: aType
432 aType = TType stop ifTrue: [^ self].
433 aType = TType bool ifTrue: [^ self readBool].
434 aType = TType byte ifTrue: [^ self readByte].
435 aType = TType i16 ifTrue: [^ self readI16].
436 aType = TType i32 ifTrue: [^ self readI32].
437 aType = TType i64 ifTrue: [^ self readI64].
438 aType = TType string ifTrue: [^ self readString].
439 aType = TType double ifTrue: [^ self readDouble].
440 aType = TType struct ifTrue:
441 [| field |
442 self readStructBegin.
443 [(field := self readFieldBegin) type = TType stop] whileFalse:
444 [self skip: field type. self readFieldEnd].
445 ^ self readStructEnd].
446 aType = TType map ifTrue:
447 [| map |
448 map := self readMapBegin.
449 map size timesRepeat: [self skip: map keyType. self skip: map valueType].
450 ^ self readMapEnd].
451 aType = TType list ifTrue:
452 [| list |
453 list := self readListBegin.
454 list size timesRepeat: [self skip: list elemType].
455 ^ self readListEnd].
456 aType = TType set ifTrue:
457 [| set |
458 set := self readSetBegin.
459 set size timesRepeat: [self skip: set elemType].
460 ^ self readSetEnd].
Mark Sleebd588222007-11-21 08:43:35 +0000461
Mark Sleeefd37f12007-11-20 05:13:09 +0000462 self error: 'Unknown type'! !
463
464!TProtocol methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 23:02'!
465transport
466 ^ transport! !
467
468!TProtocol methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:28'!
469transport: aTransport
470 transport := aTransport! !
471
472!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
473writeBool: aBool! !
474
475!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
476writeByte: aByte! !
477
478!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:38'!
479writeDouble: aFloat! !
480
481!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:38'!
482writeFieldBegin: aField! !
483
484!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
485writeFieldEnd! !
486
487!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
488writeFieldStop! !
489
490!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
491writeI16: i16! !
492
493!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
494writeI32: i32! !
495
496!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
497writeI64: i64! !
498
499!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:39'!
500writeListBegin: aList! !
501
502!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
503writeListEnd! !
504
505!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:39'!
506writeMapBegin: aMap! !
507
508!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
509writeMapEnd! !
510
511!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:36'!
512writeMessageBegin! !
513
514!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:36'!
515writeMessageEnd! !
516
517!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:39'!
518writeSetBegin: aSet! !
519
520!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
521writeSetEnd! !
522
523!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:38'!
524writeString: aString! !
525
526!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:38'!
527writeStructBegin: aStruct! !
528
529!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
530writeStructEnd! !
531
532Object subclass: #TResult
533 instanceVariableNames: 'success oprot iprot exception'
534 classVariableNames: ''
535 poolDictionaries: ''
536 category: 'Thrift'!
537
538!TResult methodsFor: 'as yet unclassified' stamp: 'pc 10/26/2007 21:35'!
539exception
540 ^ exception! !
541
542!TResult methodsFor: 'as yet unclassified' stamp: 'pc 10/26/2007 21:35'!
543exception: anError
544 exception := anError! !
545
546!TResult methodsFor: 'as yet unclassified' stamp: 'pc 10/26/2007 14:43'!
547success
548 ^ success! !
549
550!TResult methodsFor: 'as yet unclassified' stamp: 'pc 10/26/2007 14:43'!
551success: anObject
552 success := anObject! !
553
554Object subclass: #TSizedObject
555 instanceVariableNames: 'size'
556 classVariableNames: ''
557 poolDictionaries: ''
558 category: 'Thrift-Protocol'!
559
560TSizedObject subclass: #TList
561 instanceVariableNames: 'elemType'
562 classVariableNames: ''
563 poolDictionaries: ''
564 category: 'Thrift-Protocol'!
565
566!TList methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:04'!
567elemType
568 ^ elemType ifNil: [TType stop]! !
569
570!TList methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:42'!
571elemType: anInteger
572 elemType := anInteger! !
573
574TList subclass: #TSet
575 instanceVariableNames: ''
576 classVariableNames: ''
577 poolDictionaries: ''
578 category: 'Thrift-Protocol'!
579
580TSizedObject subclass: #TMap
581 instanceVariableNames: 'keyType valueType'
582 classVariableNames: ''
583 poolDictionaries: ''
584 category: 'Thrift-Protocol'!
585
586!TMap methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:04'!
587keyType
588 ^ keyType ifNil: [TType stop]! !
589
590!TMap methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:45'!
591keyType: anInteger
592 keyType := anInteger! !
593
594!TMap methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:04'!
595valueType
596 ^ valueType ifNil: [TType stop]! !
597
598!TMap methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:45'!
599valueType: anInteger
600 valueType := anInteger! !
601
602!TSizedObject methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 20:03'!
603size
604 ^ size ifNil: [0]! !
605
606!TSizedObject methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 20:06'!
607size: anInteger
608 size := anInteger! !
609
610Object subclass: #TSocket
611 instanceVariableNames: 'host port stream'
612 classVariableNames: ''
613 poolDictionaries: ''
614 category: 'Thrift-Transport'!
615
616!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:34'!
617close
618 self isOpen ifTrue: [stream close]! !
619
620!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:23'!
621connect
622 ^ (self socketStream openConnectionToHost:
623 (NetNameResolver addressForName: host) port: port)
624 timeout: 180;
625 binary;
626 yourself! !
627
628!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 20:35'!
629flush
630 stream flush! !
631
632!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:08'!
633host: aString
634 host := aString! !
635
636!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 20:34'!
637isOpen
638 ^ stream isNil not
639 and: [stream socket isConnected]
640 and: [stream socket isOtherEndClosed not]! !
641
642!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:22'!
643open
644 stream := self connect! !
645
646!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:09'!
647port: anInteger
648 port := anInteger! !
649
650!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:17'!
651read: size
652 | data |
653 [data := stream next: size.
654 data isEmpty ifTrue: [TTransportError signal: 'Could not read ', size asString, ' bytes'].
655 ^ data]
656 on: ConnectionClosed
657 do: [TTransportClosedError signal]! !
658
659!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:18'!
660socketStream
661 ^ Smalltalk at: #FastSocketStream ifAbsent: [SocketStream] ! !
662
663!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:17'!
664write: aCollection
665 [stream nextPutAll: aCollection]
666 on: ConnectionClosed
667 do: [TTransportClosedError signal]! !
668
669Object subclass: #TStruct
670 instanceVariableNames: 'name'
671 classVariableNames: ''
672 poolDictionaries: ''
673 category: 'Thrift-Protocol'!
674
675!TStruct methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:47'!
676name
677 ^ name! !
678
679!TStruct methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:47'!
680name: aString
681 name := aString! !
682
Mark Sleeefd37f12007-11-20 05:13:09 +0000683Object subclass: #TTransport
684 instanceVariableNames: ''
685 classVariableNames: ''
686 poolDictionaries: ''
687 category: 'Thrift-Transport'!
688
689!TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:18'!
690close
691 self subclassResponsibility! !
692
693!TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:22'!
694flush
695 self subclassResponsibility! !
696
697!TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:18'!
698isOpen
699 self subclassResponsibility! !
700
701!TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:18'!
702open
703 self subclassResponsibility! !
704
705!TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:18'!
706read: anInteger
707 self subclassResponsibility! !
708
709!TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:22'!
710readAll: anInteger
711 ^ String streamContents: [:str |
712 [str size < anInteger] whileTrue:
713 [str nextPutAll: (self read: anInteger - str size)]]! !
714
715!TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:22'!
716write: aString
717 self subclassResponsibility! !
718
719Object subclass: #TType
720 instanceVariableNames: ''
721 classVariableNames: ''
722 poolDictionaries: ''
723 category: 'Thrift'!
724
725!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:03'!
726bool
727 ^ 2! !
728
729!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:03'!
730byte
731 ^ 3! !
732
733!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/25/2007 15:55'!
734codeOf: aTypeName
735 self typeMap do: [:each | each first = aTypeName ifTrue: [^ each second]].
736 ^ nil! !
737
738!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:03'!
739double
740 ^ 4! !
741
742!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
743i16
744 ^ 6! !
745
746!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
747i32
748 ^ 8! !
749
750!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
751i64
752 ^ 10! !
753
754!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
755list
756 ^ 15! !
757
758!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
759map
760 ^ 13! !
761
762!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/25/2007 15:56'!
763nameOf: aTypeCode
764 self typeMap do: [:each | each second = aTypeCode ifTrue: [^ each first]].
765 ^ nil! !
766
767!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
768set
769 ^ 14! !
770
771!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:03'!
772stop
773 ^ 0! !
774
775!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
776string
777 ^ 11! !
778
779!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
780struct
781 ^ 12! !
782
783!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/25/2007 15:51'!
784typeMap
785 ^ #((bool 2) (byte 3) (double 4) (i16 6) (i32 8) (i64 10) (list 15)
786 (map 13) (set 15) (stop 0) (string 11) (struct 12) (void 1))! !
787
788!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:03'!
789void
790 ^ 1! !