1/* -----------------------------------------------------------------------------
2 * ocaml.swg
3 *
4 * The Ocaml module handles all types uniformly via typemaps. Here
5 * are the definitions.
6 * ----------------------------------------------------------------------------- */
7
8/* Pointers */
9
10%typemap(in) void ""
11
12%typemap(out) void "$result = Val_int(0);"
13
14%typemap(in) void * {
15    $1 = caml_ptr_val($input,$descriptor);
16}
17
18%typemap(varin) void * {
19    $1 = ($ltype)caml_ptr_val($input,$descriptor);
20}
21
22%typemap(out) void * {
23    $result = caml_val_ptr($1,$descriptor);
24}
25
26%typemap(varout) void * {
27    $result = caml_val_ptr($1,$descriptor);
28}
29
30%typemap(in) char *& (char *temp) {
31  temp = (char*)caml_val_ptr($1,$descriptor);
32  $1 = &temp;
33}
34
35%typemap(argout) char *& {
36  swig_result =	caml_list_append(swig_result,caml_val_string_len(*$1, strlen(*$1)));
37}
38
39%typemap(in) SWIGTYPE & {
40    $1 = ($ltype) caml_ptr_val($input,$1_descriptor);
41}
42
43%typemap(in) SWIGTYPE && {
44    $1 = ($ltype) caml_ptr_val($input,$1_descriptor);
45}
46
47%typemap(varin) SWIGTYPE & {
48    $1 = *(($ltype) caml_ptr_val($input,$1_descriptor));
49}
50
51%typemap(varin) SWIGTYPE && {
52    $1 = *(($ltype) caml_ptr_val($input,$1_descriptor));
53}
54
55%typemap(varout) SWIGTYPE &, SWIGTYPE && {
56    $result = SWIG_Ocaml_ptr_to_val("create_$ntype_from_ptr", (void *)&$1, $1_descriptor);
57}
58
59%typemap(out) SWIGTYPE &, SWIGTYPE && {
60    $result = SWIG_Ocaml_ptr_to_val("create_$ntype_from_ptr", (void *)$1, $1_descriptor);
61}
62
63#if 0
64%typemap(argout) SWIGTYPE & {
65    const CAML_VALUE *fromval = caml_named_value("create_$ntype_from_ptr");
66    if( fromval ) {
67	swig_result =
68	    caml_list_append(swig_result,
69			     caml_callback(*fromval,caml_val_ptr((void *) $1,
70							    $1_descriptor)));
71    } else {
72	swig_result =
73	    caml_list_append(swig_result,
74			     caml_val_ptr ((void *) $1,$1_descriptor));
75    }
76}
77%typemap(argout) SWIGTYPE && {
78    const CAML_VALUE *fromval = caml_named_value("create_$ntype_from_ptr");
79    if( fromval ) {
80	swig_result =
81	    caml_list_append(swig_result,
82			     caml_callback(*fromval,caml_val_ptr((void *) $1,
83							    $1_descriptor)));
84    } else {
85	swig_result =
86	    caml_list_append(swig_result,
87			     caml_val_ptr ((void *) $1,$1_descriptor));
88    }
89}
90#endif
91
92%typemap(in) SWIGTYPE {
93    $1 = *(($&1_ltype) caml_ptr_val($input,$&1_descriptor)) ;
94}
95
96#ifdef __cplusplus
97
98%typemap(out) SWIGTYPE {
99    $&1_ltype temp = new $ltype((const $1_ltype &) $1);
100    $result = SWIG_Ocaml_ptr_to_val("create_$ntype_from_ptr", (void *)temp, $&1_descriptor);
101}
102
103#else
104
105%typemap(out) SWIGTYPE {
106    void *temp = calloc(1,sizeof($ltype));
107    memmove(temp, &$1, sizeof($1_type));
108    $result = SWIG_Ocaml_ptr_to_val("create_$ntype_from_ptr", temp, $&1_descriptor);
109}
110
111#endif
112
113%typemap(directorin) SWIGTYPE {
114    $&ltype temp = new $ltype((const $ltype &)$1);
115    swig_result = SWIG_Ocaml_ptr_to_val("create_$ltype_from_ptr", (void *)temp, $&1_descriptor);
116    args = caml_list_append(args, swig_result);
117}
118
119%typemap(directorin) SWIGTYPE *, SWIGTYPE [], SWIGTYPE &, SWIGTYPE && {
120    swig_result = SWIG_Ocaml_ptr_to_val("create_$ltype_from_ptr", (void *)&$1, $&1_descriptor);
121    args = caml_list_append(args, swig_result);
122}
123
124/* The SIMPLE_MAP macro below defines the whole set of typemaps needed
125   for simple types. */
126
127%define SIMPLE_MAP(C_NAME, C_TO_OCAML, OCAML_TO_C)
128/* In */
129%typemap(in) C_NAME {
130    $1 = OCAML_TO_C($input);
131}
132%typemap(varin) C_NAME {
133    $1 = OCAML_TO_C($input);
134}
135%typemap(in) const C_NAME & ($*1_ltype temp) {
136    temp = ($*1_ltype) OCAML_TO_C($input);
137    $1 = &temp;
138}
139%typemap(varin) const C_NAME & {
140    $1 = OCAML_TO_C($input);
141}
142%typemap(directorout) C_NAME {
143    $1 = OCAML_TO_C($input);
144}
145/* Out */
146%typemap(out) C_NAME {
147    $result = C_TO_OCAML($1);
148}
149%typemap(varout) C_NAME {
150    $result = C_TO_OCAML($1);
151}
152%typemap(varout) const C_NAME & {
153    $result = C_TO_OCAML($1);
154}
155%typemap(out) const C_NAME & {
156    $result = C_TO_OCAML(*$1);
157}
158%typemap(directorin) C_NAME {
159    args = caml_list_append(args, C_TO_OCAML($1));
160}
161%enddef
162
163SIMPLE_MAP(bool, caml_val_bool, caml_long_val);
164SIMPLE_MAP(char, caml_val_char, caml_long_val);
165SIMPLE_MAP(signed char, caml_val_char, caml_long_val);
166SIMPLE_MAP(unsigned char, caml_val_uchar, caml_long_val);
167SIMPLE_MAP(int, caml_val_int, caml_long_val);
168SIMPLE_MAP(short, caml_val_short, caml_long_val);
169SIMPLE_MAP(wchar_t, caml_val_short, caml_long_val);
170SIMPLE_MAP(long, caml_val_long, caml_long_val);
171SIMPLE_MAP(ptrdiff_t, caml_val_int, caml_long_val);
172SIMPLE_MAP(unsigned int, caml_val_uint, caml_long_val);
173SIMPLE_MAP(unsigned short, caml_val_ushort, caml_long_val);
174SIMPLE_MAP(unsigned long, caml_val_ulong, caml_long_val);
175SIMPLE_MAP(size_t, caml_val_int, caml_long_val);
176SIMPLE_MAP(float, caml_val_float, caml_double_val);
177SIMPLE_MAP(double, caml_val_double, caml_double_val);
178SIMPLE_MAP(long long,caml_val_ulong,caml_long_val);
179SIMPLE_MAP(unsigned long long,caml_val_ulong,caml_long_val);
180
181/* Void */
182
183%typemap(out) void "$result = Val_unit;";
184
185/* Pass through value */
186
187%typemap (in) CAML_VALUE "$1=$input;";
188%typemap (out) CAML_VALUE "$result=$1;";
189
190#if 0
191%include <carray.i>
192#endif
193
194/* Handle char arrays as strings */
195
196%define %char_ptr_in(how)
197%typemap(how)  char *, signed char *, unsigned char * {
198    $1 = ($ltype)caml_string_val($input);
199}
200/* Again work around the empty array bound bug */
201%typemap(how) char [ANY], signed char [ANY], unsigned char [ANY] {
202    char *temp = caml_string_val($input);
203    strcpy((char *)$1,temp);
204}
205%enddef
206
207%char_ptr_in(in);
208%char_ptr_in(varin);
209%char_ptr_in(directorout);
210
211%define %char_ptr_out(how)
212%typemap(how)
213    char *, signed char *, unsigned char *,
214    const char *, const signed char *, const unsigned char * {
215    $result = caml_val_string((char *)$1);
216}
217/* I'd like to use the length here but can't because it might be empty */
218%typemap(how)
219    char [ANY], signed char [ANY], unsigned char [ANY],
220    const char [ANY], const signed char [ANY], const unsigned char [ANY] {
221    $result = caml_val_string((char *)$1);
222}
223%enddef
224
225%char_ptr_out(out);
226%char_ptr_out(varout);
227%char_ptr_out(directorin);
228
229%define %swigtype_ptr_in(how)
230%typemap(how) SWIGTYPE * {
231    $1 = ($ltype)caml_ptr_val($input,$1_descriptor);
232}
233%typemap(how) SWIGTYPE (CLASS::*) {
234    void *v = caml_ptr_val($input,$1_descriptor);
235    memcpy(& $1, &v, sizeof(v));
236}
237%enddef
238
239%typemap(out) SWIGTYPE * {
240    $result = SWIG_Ocaml_ptr_to_val("create_$ntype_from_ptr", (void *)$1, $1_descriptor);
241}
242
243%define %swigtype_ptr_out(how)
244%typemap(how) SWIGTYPE (CLASS::*) {
245    void *v;
246    memcpy(&v,& $1, sizeof(void *));
247    $result = caml_val_ptr (v,$1_descriptor);
248}
249%enddef
250
251%swigtype_ptr_in(in);
252%swigtype_ptr_in(varin);
253%swigtype_ptr_in(directorout);
254%swigtype_ptr_out(out);
255%swigtype_ptr_out(varout);
256%swigtype_ptr_out(directorin);
257
258%define %swigtype_array_fail(how,msg)
259%typemap(how) SWIGTYPE [] {
260    caml_failwith(msg);
261}
262%enddef
263
264%swigtype_array_fail(in,"Array arguments for arbitrary types need a typemap");
265%swigtype_array_fail(varin,"Assignment to global arrays for arbitrary types need a typemap");
266%swigtype_array_fail(out,"Array arguments for arbitrary types need a typemap");
267%swigtype_array_fail(varout,"Array variables need a typemap");
268%swigtype_array_fail(directorin,"Array results with arbitrary types need a typemap");
269%swigtype_array_fail(directorout,"Array arguments with arbitrary types need a typemap");
270
271/* C++ References */
272
273/* Enums */
274%define %swig_enum_in(how)
275%typemap(how) enum SWIGTYPE {
276    $1 = ($type)caml_long_val_full($input,"$type_marker");
277}
278%enddef
279
280%define %swig_enum_out(how)
281%typemap(how) enum SWIGTYPE {
282    $result = caml_callback2(*caml_named_value(SWIG_MODULE "_int_to_enum"),*caml_named_value("$type_marker"),Val_int((int)$1));
283}
284%enddef
285
286%swig_enum_in(in)
287%swig_enum_in(varin)
288%swig_enum_in(directorout)
289%swig_enum_out(out)
290%swig_enum_out(varout)
291%swig_enum_out(directorin)
292
293%typemap(in) (char *STRING, int LENGTH), (char *STRING, size_t LENGTH) {
294    $1 = ($1_ltype) caml_string_val($input);
295    $2 = ($2_ltype) caml_string_len($input);
296}
297
298%typemap(out) SWIGTYPE *DYNAMIC, SWIGTYPE &DYNAMIC {
299    swig_type_info *ty = SWIG_TypeDynamicCast($1_descriptor, (void **)&$1);
300    $result = SWIG_Ocaml_ptr_to_val("create_$ntype_from_ptr", (void *)$1, ty);
301}
302
303/* Array reference typemaps */
304%apply SWIGTYPE & { SWIGTYPE ((&)[ANY]) }
305%apply SWIGTYPE && { SWIGTYPE ((&)[ANY]) }
306
307/* const pointers */
308%apply SWIGTYPE * { SWIGTYPE *const }
309%apply SWIGTYPE (CLASS::*) { SWIGTYPE (CLASS::*const) }
310%apply SWIGTYPE & { SWIGTYPE (CLASS::*const&) }
311
312