blob: 0d164704657678dc544fcae6128fb85dfe08f4f2 [file] [log] [blame]
David Reissea2cba82009-03-30 21:35:00 +00001(*
2 Licensed to the Apache Software Foundation (ASF) under one
3 or more contributor license agreements. See the NOTICE file
4 distributed with this work for additional information
5 regarding copyright ownership. The ASF licenses this file
6 to you under the Apache License, Version 2.0 (the
7 "License"); you may not use this file except in compliance
8 with the License. You may obtain a copy of the License at
9
10 http://www.apache.org/licenses/LICENSE-2.0
11
12 Unless required by applicable law or agreed to in writing,
13 software distributed under the License is distributed on an
14 "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
15 KIND, either express or implied. See the License for the
16 specific language governing permissions and limitations
17 under the License.
18*)
19
iproctor9a41a0c2007-07-16 21:59:24 +000020exception Break;;
21exception Thrift_error;;
22exception Field_empty of string;;
23
David Reiss0c90f6f2008-02-06 22:18:40 +000024class t_exn =
iproctor9a41a0c2007-07-16 21:59:24 +000025object
26 val mutable message = ""
27 method get_message = message
28 method set_message s = message <- s
29end;;
30
iproctor9a41a0c2007-07-16 21:59:24 +000031module Transport =
32struct
David Reiss0c90f6f2008-02-06 22:18:40 +000033 type exn_type =
iproctor9a41a0c2007-07-16 21:59:24 +000034 | UNKNOWN
35 | NOT_OPEN
36 | ALREADY_OPEN
37 | TIMED_OUT
38 | END_OF_FILE;;
39
iproctore470aa32007-08-10 20:48:12 +000040 exception E of exn_type * string
iproctor9a41a0c2007-07-16 21:59:24 +000041
42 class virtual t =
43 object (self)
44 method virtual isOpen : bool
45 method virtual opn : unit
46 method virtual close : unit
47 method virtual read : string -> int -> int -> int
48 method readAll buf off len =
49 let got = ref 0 in
50 let ret = ref 0 in
51 while !got < len do
52 ret := self#read buf (off+(!got)) (len - (!got));
53 if !ret <= 0 then
iproctore470aa32007-08-10 20:48:12 +000054 raise (E (UNKNOWN, "Cannot read. Remote side has closed."));
iproctor9a41a0c2007-07-16 21:59:24 +000055 got := !got + !ret
56 done;
57 !got
58 method virtual write : string -> int -> int -> unit
59 method virtual flush : unit
60 end
61
62 class factory =
63 object
64 method getTransport (t : t) = t
65 end
66
67 class virtual server_t =
68 object (self)
69 method virtual listen : unit
70 method accept = self#acceptImpl
71 method virtual close : unit
72 method virtual acceptImpl : t
73 end
David Reiss0c90f6f2008-02-06 22:18:40 +000074
iproctor9a41a0c2007-07-16 21:59:24 +000075end;;
76
77
78
79module Protocol =
80struct
David Reiss0c90f6f2008-02-06 22:18:40 +000081 type t_type =
82 | T_STOP
83 | T_VOID
iproctor9a41a0c2007-07-16 21:59:24 +000084 | T_BOOL
85 | T_BYTE
David Reiss0c90f6f2008-02-06 22:18:40 +000086 | T_I08
87 | T_I16
88 | T_I32
89 | T_U64
90 | T_I64
91 | T_DOUBLE
92 | T_STRING
93 | T_UTF7
94 | T_STRUCT
95 | T_MAP
96 | T_SET
97 | T_LIST
98 | T_UTF8
iproctor9a41a0c2007-07-16 21:59:24 +000099 | T_UTF16
100
101 let t_type_to_i = function
102 T_STOP -> 0
103 | T_VOID -> 1
104 | T_BOOL -> 2
105 | T_BYTE -> 3
106 | T_I08 -> 3
107 | T_I16 -> 6
108 | T_I32 -> 8
109 | T_U64 -> 9
110 | T_I64 -> 10
111 | T_DOUBLE -> 4
112 | T_STRING -> 11
113 | T_UTF7 -> 11
114 | T_STRUCT -> 12
115 | T_MAP -> 13
116 | T_SET -> 14
117 | T_LIST -> 15
118 | T_UTF8 -> 16
119 | T_UTF16 -> 17
David Reiss0c90f6f2008-02-06 22:18:40 +0000120
iproctor9a41a0c2007-07-16 21:59:24 +0000121 let t_type_of_i = function
David Reiss0c90f6f2008-02-06 22:18:40 +0000122 0 -> T_STOP
123 | 1 -> T_VOID
iproctor9a41a0c2007-07-16 21:59:24 +0000124 | 2 -> T_BOOL
125 | 3 -> T_BYTE
David Reiss0c90f6f2008-02-06 22:18:40 +0000126 | 6-> T_I16
127 | 8 -> T_I32
128 | 9 -> T_U64
129 | 10 -> T_I64
130 | 4 -> T_DOUBLE
iproctor9a41a0c2007-07-16 21:59:24 +0000131 | 11 -> T_STRING
132 | 12 -> T_STRUCT
David Reiss0c90f6f2008-02-06 22:18:40 +0000133 | 13 -> T_MAP
134 | 14 -> T_SET
135 | 15 -> T_LIST
136 | 16 -> T_UTF8
iproctor9a41a0c2007-07-16 21:59:24 +0000137 | 17 -> T_UTF16
David Reiss0c90f6f2008-02-06 22:18:40 +0000138 | _ -> raise Thrift_error
iproctor9a41a0c2007-07-16 21:59:24 +0000139
140 type message_type =
141 | CALL
142 | REPLY
143 | EXCEPTION
144
145 let message_type_to_i = function
146 | CALL -> 1
147 | REPLY -> 2
148 | EXCEPTION -> 3
149
David Reiss0c90f6f2008-02-06 22:18:40 +0000150 let message_type_of_i = function
iproctor9a41a0c2007-07-16 21:59:24 +0000151 | 1 -> CALL
152 | 2 -> REPLY
153 | 3 -> EXCEPTION
154 | _ -> raise Thrift_error
155
156 class virtual t (trans: Transport.t) =
157 object (self)
158 val mutable trans_ = trans
159 method getTransport = trans_
160 (* writing methods *)
161 method virtual writeMessageBegin : string * message_type * int -> unit
162 method virtual writeMessageEnd : unit
163 method virtual writeStructBegin : string -> unit
164 method virtual writeStructEnd : unit
165 method virtual writeFieldBegin : string * t_type * int -> unit
166 method virtual writeFieldEnd : unit
167 method virtual writeFieldStop : unit
168 method virtual writeMapBegin : t_type * t_type * int -> unit
169 method virtual writeMapEnd : unit
170 method virtual writeListBegin : t_type * int -> unit
171 method virtual writeListEnd : unit
172 method virtual writeSetBegin : t_type * int -> unit
173 method virtual writeSetEnd : unit
174 method virtual writeBool : bool -> unit
175 method virtual writeByte : int -> unit
176 method virtual writeI16 : int -> unit
177 method virtual writeI32 : int -> unit
178 method virtual writeI64 : Int64.t -> unit
179 method virtual writeDouble : float -> unit
180 method virtual writeString : string -> unit
181 method virtual writeBinary : string -> unit
182 (* reading methods *)
183 method virtual readMessageBegin : string * message_type * int
184 method virtual readMessageEnd : unit
185 method virtual readStructBegin : string
186 method virtual readStructEnd : unit
187 method virtual readFieldBegin : string * t_type * int
188 method virtual readFieldEnd : unit
189 method virtual readMapBegin : t_type * t_type * int
190 method virtual readMapEnd : unit
191 method virtual readListBegin : t_type * int
192 method virtual readListEnd : unit
193 method virtual readSetBegin : t_type * int
194 method virtual readSetEnd : unit
195 method virtual readBool : bool
196 method virtual readByte : int
197 method virtual readI16 : int
198 method virtual readI32: int
199 method virtual readI64 : Int64.t
200 method virtual readDouble : float
201 method virtual readString : string
202 method virtual readBinary : string
203 (* skippage *)
David Reiss0c90f6f2008-02-06 22:18:40 +0000204 method skip typ =
iproctor9a41a0c2007-07-16 21:59:24 +0000205 match typ with
206 | T_STOP -> ()
207 | T_VOID -> ()
208 | T_BOOL -> ignore self#readBool
209 | T_BYTE
210 | T_I08 -> ignore self#readByte
211 | T_I16 -> ignore self#readI16
212 | T_I32 -> ignore self#readI32
213 | T_U64
David Reiss0c90f6f2008-02-06 22:18:40 +0000214 | T_I64 -> ignore self#readI64
iproctor9a41a0c2007-07-16 21:59:24 +0000215 | T_DOUBLE -> ignore self#readDouble
216 | T_STRING -> ignore self#readString
217 | T_UTF7 -> ()
218 | T_STRUCT -> ignore ((ignore self#readStructBegin);
219 (try
220 while true do
221 let (_,t,_) = self#readFieldBegin in
222 if t = T_STOP then
223 raise Break
David Reiss0c90f6f2008-02-06 22:18:40 +0000224 else
iproctor9a41a0c2007-07-16 21:59:24 +0000225 (self#skip t;
226 self#readFieldEnd)
227 done
228 with Break -> ());
229 self#readStructEnd)
230 | T_MAP -> ignore (let (k,v,s) = self#readMapBegin in
231 for i=0 to s do
232 self#skip k;
233 self#skip v;
234 done;
235 self#readMapEnd)
236 | T_SET -> ignore (let (t,s) = self#readSetBegin in
237 for i=0 to s do
238 self#skip t
239 done;
240 self#readSetEnd)
241 | T_LIST -> ignore (let (t,s) = self#readListBegin in
242 for i=0 to s do
243 self#skip t
244 done;
245 self#readListEnd)
246 | T_UTF8 -> ()
247 | T_UTF16 -> ()
248 end
249
250 class virtual factory =
251 object
252 method virtual getProtocol : Transport.t -> t
253 end
iproctord4de1e92007-07-24 19:47:55 +0000254
255 type exn_type =
256 | UNKNOWN
257 | INVALID_DATA
258 | NEGATIVE_SIZE
259 | SIZE_LIMIT
260 | BAD_VERSION
261
iproctore470aa32007-08-10 20:48:12 +0000262 exception E of exn_type * string;;
David Reiss0c90f6f2008-02-06 22:18:40 +0000263
264end;;
iproctor9a41a0c2007-07-16 21:59:24 +0000265
266
267module Processor =
268struct
269 class virtual t =
270 object
271 method virtual process : Protocol.t -> Protocol.t -> bool
272 end;;
David Reiss0c90f6f2008-02-06 22:18:40 +0000273
iproctor9a41a0c2007-07-16 21:59:24 +0000274 class factory (processor : t) =
275 object
David Reiss0c90f6f2008-02-06 22:18:40 +0000276 val processor_ = processor
iproctor9a41a0c2007-07-16 21:59:24 +0000277 method getProcessor (trans : Transport.t) = processor_
278 end;;
279end
280
281
iproctore470aa32007-08-10 20:48:12 +0000282(* Ugly *)
iproctor9a41a0c2007-07-16 21:59:24 +0000283module Application_Exn =
284struct
285 type typ=
286 | UNKNOWN
287 | UNKNOWN_METHOD
288 | INVALID_MESSAGE_TYPE
289 | WRONG_METHOD_NAME
290 | BAD_SEQUENCE_ID
291 | MISSING_RESULT
292
293 let typ_of_i = function
294 0 -> UNKNOWN
295 | 1 -> UNKNOWN_METHOD
296 | 2 -> INVALID_MESSAGE_TYPE
297 | 3 -> WRONG_METHOD_NAME
298 | 4 -> BAD_SEQUENCE_ID
299 | 5 -> MISSING_RESULT
300 | _ -> raise Thrift_error;;
301 let typ_to_i = function
302 | UNKNOWN -> 0
303 | UNKNOWN_METHOD -> 1
304 | INVALID_MESSAGE_TYPE -> 2
305 | WRONG_METHOD_NAME -> 3
306 | BAD_SEQUENCE_ID -> 4
307 | MISSING_RESULT -> 5
308
309 class t =
310 object (self)
311 inherit t_exn
312 val mutable typ = UNKNOWN
313 method get_type = typ
314 method set_type t = typ <- t
315 method write (oprot : Protocol.t) =
316 oprot#writeStructBegin "TApplicationExeception";
317 if self#get_message != "" then
318 (oprot#writeFieldBegin ("message",Protocol.T_STRING, 1);
319 oprot#writeString self#get_message;
320 oprot#writeFieldEnd)
321 else ();
322 oprot#writeFieldBegin ("type",Protocol.T_I32,2);
323 oprot#writeI32 (typ_to_i typ);
324 oprot#writeFieldEnd;
325 oprot#writeFieldStop;
326 oprot#writeStructEnd
327 end;;
David Reiss0c90f6f2008-02-06 22:18:40 +0000328
iproctor9a41a0c2007-07-16 21:59:24 +0000329 let create typ msg =
330 let e = new t in
331 e#set_type typ;
332 e#set_message msg;
333 e
David Reiss0c90f6f2008-02-06 22:18:40 +0000334
iproctor9a41a0c2007-07-16 21:59:24 +0000335 let read (iprot : Protocol.t) =
336 let msg = ref "" in
337 let typ = ref 0 in
iproctore470aa32007-08-10 20:48:12 +0000338 ignore iprot#readStructBegin;
David Reiss0c90f6f2008-02-06 22:18:40 +0000339 (try
iproctor9a41a0c2007-07-16 21:59:24 +0000340 while true do
341 let (name,ft,id) =iprot#readFieldBegin in
342 if ft = Protocol.T_STOP then
343 raise Break
344 else ();
345 (match id with
346 | 1 -> (if ft = Protocol.T_STRING then
347 msg := (iprot#readString)
348 else
349 iprot#skip ft)
350 | 2 -> (if ft = Protocol.T_I32 then
351 typ := iprot#readI32
352 else
353 iprot#skip ft)
354 | _ -> iprot#skip ft);
355 iprot#readFieldEnd
356 done
357 with Break -> ());
358 iprot#readStructEnd;
359 let e = new t in
360 e#set_type (typ_of_i !typ);
361 e#set_message !msg;
362 e;;
David Reiss0c90f6f2008-02-06 22:18:40 +0000363
iproctor9a41a0c2007-07-16 21:59:24 +0000364 exception E of t
365end;;