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