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