blob: f0d7a429659b8e857852446c07c9cf421bcc6602 [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
David Reissdeda1412009-04-02 19:22:31 +0000144 | ONEWAY
iproctor9a41a0c2007-07-16 21:59:24 +0000145
146 let message_type_to_i = function
147 | CALL -> 1
148 | REPLY -> 2
149 | EXCEPTION -> 3
David Reissdeda1412009-04-02 19:22:31 +0000150 | ONEWAY -> 4
iproctor9a41a0c2007-07-16 21:59:24 +0000151
David Reiss0c90f6f2008-02-06 22:18:40 +0000152 let message_type_of_i = function
iproctor9a41a0c2007-07-16 21:59:24 +0000153 | 1 -> CALL
154 | 2 -> REPLY
155 | 3 -> EXCEPTION
David Reissdeda1412009-04-02 19:22:31 +0000156 | 4 -> ONEWAY
iproctor9a41a0c2007-07-16 21:59:24 +0000157 | _ -> raise Thrift_error
158
159 class virtual t (trans: Transport.t) =
160 object (self)
161 val mutable trans_ = trans
162 method getTransport = trans_
163 (* writing methods *)
164 method virtual writeMessageBegin : string * message_type * int -> unit
165 method virtual writeMessageEnd : unit
166 method virtual writeStructBegin : string -> unit
167 method virtual writeStructEnd : unit
168 method virtual writeFieldBegin : string * t_type * int -> unit
169 method virtual writeFieldEnd : unit
170 method virtual writeFieldStop : unit
171 method virtual writeMapBegin : t_type * t_type * int -> unit
172 method virtual writeMapEnd : unit
173 method virtual writeListBegin : t_type * int -> unit
174 method virtual writeListEnd : unit
175 method virtual writeSetBegin : t_type * int -> unit
176 method virtual writeSetEnd : unit
177 method virtual writeBool : bool -> unit
178 method virtual writeByte : int -> unit
179 method virtual writeI16 : int -> unit
Bryan Duxburyfad8d6b2011-01-12 18:41:52 +0000180 method virtual writeI32 : Int32.t -> unit
iproctor9a41a0c2007-07-16 21:59:24 +0000181 method virtual writeI64 : Int64.t -> unit
182 method virtual writeDouble : float -> unit
183 method virtual writeString : string -> unit
184 method virtual writeBinary : string -> unit
185 (* reading methods *)
186 method virtual readMessageBegin : string * message_type * int
187 method virtual readMessageEnd : unit
188 method virtual readStructBegin : string
189 method virtual readStructEnd : unit
190 method virtual readFieldBegin : string * t_type * int
191 method virtual readFieldEnd : unit
192 method virtual readMapBegin : t_type * t_type * int
193 method virtual readMapEnd : unit
194 method virtual readListBegin : t_type * int
195 method virtual readListEnd : unit
196 method virtual readSetBegin : t_type * int
197 method virtual readSetEnd : unit
198 method virtual readBool : bool
199 method virtual readByte : int
200 method virtual readI16 : int
Bryan Duxburyfad8d6b2011-01-12 18:41:52 +0000201 method virtual readI32: Int32.t
iproctor9a41a0c2007-07-16 21:59:24 +0000202 method virtual readI64 : Int64.t
203 method virtual readDouble : float
204 method virtual readString : string
205 method virtual readBinary : string
206 (* skippage *)
David Reiss0c90f6f2008-02-06 22:18:40 +0000207 method skip typ =
iproctor9a41a0c2007-07-16 21:59:24 +0000208 match typ with
209 | T_STOP -> ()
210 | T_VOID -> ()
211 | T_BOOL -> ignore self#readBool
212 | T_BYTE
213 | T_I08 -> ignore self#readByte
214 | T_I16 -> ignore self#readI16
215 | T_I32 -> ignore self#readI32
216 | T_U64
David Reiss0c90f6f2008-02-06 22:18:40 +0000217 | T_I64 -> ignore self#readI64
iproctor9a41a0c2007-07-16 21:59:24 +0000218 | T_DOUBLE -> ignore self#readDouble
219 | T_STRING -> ignore self#readString
220 | T_UTF7 -> ()
221 | T_STRUCT -> ignore ((ignore self#readStructBegin);
222 (try
223 while true do
224 let (_,t,_) = self#readFieldBegin in
225 if t = T_STOP then
226 raise Break
David Reiss0c90f6f2008-02-06 22:18:40 +0000227 else
iproctor9a41a0c2007-07-16 21:59:24 +0000228 (self#skip t;
229 self#readFieldEnd)
230 done
231 with Break -> ());
232 self#readStructEnd)
233 | T_MAP -> ignore (let (k,v,s) = self#readMapBegin in
234 for i=0 to s do
235 self#skip k;
236 self#skip v;
237 done;
238 self#readMapEnd)
239 | T_SET -> ignore (let (t,s) = self#readSetBegin in
240 for i=0 to s do
241 self#skip t
242 done;
243 self#readSetEnd)
244 | T_LIST -> ignore (let (t,s) = self#readListBegin in
245 for i=0 to s do
246 self#skip t
247 done;
248 self#readListEnd)
249 | T_UTF8 -> ()
250 | T_UTF16 -> ()
251 end
252
253 class virtual factory =
254 object
255 method virtual getProtocol : Transport.t -> t
256 end
iproctord4de1e92007-07-24 19:47:55 +0000257
258 type exn_type =
259 | UNKNOWN
260 | INVALID_DATA
261 | NEGATIVE_SIZE
262 | SIZE_LIMIT
263 | BAD_VERSION
Jens Geyer6d1a83a2014-05-03 00:49:05 +0200264 | NOT_IMPLEMENTED
265 | DEPTH_LIMIT
iproctord4de1e92007-07-24 19:47:55 +0000266
iproctore470aa32007-08-10 20:48:12 +0000267 exception E of exn_type * string;;
David Reiss0c90f6f2008-02-06 22:18:40 +0000268
269end;;
iproctor9a41a0c2007-07-16 21:59:24 +0000270
271
272module Processor =
273struct
274 class virtual t =
275 object
276 method virtual process : Protocol.t -> Protocol.t -> bool
277 end;;
David Reiss0c90f6f2008-02-06 22:18:40 +0000278
iproctor9a41a0c2007-07-16 21:59:24 +0000279 class factory (processor : t) =
280 object
David Reiss0c90f6f2008-02-06 22:18:40 +0000281 val processor_ = processor
iproctor9a41a0c2007-07-16 21:59:24 +0000282 method getProcessor (trans : Transport.t) = processor_
283 end;;
284end
285
286
iproctore470aa32007-08-10 20:48:12 +0000287(* Ugly *)
iproctor9a41a0c2007-07-16 21:59:24 +0000288module Application_Exn =
289struct
290 type typ=
291 | UNKNOWN
292 | UNKNOWN_METHOD
293 | INVALID_MESSAGE_TYPE
294 | WRONG_METHOD_NAME
295 | BAD_SEQUENCE_ID
296 | MISSING_RESULT
Roger Meier345ecc72011-08-03 09:49:27 +0000297 | INTERNAL_ERROR
298 | PROTOCOL_ERROR
Roger Meier01931492012-12-22 21:31:03 +0100299 | INVALID_TRANSFORM
300 | INVALID_PROTOCOL
301 | UNSUPPORTED_CLIENT_TYPE
iproctor9a41a0c2007-07-16 21:59:24 +0000302
303 let typ_of_i = function
Bryan Duxburyfad8d6b2011-01-12 18:41:52 +0000304 0l -> UNKNOWN
305 | 1l -> UNKNOWN_METHOD
306 | 2l -> INVALID_MESSAGE_TYPE
307 | 3l -> WRONG_METHOD_NAME
308 | 4l -> BAD_SEQUENCE_ID
309 | 5l -> MISSING_RESULT
Jake Farrelleb7a7552011-09-06 16:26:58 +0000310 | 6l -> INTERNAL_ERROR
311 | 7l -> PROTOCOL_ERROR
Roger Meier01931492012-12-22 21:31:03 +0100312 | 8l -> INVALID_TRANSFORM
313 | 9l -> INVALID_PROTOCOL
314 | 10l -> UNSUPPORTED_CLIENT_TYPE
iproctor9a41a0c2007-07-16 21:59:24 +0000315 | _ -> raise Thrift_error;;
316 let typ_to_i = function
Bryan Duxburyfad8d6b2011-01-12 18:41:52 +0000317 | UNKNOWN -> 0l
318 | UNKNOWN_METHOD -> 1l
319 | INVALID_MESSAGE_TYPE -> 2l
320 | WRONG_METHOD_NAME -> 3l
321 | BAD_SEQUENCE_ID -> 4l
322 | MISSING_RESULT -> 5l
Jake Farrelleb7a7552011-09-06 16:26:58 +0000323 | INTERNAL_ERROR -> 6l
324 | PROTOCOL_ERROR -> 7l
Roger Meier01931492012-12-22 21:31:03 +0100325 | INVALID_TRANSFORM -> 8l
326 | INVALID_PROTOCOL -> 9l
327 | UNSUPPORTED_CLIENT_TYPE -> 10l
iproctor9a41a0c2007-07-16 21:59:24 +0000328
329 class t =
330 object (self)
331 inherit t_exn
332 val mutable typ = UNKNOWN
333 method get_type = typ
334 method set_type t = typ <- t
335 method write (oprot : Protocol.t) =
336 oprot#writeStructBegin "TApplicationExeception";
337 if self#get_message != "" then
338 (oprot#writeFieldBegin ("message",Protocol.T_STRING, 1);
339 oprot#writeString self#get_message;
340 oprot#writeFieldEnd)
341 else ();
342 oprot#writeFieldBegin ("type",Protocol.T_I32,2);
343 oprot#writeI32 (typ_to_i typ);
344 oprot#writeFieldEnd;
345 oprot#writeFieldStop;
346 oprot#writeStructEnd
347 end;;
David Reiss0c90f6f2008-02-06 22:18:40 +0000348
iproctor9a41a0c2007-07-16 21:59:24 +0000349 let create typ msg =
350 let e = new t in
351 e#set_type typ;
352 e#set_message msg;
353 e
David Reiss0c90f6f2008-02-06 22:18:40 +0000354
iproctor9a41a0c2007-07-16 21:59:24 +0000355 let read (iprot : Protocol.t) =
356 let msg = ref "" in
Bryan Duxburyfad8d6b2011-01-12 18:41:52 +0000357 let typ = ref 0l in
iproctore470aa32007-08-10 20:48:12 +0000358 ignore iprot#readStructBegin;
David Reiss0c90f6f2008-02-06 22:18:40 +0000359 (try
iproctor9a41a0c2007-07-16 21:59:24 +0000360 while true do
361 let (name,ft,id) =iprot#readFieldBegin in
Bryan Duxburyfad8d6b2011-01-12 18:41:52 +0000362 if ft = Protocol.T_STOP
363 then raise Break
iproctor9a41a0c2007-07-16 21:59:24 +0000364 else ();
365 (match id with
Bryan Duxburyfad8d6b2011-01-12 18:41:52 +0000366 | 1 -> (if ft = Protocol.T_STRING
367 then msg := (iprot#readString)
368 else iprot#skip ft)
369 | 2 -> (if ft = Protocol.T_I32
370 then typ := iprot#readI32
371 else iprot#skip ft)
iproctor9a41a0c2007-07-16 21:59:24 +0000372 | _ -> iprot#skip ft);
373 iprot#readFieldEnd
374 done
375 with Break -> ());
376 iprot#readStructEnd;
377 let e = new t in
378 e#set_type (typ_of_i !typ);
379 e#set_message !msg;
380 e;;
David Reiss0c90f6f2008-02-06 22:18:40 +0000381
iproctor9a41a0c2007-07-16 21:59:24 +0000382 exception E of t
383end;;