blob: 6883539ffb65cefbc777f11b6e5dfe19420b12c8 [file] [log] [blame]
Gavin McDonald0b75e1a2010-10-28 02:12:01 +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
20SystemOrganization addCategory: #Thrift!
21SystemOrganization addCategory: #'Thrift-Protocol'!
22SystemOrganization 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
80Object subclass: #TClient
81 instanceVariableNames: 'iprot oprot seqid remoteSeqid'
82 classVariableNames: ''
83 poolDictionaries: ''
84 category: 'Thrift'!
85
86!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! !
93
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]
113 ifNotNil:
114 [(remoteSeqid + 1) = aMsg seqid ifFalse:
115 [TProtocolError signal: 'Bad seqid: ', aMsg seqid asString,
116 '; wanted: ', remoteSeqid asString].
117 remoteSeqid := aMsg seqid]! !
118
119Object 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.
228
229 ^ 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.
271
272 (version bitAnd: self versionMask) = self version1
273 ifFalse: [TProtocolError signalWithCode: TProtocolError badVersion].
274
275 ^ 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 02/07/2009 19:00'!
292readString
293readString
294 | sz |
295 sz := self readI32.
296 ^ sz > 0 ifTrue: [(transport read: sz) asString] ifFalse: ['']! !
297
298!TBinaryProtocol methodsFor: 'reading' stamp: 'pc 11/1/2007 04:22'!
299unsignedInt: val size: size
300 ^ 0 - ((val - 1) bitXor: ((2 raisedTo: (size * 8)) - 1))! !
301
302!TBinaryProtocol methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:13'!
303version1
304 ^ 16r80010000 ! !
305
306!TBinaryProtocol methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 18:01'!
307versionMask
308 ^ 16rFFFF0000! !
309
310!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 18:35'!
311write: aString
312 transport write: aString! !
313
314!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:23'!
315writeBool: bool
316 bool ifTrue: [self writeByte: 1]
317 ifFalse: [self writeByte: 0]! !
318
319!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/26/2007 09:31'!
320writeByte: aNumber
321 aNumber > 16rFF ifTrue: [TError signal: 'writeByte too big'].
322 transport write: (Array with: aNumber)! !
323
324!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/28/2007 16:16'!
325writeDouble: aDouble
326 self writeI32: (aDouble basicAt: 1);
327 writeI32: (aDouble basicAt: 2)! !
328
329!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:56'!
330writeField: aField
331 self writeByte: aField type;
332 writeI16: aField id! !
333
334!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/25/2007 00:01'!
335writeFieldBegin: aField
336 self writeByte: aField type.
337 self writeI16: aField id! !
338
339!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 18:04'!
340writeFieldStop
341 self writeByte: TType stop! !
342
343!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 11/1/2007 02:06'!
344writeI16: i16
345 self writeInt: i16 size: 2! !
346
347!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 11/1/2007 02:06'!
348writeI32: i32
349 self writeInt: i32 size: 4! !
350
351!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 11/1/2007 02:06'!
352writeI64: i64
353 self writeInt: i64 size: 8! !
354
355!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 11/1/2007 04:23'!
356writeInt: val size: size
357 1 to: size do: [:n | self writeByte: ((val bitShift: (size negated + n) * 8) bitAnd: 16rFF)]! !
358
359!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 11/1/2007 00:48'!
360writeListBegin: aList
361 self writeByte: aList elemType; writeI32: aList size! !
362
363!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:55'!
364writeMapBegin: aMap
365 self writeByte: aMap keyType;
366 writeByte: aMap valueType;
367 writeI32: aMap size! !
368
369!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 20:36'!
370writeMessageBegin: msg
371 self writeI32: (self version1 bitOr: msg type);
372 writeString: msg name;
373 writeI32: msg seqid! !
374
375!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 11/1/2007 00:56'!
376writeSetBegin: aSet
377 self writeByte: aSet elemType; writeI32: aSet size! !
378
379!TBinaryProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 18:35'!
380writeString: aString
381 self writeI32: aString size;
382 write: aString! !
383
384!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
385readBool! !
386
387!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
388readByte! !
389
390!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
391readDouble! !
392
393!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
394readFieldBegin! !
395
396!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
397readFieldEnd! !
398
399!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
400readI16! !
401
402!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
403readI32! !
404
405!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
406readI64! !
407
408!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
409readListBegin! !
410
411!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
412readListEnd! !
413
414!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
415readMapBegin! !
416
417!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
418readMapEnd! !
419
420!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:39'!
421readMessageBegin! !
422
423!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:39'!
424readMessageEnd! !
425
426!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
427readSetBegin! !
428
429!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
430readSetEnd! !
431
432!TProtocol methodsFor: 'reading' stamp: 'pc 10/25/2007 16:10'!
433readSimpleType: aType
434 aType = TType bool ifTrue: [^ self readBool].
435 aType = TType byte ifTrue: [^ self readByte].
436 aType = TType double ifTrue: [^ self readDouble].
437 aType = TType i16 ifTrue: [^ self readI16].
438 aType = TType i32 ifTrue: [^ self readI32].
439 aType = TType i64 ifTrue: [^ self readI64].
440 aType = TType list ifTrue: [^ self readBool].! !
441
442!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
443readString! !
444
445!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
446readStructBegin
447 ! !
448
449!TProtocol methodsFor: 'reading' stamp: 'pc 10/24/2007 19:40'!
450readStructEnd! !
451
452!TProtocol methodsFor: 'reading' stamp: 'pc 10/26/2007 21:34'!
453skip: aType
454 aType = TType stop ifTrue: [^ self].
455 aType = TType bool ifTrue: [^ self readBool].
456 aType = TType byte ifTrue: [^ self readByte].
457 aType = TType i16 ifTrue: [^ self readI16].
458 aType = TType i32 ifTrue: [^ self readI32].
459 aType = TType i64 ifTrue: [^ self readI64].
460 aType = TType string ifTrue: [^ self readString].
461 aType = TType double ifTrue: [^ self readDouble].
462 aType = TType struct ifTrue:
463 [| field |
464 self readStructBegin.
465 [(field := self readFieldBegin) type = TType stop] whileFalse:
466 [self skip: field type. self readFieldEnd].
467 ^ self readStructEnd].
468 aType = TType map ifTrue:
469 [| map |
470 map := self readMapBegin.
471 map size timesRepeat: [self skip: map keyType. self skip: map valueType].
472 ^ self readMapEnd].
473 aType = TType list ifTrue:
474 [| list |
475 list := self readListBegin.
476 list size timesRepeat: [self skip: list elemType].
477 ^ self readListEnd].
478 aType = TType set ifTrue:
479 [| set |
480 set := self readSetBegin.
481 set size timesRepeat: [self skip: set elemType].
482 ^ self readSetEnd].
483
484 self error: 'Unknown type'! !
485
486!TProtocol methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 23:02'!
487transport
488 ^ transport! !
489
490!TProtocol methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:28'!
491transport: aTransport
492 transport := aTransport! !
493
494!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
495writeBool: aBool! !
496
497!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
498writeByte: aByte! !
499
500!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:38'!
501writeDouble: aFloat! !
502
503!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:38'!
504writeFieldBegin: aField! !
505
506!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
507writeFieldEnd! !
508
509!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
510writeFieldStop! !
511
512!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
513writeI16: i16! !
514
515!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
516writeI32: i32! !
517
518!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
519writeI64: i64! !
520
521!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:39'!
522writeListBegin: aList! !
523
524!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
525writeListEnd! !
526
527!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:39'!
528writeMapBegin: aMap! !
529
530!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
531writeMapEnd! !
532
533!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:36'!
534writeMessageBegin! !
535
536!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:36'!
537writeMessageEnd! !
538
539!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:39'!
540writeSetBegin: aSet! !
541
542!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
543writeSetEnd! !
544
545!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:38'!
546writeString: aString! !
547
548!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:38'!
549writeStructBegin: aStruct! !
550
551!TProtocol methodsFor: 'writing' stamp: 'pc 10/24/2007 19:37'!
552writeStructEnd! !
553
554Object subclass: #TResult
555 instanceVariableNames: 'success oprot iprot exception'
556 classVariableNames: ''
557 poolDictionaries: ''
558 category: 'Thrift'!
559
560!TResult methodsFor: 'as yet unclassified' stamp: 'pc 10/26/2007 21:35'!
561exception
562 ^ exception! !
563
564!TResult methodsFor: 'as yet unclassified' stamp: 'pc 10/26/2007 21:35'!
565exception: anError
566 exception := anError! !
567
568!TResult methodsFor: 'as yet unclassified' stamp: 'pc 10/26/2007 14:43'!
569success
570 ^ success! !
571
572!TResult methodsFor: 'as yet unclassified' stamp: 'pc 10/26/2007 14:43'!
573success: anObject
574 success := anObject! !
575
576Object subclass: #TSizedObject
577 instanceVariableNames: 'size'
578 classVariableNames: ''
579 poolDictionaries: ''
580 category: 'Thrift-Protocol'!
581
582TSizedObject subclass: #TList
583 instanceVariableNames: 'elemType'
584 classVariableNames: ''
585 poolDictionaries: ''
586 category: 'Thrift-Protocol'!
587
588!TList methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:04'!
589elemType
590 ^ elemType ifNil: [TType stop]! !
591
592!TList methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:42'!
593elemType: anInteger
594 elemType := anInteger! !
595
596TList subclass: #TSet
597 instanceVariableNames: ''
598 classVariableNames: ''
599 poolDictionaries: ''
600 category: 'Thrift-Protocol'!
601
602TSizedObject subclass: #TMap
603 instanceVariableNames: 'keyType valueType'
604 classVariableNames: ''
605 poolDictionaries: ''
606 category: 'Thrift-Protocol'!
607
608!TMap methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:04'!
609keyType
610 ^ keyType ifNil: [TType stop]! !
611
612!TMap methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:45'!
613keyType: anInteger
614 keyType := anInteger! !
615
616!TMap methodsFor: 'accessing' stamp: 'pc 10/24/2007 20:04'!
617valueType
618 ^ valueType ifNil: [TType stop]! !
619
620!TMap methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:45'!
621valueType: anInteger
622 valueType := anInteger! !
623
624!TSizedObject methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 20:03'!
625size
626 ^ size ifNil: [0]! !
627
628!TSizedObject methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 20:06'!
629size: anInteger
630 size := anInteger! !
631
632Object subclass: #TSocket
633 instanceVariableNames: 'host port stream'
634 classVariableNames: ''
635 poolDictionaries: ''
636 category: 'Thrift-Transport'!
637
638!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:34'!
639close
640 self isOpen ifTrue: [stream close]! !
641
642!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:23'!
643connect
644 ^ (self socketStream openConnectionToHost:
645 (NetNameResolver addressForName: host) port: port)
646 timeout: 180;
647 binary;
648 yourself! !
649
650!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 20:35'!
651flush
652 stream flush! !
653
654!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:08'!
655host: aString
656 host := aString! !
657
658!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 20:34'!
659isOpen
660 ^ stream isNil not
661 and: [stream socket isConnected]
662 and: [stream socket isOtherEndClosed not]! !
663
664!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:22'!
665open
666 stream := self connect! !
667
668!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:09'!
669port: anInteger
670 port := anInteger! !
671
672!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:17'!
673read: size
674 | data |
675 [data := stream next: size.
676 data isEmpty ifTrue: [TTransportError signal: 'Could not read ', size asString, ' bytes'].
677 ^ data]
678 on: ConnectionClosed
679 do: [TTransportClosedError signal]! !
680
681!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:18'!
682socketStream
683 ^ Smalltalk at: #FastSocketStream ifAbsent: [SocketStream] ! !
684
685!TSocket methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 22:17'!
686write: aCollection
687 [stream nextPutAll: aCollection]
688 on: ConnectionClosed
689 do: [TTransportClosedError signal]! !
690
691Object subclass: #TStruct
692 instanceVariableNames: 'name'
693 classVariableNames: ''
694 poolDictionaries: ''
695 category: 'Thrift-Protocol'!
696
697!TStruct methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:47'!
698name
699 ^ name! !
700
701!TStruct methodsFor: 'accessing' stamp: 'pc 10/24/2007 19:47'!
702name: aString
703 name := aString! !
704
705Object subclass: #TTransport
706 instanceVariableNames: ''
707 classVariableNames: ''
708 poolDictionaries: ''
709 category: 'Thrift-Transport'!
710
711!TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:18'!
712close
713 self subclassResponsibility! !
714
715!TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:22'!
716flush
717 self subclassResponsibility! !
718
719!TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:18'!
720isOpen
721 self subclassResponsibility! !
722
723!TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:18'!
724open
725 self subclassResponsibility! !
726
727!TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:18'!
728read: anInteger
729 self subclassResponsibility! !
730
731!TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:22'!
732readAll: anInteger
733 ^ String streamContents: [:str |
734 [str size < anInteger] whileTrue:
735 [str nextPutAll: (self read: anInteger - str size)]]! !
736
737!TTransport methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:22'!
738write: aString
739 self subclassResponsibility! !
740
741Object subclass: #TType
742 instanceVariableNames: ''
743 classVariableNames: ''
744 poolDictionaries: ''
745 category: 'Thrift'!
746
747!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:03'!
748bool
749 ^ 2! !
750
751!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:03'!
752byte
753 ^ 3! !
754
755!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/25/2007 15:55'!
756codeOf: aTypeName
757 self typeMap do: [:each | each first = aTypeName ifTrue: [^ each second]].
758 ^ nil! !
759
760!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:03'!
761double
762 ^ 4! !
763
764!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
765i16
766 ^ 6! !
767
768!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
769i32
770 ^ 8! !
771
772!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
773i64
774 ^ 10! !
775
776!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
777list
778 ^ 15! !
779
780!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
781map
782 ^ 13! !
783
784!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/25/2007 15:56'!
785nameOf: aTypeCode
786 self typeMap do: [:each | each second = aTypeCode ifTrue: [^ each first]].
787 ^ nil! !
788
789!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
790set
791 ^ 14! !
792
793!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:03'!
794stop
795 ^ 0! !
796
797!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
798string
799 ^ 11! !
800
801!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:04'!
802struct
803 ^ 12! !
804
805!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/25/2007 15:51'!
806typeMap
807 ^ #((bool 2) (byte 3) (double 4) (i16 6) (i32 8) (i64 10) (list 15)
808 (map 13) (set 15) (stop 0) (string 11) (struct 12) (void 1))! !
809
810!TType class methodsFor: 'as yet unclassified' stamp: 'pc 10/24/2007 17:03'!
811void
812 ^ 1! !