r1341@opsdev009 (orig r71050): mcslee | 2007-11-21 00:43:35 -0800
[amiethrift.git] / lib / st / thrift.st
blob445534cbffc52b102adc1288198c93514fdc76a7
1 SystemOrganization addCategory: #Thrift!
2 SystemOrganization addCategory: #'Thrift-Protocol'!
3 SystemOrganization addCategory: #'Thrift-Transport'!
5 Error subclass: #TError
6         instanceVariableNames: 'code'
7         classVariableNames: ''
8         poolDictionaries: ''
9         category: 'Thrift'!
11 !TError class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:28'!
12 signalWithCode: anInteger
13         self new code: anInteger; signal! !
15 !TError methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:28'!
16 code
17         ^ code! !
19 !TError methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:28'!
20 code: anInteger
21         code := anInteger! !
23 TError subclass: #TProtocolError
24         instanceVariableNames: ''
25         classVariableNames: ''
26         poolDictionaries: ''
27         category: 'Thrift-Protocol'!
29 !TProtocolError class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 18:39'!
30 badVersion
31         ^ 4! !
33 !TProtocolError class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 18:39'!
34 invalidData
35         ^ 1! !
37 !TProtocolError class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 18:39'!
38 negativeSize
39         ^ 2! !
41 !TProtocolError class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 18:40'!
42 sizeLimit
43         ^ 3! !
45 !TProtocolError class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 18:40'!
46 unknown
47         ^ 0! !
49 TError subclass: #TTransportError
50         instanceVariableNames: ''
51         classVariableNames: ''
52         poolDictionaries: ''
53         category: 'Thrift-Transport'!
55 TTransportError subclass: #TTransportClosedError
56         instanceVariableNames: ''
57         classVariableNames: ''
58         poolDictionaries: ''
59         category: 'Thrift-Transport'!
61 Object subclass: #TClient
62         instanceVariableNames: 'iprot oprot seqid remoteSeqid'
63         classVariableNames: ''
64         poolDictionaries: ''
65         category: 'Thrift'!
67 !TClient class methodsFor: 'as yet unclassified' stamp: 'pc 11/7/2007 06:00'!
68 binaryOnHost: 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! !
75 !TClient methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 23:03'!
76 inProtocol: aProtocol
77         iprot := aProtocol.
78         oprot ifNil: [oprot := aProtocol]! !
80 !TClient methodsFor: 'as yet unclassified' stamp: 'pc 10/26/2007 04:28'!
81 nextSeqid
82         ^ seqid
83                 ifNil: [seqid := 0]
84                 ifNotNil: [seqid := seqid + 1]! !
86 !TClient methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:51'!
87 outProtocol: aProtocol
88         oprot := aProtocol! !
90 !TClient methodsFor: 'as yet unclassified' stamp: 'pc 10/28/2007 15:32'!
91 validateRemoteMessage: aMsg
92         remoteSeqid
93                 ifNil: [remoteSeqid := aMsg seqid]
94                 ifNotNil:
95                         [(remoteSeqid + 1) = aMsg seqid ifFalse:
96                                 [TProtocolError signal: 'Bad seqid: ', aMsg seqid asString,
97                                                         '; wanted: ', remoteSeqid asString].
98                         remoteSeqid := aMsg seqid]! !
100 Object subclass: #TField
101         instanceVariableNames: 'name type id'
102         classVariableNames: ''
103         poolDictionaries: ''
104         category: 'Thrift-Protocol'!
106 !TField methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:05'!
108         ^ id ifNil: [0]! !
110 !TField methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:44'!
111 id: anInteger
112         id := anInteger! !
114 !TField methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:04'!
115 name
116         ^ name ifNil: ['']! !
118 !TField methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:44'!
119 name: anObject
120         name := anObject! !
122 !TField methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:05'!
123 type
124         ^ type ifNil: [TType stop]! !
126 !TField methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:44'!
127 type: anInteger
128         type := anInteger! !
130 Object subclass: #TMessage
131         instanceVariableNames: 'name seqid type'
132         classVariableNames: ''
133         poolDictionaries: ''
134         category: 'Thrift-Protocol'!
136 TMessage subclass: #TCallMessage
137         instanceVariableNames: ''
138         classVariableNames: ''
139         poolDictionaries: ''
140         category: 'Thrift-Protocol'!
142 !TCallMessage methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:53'!
143 type
144         ^ 1! !
146 !TMessage methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:05'!
147 name
148         ^ name ifNil: ['']! !
150 !TMessage methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:35'!
151 name: aString
152         name := aString! !
154 !TMessage methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:05'!
155 seqid
156         ^ seqid ifNil: [0]! !
158 !TMessage methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:35'!
159 seqid: anInteger
160         seqid := anInteger! !
162 !TMessage methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:06'!
163 type
164         ^ type ifNil: [0]! !
166 !TMessage methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:35'!
167 type: anInteger
168         type := anInteger! !
170 Object subclass: #TProtocol
171         instanceVariableNames: 'transport'
172         classVariableNames: ''
173         poolDictionaries: ''
174         category: 'Thrift-Protocol'!
176 TProtocol subclass: #TBinaryProtocol
177         instanceVariableNames: ''
178         classVariableNames: ''
179         poolDictionaries: ''
180         category: 'Thrift-Protocol'!
182 !TBinaryProtocol methodsFor: 'reading' stamp: 'pc 11/1/2007 04:24'!
183 intFromByteArray: 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! !
189 !TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 18:46'!
190 readBool
191         ^ self readByte isZero not! !
193 !TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/25/2007 00:02'!
194 readByte
195         ^ (self transport read: 1) first! !
197 !TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/28/2007 16:24'!
198 readDouble
199         | val |
200         val := Float new: 2.
201         ^ val basicAt: 1 put: (self readRawInt: 4);
202                 basicAt: 2 put: (self readRawInt: 4);
203                 yourself! !
205 !TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 20:02'!
206 readFieldBegin
207         | field |
208         field := TField new type: self readByte.
210         ^ field type = TType stop
211                 ifTrue: [field]
212                 ifFalse: [field id: self readI16; yourself]! !
214 !TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:15'!
215 readI16
216         ^ self readInt: 2! !
218 !TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:20'!
219 readI32
220         ^ self readInt: 4! !
222 !TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:20'!
223 readI64
224         ^ self readInt: 8! !
226 !TBinaryProtocol methodsFor: 'reading' stamp: 'pc 11/1/2007 02:35'!
227 readInt: 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]! !
235 !TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:57'!
236 readListBegin
237         ^ TList new
238                 elemType: self readByte;
239                 size: self readI32! !
241 !TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:58'!
242 readMapBegin
243         ^ TMap new
244                 keyType: self readByte;
245                 valueType: self readByte;
246                 size: self readI32! !
248 !TBinaryProtocol methodsFor: 'reading' stamp: 'pc 11/1/2007 04:22'!
249 readMessageBegin
250         | version |
251         version := self readI32.
253         (version bitAnd: self versionMask) = self version1
254                 ifFalse: [TProtocolError signalWithCode: TProtocolError badVersion].
256         ^ TMessage new
257                 type: (version bitAnd: 16r000000FF);
258                 name: self readString;
259                 seqid: self readI32! !
261 !TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/28/2007 16:24'!
262 readRawInt: size
263         ^ self intFromByteArray: (transport read: size)! !
265 !TBinaryProtocol methodsFor: 'reading' stamp: 'pc 11/1/2007 00:59'!
266 readSetBegin
267         "element type, size"
268         ^ TSet new
269                 elemType: self readByte;
270                 size: self readI32! !
272 !TBinaryProtocol methodsFor: 'reading' stamp: 'pc 10/26/2007 04:48'!
273 readString
274         ^ (transport read: self readI32) asString! !
276 !TBinaryProtocol methodsFor: 'reading' stamp: 'pc 11/1/2007 04:22'!
277 unsignedInt: val size: size
278         ^ 0 - ((val - 1) bitXor: ((2 raisedTo: (size * 8)) - 1))! !
280 !TBinaryProtocol methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:13'!
281 version1
282         ^ 16r80010000 ! !
284 !TBinaryProtocol methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 18:01'!
285 versionMask
286         ^ 16rFFFF0000! !
288 !TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 18:35'!
289 write: aString
290         transport write: aString! !
292 !TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:23'!
293 writeBool: bool
294         bool ifTrue: [self writeByte: 1]
295                 ifFalse: [self writeByte: 0]! !
297 !TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/26/2007 09:31'!
298 writeByte: aNumber
299         aNumber > 16rFF ifTrue: [TError signal: 'writeByte too big'].
300         transport write: (Array with: aNumber)! !
302 !TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/28/2007 16:16'!
303 writeDouble: aDouble
304         self writeI32: (aDouble basicAt: 1);
305                 writeI32: (aDouble basicAt: 2)! !
307 !TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:56'!
308 writeField: aField
309         self writeByte: aField type;
310                 writeI16: aField id! !
312 !TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/25/2007 00:01'!
313 writeFieldBegin: aField
314         self writeByte: aField type.
315         self writeI16: aField id! !
317 !TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 18:04'!
318 writeFieldStop
319         self writeByte: TType stop! !
321 !TBinaryProtocol methodsFor: 'writing' stamp: 'pc 11/1/2007 02:06'!
322 writeI16: i16
323         self writeInt: i16 size: 2! !
325 !TBinaryProtocol methodsFor: 'writing' stamp: 'pc 11/1/2007 02:06'!
326 writeI32: i32
327         self writeInt: i32 size: 4! !
329 !TBinaryProtocol methodsFor: 'writing' stamp: 'pc 11/1/2007 02:06'!
330 writeI64: i64
331         self writeInt: i64 size: 8! !
333 !TBinaryProtocol methodsFor: 'writing' stamp: 'pc 11/1/2007 04:23'!
334 writeInt: val size: size
335         1 to: size do: [:n | self writeByte: ((val bitShift: (size negated + n) * 8) bitAnd: 16rFF)]! !
337 !TBinaryProtocol methodsFor: 'writing' stamp: 'pc 11/1/2007 00:48'!
338 writeListBegin: aList
339         self writeByte: aList elemType; writeI32: aList size! !
341 !TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:55'!
342 writeMapBegin: aMap
343         self writeByte: aMap keyType;
344                 writeByte: aMap valueType;
345                 writeI32: aMap size! !
347 !TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 20:36'!
348 writeMessageBegin: msg
349         self writeI32: (self version1 bitOr: msg type);
350                 writeString: msg name;
351                 writeI32: msg seqid! !
353 !TBinaryProtocol methodsFor: 'writing' stamp: 'pc 11/1/2007 00:56'!
354 writeSetBegin: aSet
355         self writeByte: aSet elemType; writeI32: aSet size! !
357 !TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 18:35'!
358 writeString: aString
359         self writeI32: aString size;
360                 write: aString! !
362 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
363 readBool! !
365 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
366 readByte! !
368 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
369 readDouble! !
371 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
372 readFieldBegin! !
374 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
375 readFieldEnd! !
377 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
378 readI16! !
380 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
381 readI32! !
383 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
384 readI64! !
386 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
387 readListBegin! !
389 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
390 readListEnd! !
392 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
393 readMapBegin! !
395 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
396 readMapEnd! !
398 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:39'!
399 readMessageBegin! !
401 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:39'!
402 readMessageEnd! !
404 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
405 readSetBegin! !
407 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
408 readSetEnd! !
410 !TProtocol methodsFor: 'reading' stamp: 'pc 10/25/2007 16:10'!
411 readSimpleType: 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].! !
420 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
421 readString! !
423 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
424 readStructBegin
425         ! !
427 !TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
428 readStructEnd! !
430 !TProtocol methodsFor: 'reading' stamp: 'pc 10/26/2007 21:34'!
431 skip: 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].
462         self error: 'Unknown type'! !
464 !TProtocol methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 23:02'!
465 transport
466         ^ transport! !
468 !TProtocol methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:28'!
469 transport: aTransport
470         transport := aTransport! !
472 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
473 writeBool: aBool! !
475 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
476 writeByte: aByte! !
478 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:38'!
479 writeDouble: aFloat! !
481 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:38'!
482 writeFieldBegin: aField! !
484 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
485 writeFieldEnd! !
487 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
488 writeFieldStop! !
490 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
491 writeI16: i16! !
493 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
494 writeI32: i32! !
496 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
497 writeI64: i64! !
499 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:39'!
500 writeListBegin: aList! !
502 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
503 writeListEnd! !
505 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:39'!
506 writeMapBegin: aMap! !
508 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
509 writeMapEnd! !
511 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:36'!
512 writeMessageBegin! !
514 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:36'!
515 writeMessageEnd! !
517 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:39'!
518 writeSetBegin: aSet! !
520 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
521 writeSetEnd! !
523 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:38'!
524 writeString: aString! !
526 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:38'!
527 writeStructBegin: aStruct! !
529 !TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
530 writeStructEnd! !
532 Object subclass: #TResult
533         instanceVariableNames: 'success oprot iprot exception'
534         classVariableNames: ''
535         poolDictionaries: ''
536         category: 'Thrift'!
538 !TResult methodsFor: 'as yet unclassified' stamp: 'pc 10/26/2007 21:35'!
539 exception
540         ^ exception! !
542 !TResult methodsFor: 'as yet unclassified' stamp: 'pc 10/26/2007 21:35'!
543 exception: anError
544         exception := anError! !
546 !TResult methodsFor: 'as yet unclassified' stamp: 'pc 10/26/2007 14:43'!
547 success
548         ^ success! !
550 !TResult methodsFor: 'as yet unclassified' stamp: 'pc 10/26/2007 14:43'!
551 success: anObject
552         success := anObject! !
554 Object subclass: #TSizedObject
555         instanceVariableNames: 'size'
556         classVariableNames: ''
557         poolDictionaries: ''
558         category: 'Thrift-Protocol'!
560 TSizedObject subclass: #TList
561         instanceVariableNames: 'elemType'
562         classVariableNames: ''
563         poolDictionaries: ''
564         category: 'Thrift-Protocol'!
566 !TList methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:04'!
567 elemType
568         ^ elemType ifNil: [TType stop]! !
570 !TList methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:42'!
571 elemType: anInteger
572         elemType := anInteger! !
574 TList subclass: #TSet
575         instanceVariableNames: ''
576         classVariableNames: ''
577         poolDictionaries: ''
578         category: 'Thrift-Protocol'!
580 TSizedObject subclass: #TMap
581         instanceVariableNames: 'keyType valueType'
582         classVariableNames: ''
583         poolDictionaries: ''
584         category: 'Thrift-Protocol'!
586 !TMap methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:04'!
587 keyType
588         ^ keyType ifNil: [TType stop]! !
590 !TMap methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:45'!
591 keyType: anInteger
592         keyType := anInteger! !
594 !TMap methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:04'!
595 valueType
596         ^ valueType ifNil: [TType stop]! !
598 !TMap methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:45'!
599 valueType: anInteger
600         valueType := anInteger! !
602 !TSizedObject methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 20:03'!
603 size
604         ^ size ifNil: [0]! !
606 !TSizedObject methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 20:06'!
607 size: anInteger
608         size := anInteger! !
610 Object subclass: #TSocket
611         instanceVariableNames: 'host port stream'
612         classVariableNames: ''
613         poolDictionaries: ''
614         category: 'Thrift-Transport'!
616 !TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:34'!
617 close
618         self isOpen ifTrue: [stream close]! !
620 !TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:23'!
621 connect
622         ^ (self socketStream openConnectionToHost:
623                 (NetNameResolver addressForName: host) port: port)
624                         timeout: 180;
625                         binary;
626                         yourself! !
628 !TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 20:35'!
629 flush
630         stream flush! !
632 !TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:08'!
633 host: aString
634         host := aString! !
636 !TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 20:34'!
637 isOpen
638         ^ stream isNil not
639                 and: [stream socket isConnected]
640                 and: [stream socket isOtherEndClosed not]! !
642 !TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:22'!
643 open
644         stream := self connect! !
646 !TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:09'!
647 port: anInteger
648         port := anInteger! !
650 !TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:17'!
651 read: 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]! !
659 !TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:18'!
660 socketStream
661         ^ Smalltalk at: #FastSocketStream ifAbsent: [SocketStream] ! !
663 !TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:17'!
664 write: aCollection
665         [stream nextPutAll: aCollection]
666                 on: ConnectionClosed
667                 do: [TTransportClosedError signal]! !
669 Object subclass: #TStruct
670         instanceVariableNames: 'name'
671         classVariableNames: ''
672         poolDictionaries: ''
673         category: 'Thrift-Protocol'!
675 !TStruct methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:47'!
676 name
677         ^ name! !
679 !TStruct methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:47'!
680 name: aString
681         name := aString! !
683 Object subclass: #TTransport
684         instanceVariableNames: ''
685         classVariableNames: ''
686         poolDictionaries: ''
687         category: 'Thrift-Transport'!
689 !TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:18'!
690 close
691         self subclassResponsibility! !
693 !TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:22'!
694 flush
695         self subclassResponsibility! !
697 !TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:18'!
698 isOpen
699         self subclassResponsibility! !
701 !TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:18'!
702 open
703         self subclassResponsibility! !
705 !TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:18'!
706 read: anInteger
707         self subclassResponsibility! !
709 !TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:22'!
710 readAll: anInteger
711         ^ String streamContents: [:str |
712                 [str size < anInteger] whileTrue:
713                         [str nextPutAll: (self read: anInteger - str size)]]! !
715 !TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:22'!
716 write: aString
717         self subclassResponsibility! !
719 Object subclass: #TType
720         instanceVariableNames: ''
721         classVariableNames: ''
722         poolDictionaries: ''
723         category: 'Thrift'!
725 !TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:03'!
726 bool
727         ^ 2! !
729 !TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:03'!
730 byte
731         ^ 3! !
733 !TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/25/2007 15:55'!
734 codeOf: aTypeName
735         self typeMap do: [:each | each first = aTypeName ifTrue: [^ each second]].
736         ^ nil! !
738 !TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:03'!
739 double
740         ^ 4! !
742 !TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
744         ^ 6! !
746 !TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
748         ^ 8! !
750 !TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
752         ^ 10! !
754 !TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
755 list
756         ^ 15! !
758 !TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
760         ^ 13! !
762 !TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/25/2007 15:56'!
763 nameOf: aTypeCode
764         self typeMap do: [:each | each second = aTypeCode ifTrue: [^ each first]].
765         ^ nil! !
767 !TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
769         ^ 14! !
771 !TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:03'!
772 stop
773         ^ 0! !
775 !TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
776 string
777         ^ 11! !
779 !TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
780 struct
781         ^ 12! !
783 !TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/25/2007 15:51'!
784 typeMap
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))! !
788 !TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:03'!
789 void
790         ^ 1! !