blob: 8ff5fa9d56f219100f97eba3704d4c980508c1dd [file] [log] [blame]
iproctor9a41a0c2007-07-16 21:59:24 +00001exception Break;;
2exception Thrift_error;;
3exception Field_empty of string;;
4
5class t_exn =
6object
7 val mutable message = ""
8 method get_message = message
9 method set_message s = message <- s
10end;;
11
12exception TExn of t_exn;;
13
14
15
16
17module Transport =
18struct
19 type exn_type =
20 | UNKNOWN
21 | NOT_OPEN
22 | ALREADY_OPEN
23 | TIMED_OUT
24 | END_OF_FILE;;
25
26 class exn =
27 object
28 inherit t_exn
29 val mutable typ = UNKNOWN
30 method get_type = typ
31 method set_type t = typ <- t
32 end
33 exception TTransportExn of exn
34 let raise_TTransportExn message typ =
35 let e = new exn in
36 e#set_message message;
37 e#set_type typ;
38 raise (TTransportExn e)
39
40 class virtual t =
41 object (self)
42 method virtual isOpen : bool
43 method virtual opn : unit
44 method virtual close : unit
45 method virtual read : string -> int -> int -> int
46 method readAll buf off len =
47 let got = ref 0 in
48 let ret = ref 0 in
49 while !got < len do
50 ret := self#read buf (off+(!got)) (len - (!got));
51 if !ret <= 0 then
52 let e = new exn in
53 e#set_message "Cannot read. Remote side has closed.";
54 raise (TTransportExn e)
55 else ();
56 got := !got + !ret
57 done;
58 !got
59 method virtual write : string -> int -> int -> unit
60 method virtual flush : unit
61 end
62
63 class factory =
64 object
65 method getTransport (t : t) = t
66 end
67
68 class virtual server_t =
69 object (self)
70 method virtual listen : unit
71 method accept = self#acceptImpl
72 method virtual close : unit
73 method virtual acceptImpl : t
74 end
75
76end;;
77
78
79
80module Protocol =
81struct
82 type t_type =
83 | T_STOP
84 | T_VOID
85 | T_BOOL
86 | T_BYTE
87 | T_I08
88 | T_I16
89 | T_I32
90 | T_U64
91 | T_I64
92 | T_DOUBLE
93 | T_STRING
94 | T_UTF7
95 | T_STRUCT
96 | T_MAP
97 | T_SET
98 | T_LIST
99 | T_UTF8
100 | T_UTF16
101
102 let t_type_to_i = function
103 T_STOP -> 0
104 | T_VOID -> 1
105 | T_BOOL -> 2
106 | T_BYTE -> 3
107 | T_I08 -> 3
108 | T_I16 -> 6
109 | T_I32 -> 8
110 | T_U64 -> 9
111 | T_I64 -> 10
112 | T_DOUBLE -> 4
113 | T_STRING -> 11
114 | T_UTF7 -> 11
115 | T_STRUCT -> 12
116 | T_MAP -> 13
117 | T_SET -> 14
118 | T_LIST -> 15
119 | T_UTF8 -> 16
120 | T_UTF16 -> 17
121
122 let t_type_of_i = function
123 0 -> T_STOP
124 | 1 -> T_VOID
125 | 2 -> T_BOOL
126 | 3 -> T_BYTE
127 | 6-> T_I16
128 | 8 -> T_I32
129 | 9 -> T_U64
130 | 10 -> T_I64
131 | 4 -> T_DOUBLE
132 | 11 -> T_STRING
133 | 12 -> T_STRUCT
134 | 13 -> T_MAP
135 | 14 -> T_SET
136 | 15 -> T_LIST
137 | 16 -> T_UTF8
138 | 17 -> T_UTF16
139 | _ -> raise Thrift_error
140
141 type message_type =
142 | CALL
143 | REPLY
144 | EXCEPTION
145
146 let message_type_to_i = function
147 | CALL -> 1
148 | REPLY -> 2
149 | EXCEPTION -> 3
150
151 let message_type_of_i = function
152 | 1 -> CALL
153 | 2 -> REPLY
154 | 3 -> EXCEPTION
155 | _ -> raise Thrift_error
156
157 class virtual t (trans: Transport.t) =
158 object (self)
159 val mutable trans_ = trans
160 method getTransport = trans_
161 (* writing methods *)
162 method virtual writeMessageBegin : string * message_type * int -> unit
163 method virtual writeMessageEnd : unit
164 method virtual writeStructBegin : string -> unit
165 method virtual writeStructEnd : unit
166 method virtual writeFieldBegin : string * t_type * int -> unit
167 method virtual writeFieldEnd : unit
168 method virtual writeFieldStop : unit
169 method virtual writeMapBegin : t_type * t_type * int -> unit
170 method virtual writeMapEnd : unit
171 method virtual writeListBegin : t_type * int -> unit
172 method virtual writeListEnd : unit
173 method virtual writeSetBegin : t_type * int -> unit
174 method virtual writeSetEnd : unit
175 method virtual writeBool : bool -> unit
176 method virtual writeByte : int -> unit
177 method virtual writeI16 : int -> unit
178 method virtual writeI32 : int -> unit
179 method virtual writeI64 : Int64.t -> unit
180 method virtual writeDouble : float -> unit
181 method virtual writeString : string -> unit
182 method virtual writeBinary : string -> unit
183 (* reading methods *)
184 method virtual readMessageBegin : string * message_type * int
185 method virtual readMessageEnd : unit
186 method virtual readStructBegin : string
187 method virtual readStructEnd : unit
188 method virtual readFieldBegin : string * t_type * int
189 method virtual readFieldEnd : unit
190 method virtual readMapBegin : t_type * t_type * int
191 method virtual readMapEnd : unit
192 method virtual readListBegin : t_type * int
193 method virtual readListEnd : unit
194 method virtual readSetBegin : t_type * int
195 method virtual readSetEnd : unit
196 method virtual readBool : bool
197 method virtual readByte : int
198 method virtual readI16 : int
199 method virtual readI32: int
200 method virtual readI64 : Int64.t
201 method virtual readDouble : float
202 method virtual readString : string
203 method virtual readBinary : string
204 (* skippage *)
205 method skip typ =
206 match typ with
207 | T_STOP -> ()
208 | T_VOID -> ()
209 | T_BOOL -> ignore self#readBool
210 | T_BYTE
211 | T_I08 -> ignore self#readByte
212 | T_I16 -> ignore self#readI16
213 | T_I32 -> ignore self#readI32
214 | T_U64
215 | T_I64 -> ignore self#readI64
216 | T_DOUBLE -> ignore self#readDouble
217 | T_STRING -> ignore self#readString
218 | T_UTF7 -> ()
219 | T_STRUCT -> ignore ((ignore self#readStructBegin);
220 (try
221 while true do
222 let (_,t,_) = self#readFieldBegin in
223 if t = T_STOP then
224 raise Break
225 else
226 (self#skip t;
227 self#readFieldEnd)
228 done
229 with Break -> ());
230 self#readStructEnd)
231 | T_MAP -> ignore (let (k,v,s) = self#readMapBegin in
232 for i=0 to s do
233 self#skip k;
234 self#skip v;
235 done;
236 self#readMapEnd)
237 | T_SET -> ignore (let (t,s) = self#readSetBegin in
238 for i=0 to s do
239 self#skip t
240 done;
241 self#readSetEnd)
242 | T_LIST -> ignore (let (t,s) = self#readListBegin in
243 for i=0 to s do
244 self#skip t
245 done;
246 self#readListEnd)
247 | T_UTF8 -> ()
248 | T_UTF16 -> ()
249 end
250
251 class virtual factory =
252 object
253 method virtual getProtocol : Transport.t -> t
254 end
iproctord4de1e92007-07-24 19:47:55 +0000255
256 type exn_type =
257 | UNKNOWN
258 | INVALID_DATA
259 | NEGATIVE_SIZE
260 | SIZE_LIMIT
261 | BAD_VERSION
262
263 exception TProtocolExn of exn_type * string;;
iproctor9a41a0c2007-07-16 21:59:24 +0000264
265end;;
266
267
268module Processor =
269struct
270 class virtual t =
271 object
272 method virtual process : Protocol.t -> Protocol.t -> bool
273 end;;
274
275 class factory (processor : t) =
276 object
277 val processor_ = processor
278 method getProcessor (trans : Transport.t) = processor_
279 end;;
280end
281
282
283
284module Application_Exn =
285struct
286 type typ=
287 | UNKNOWN
288 | UNKNOWN_METHOD
289 | INVALID_MESSAGE_TYPE
290 | WRONG_METHOD_NAME
291 | BAD_SEQUENCE_ID
292 | MISSING_RESULT
293
294 let typ_of_i = function
295 0 -> UNKNOWN
296 | 1 -> UNKNOWN_METHOD
297 | 2 -> INVALID_MESSAGE_TYPE
298 | 3 -> WRONG_METHOD_NAME
299 | 4 -> BAD_SEQUENCE_ID
300 | 5 -> MISSING_RESULT
301 | _ -> raise Thrift_error;;
302 let typ_to_i = function
303 | UNKNOWN -> 0
304 | UNKNOWN_METHOD -> 1
305 | INVALID_MESSAGE_TYPE -> 2
306 | WRONG_METHOD_NAME -> 3
307 | BAD_SEQUENCE_ID -> 4
308 | MISSING_RESULT -> 5
309
310 class t =
311 object (self)
312 inherit t_exn
313 val mutable typ = UNKNOWN
314 method get_type = typ
315 method set_type t = typ <- t
316 method write (oprot : Protocol.t) =
317 oprot#writeStructBegin "TApplicationExeception";
318 if self#get_message != "" then
319 (oprot#writeFieldBegin ("message",Protocol.T_STRING, 1);
320 oprot#writeString self#get_message;
321 oprot#writeFieldEnd)
322 else ();
323 oprot#writeFieldBegin ("type",Protocol.T_I32,2);
324 oprot#writeI32 (typ_to_i typ);
325 oprot#writeFieldEnd;
326 oprot#writeFieldStop;
327 oprot#writeStructEnd
328 end;;
329
330 let create typ msg =
331 let e = new t in
332 e#set_type typ;
333 e#set_message msg;
334 e
335
336 let read (iprot : Protocol.t) =
337 let msg = ref "" in
338 let typ = ref 0 in
339 iprot#readStructBegin;
340 (try
341 while true do
342 let (name,ft,id) =iprot#readFieldBegin in
343 if ft = Protocol.T_STOP then
344 raise Break
345 else ();
346 (match id with
347 | 1 -> (if ft = Protocol.T_STRING then
348 msg := (iprot#readString)
349 else
350 iprot#skip ft)
351 | 2 -> (if ft = Protocol.T_I32 then
352 typ := iprot#readI32
353 else
354 iprot#skip ft)
355 | _ -> iprot#skip ft);
356 iprot#readFieldEnd
357 done
358 with Break -> ());
359 iprot#readStructEnd;
360 let e = new t in
361 e#set_type (typ_of_i !typ);
362 e#set_message !msg;
363 e;;
364
365 exception E of t
366end;;