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