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