Initial commit of OpenSPARC T2 architecture model.
[OpenSPARC-T2-SAM] / sam-t2 / devtools / amd64 / share / swig / 1.3.26 / ocaml / ocaml.swg
CommitLineData
920dae64
AT
1/* -*-c-*- */
2
3/* SWIG pointer structure */
4
5#include <string.h>
6#include <assert.h>
7
8#ifdef __cplusplus
9extern "C" {
10#endif
11
12#define C_bool 0
13#define C_char 1
14#define C_uchar 2
15#define C_short 3
16#define C_ushort 4
17#define C_int 5
18#define C_uint 6
19#define C_int32 7
20#define C_int64 8
21#define C_float 9
22#define C_double 10
23#define C_ptr 11
24#define C_array 12
25#define C_list 13
26#define C_obj 14
27#define C_string 15
28#define C_enum 16
29#define C_director_core 17
30
31
32/* Cast a pointer if possible; returns 1 if successful */
33
34 SWIGSTATIC int
35 SWIG_Cast (void *source, swig_type_info *source_type,
36 void **ptr, swig_type_info *dest_type)
37 {
38 if( !source ) { // Special case for NULL. This is a popular question
39 // for other modules on the list, so I want an easy way out...
40 *ptr = 0;
41 return 0;
42 }
43
44#ifdef TYPE_CAST_VERBOSE
45 fprintf( stderr, "Trying to cast %s to %s\n",
46 source_type ? source_type->str : "<none>",
47 dest_type ? dest_type->str : "<none>" );
48#endif
49 if (dest_type != source_type) {
50 /* We have a type mismatch. Will have to look through our type
51 mapping table to figure out whether or not we can accept this
52 datatype.
53 --
54 Ignore typechecks for void *. Allow any conversion. */
55 if( !dest_type || !source_type ||
56 !strcmp(dest_type->name,"_p_void") ||
57 !strcmp(source_type->name,"_p_void") ) {
58 *ptr = source;
59 return 0;
60 } else {
61 swig_cast_info *tc =
62 SWIG_TypeCheckStruct(source_type, dest_type );
63#ifdef TYPE_CAST_VERBOSE
64 fprintf( stderr, "Typecheck -> %s\n",
65 tc ? tc->str : "<none>" );
66#endif
67 if( tc ) {
68 *ptr = SWIG_TypeCast( tc, source );
69 return 0;
70 } else
71 return -1;
72 }
73 } else {
74 *ptr = source;
75 return 0;
76 }
77 }
78
79/* Return 0 if successful. */
80 SWIGSTATIC int
81 SWIG_GetPtr(void *inptr, void **outptr,
82 swig_type_info *intype, swig_type_info *outtype) {
83 if (intype) {
84 return SWIG_Cast(inptr, intype,
85 outptr, outtype) == -1;
86 } else {
87 *outptr = inptr;
88 return 0;
89 }
90 }
91
92 SWIGSTATIC void caml_print_list( CAML_VALUE v );
93
94 SWIGSTATIC void caml_print_val( CAML_VALUE v ) {
95 switch( SWIG_Tag_val(v) ) {
96 case C_bool:
97 if( Bool_val(SWIG_Field(v,0)) ) fprintf( stderr, "true " );
98 else fprintf( stderr, "false " );
99 break;
100 case C_char:
101 case C_uchar:
102 fprintf( stderr, "'%c' (\\%03d) ",
103 (Int_val(SWIG_Field(v,0)) >= ' ' &&
104 Int_val(SWIG_Field(v,0)) < 127) ? Int_val(SWIG_Field(v,0)) : '.',
105 Int_val(SWIG_Field(v,0)) );
106 break;
107 case C_short:
108 case C_ushort:
109 case C_int:
110 fprintf( stderr, "%d ", (int)caml_long_val(v) );
111 break;
112
113 case C_uint:
114 case C_int32:
115 fprintf( stderr, "%ud ", (unsigned int)caml_long_val(v) );
116 break;
117 case C_int64:
118 fprintf( stderr, "%ld ", caml_long_val(v) );
119 break;
120 case C_float:
121 case C_double:
122 fprintf( stderr, "%f ", caml_double_val(v) );
123 break;
124
125 case C_ptr:
126 {
127 void *vout = 0;
128 swig_type_info *ty = (swig_type_info *)(long)SWIG_Int64_val(SWIG_Field(v,1));
129 caml_ptr_val_internal(v,&vout,0);
130 fprintf( stderr, "PTR(%p,%s) ",
131 vout,
132 ty ? ty->name : "(null)" );
133 }
134 break;
135 case C_array:
136 {
137 unsigned int i;
138 for( i = 0; i < Wosize_val( SWIG_Field(v,0) ); i++ )
139 caml_print_val( SWIG_Field(SWIG_Field(v,0),i) );
140 }
141 break;
142 case C_list:
143 caml_print_list( SWIG_Field(v,0) );
144 break;
145 case C_obj:
146 fprintf( stderr, "OBJ(%p) ", (void *)SWIG_Field(v,0) );
147 break;
148 case C_string:
149 {
150 void *cout;
151 caml_ptr_val_internal(v,&cout,0);
152 fprintf( stderr, "'%s' ", (char *)cout );
153 }
154 break;
155 }
156 }
157
158 SWIGSTATIC void caml_print_list( CAML_VALUE v ) {
159 CAMLparam1(v);
160 while( v && Is_block(v) ) {
161 fprintf( stderr, "[ " );
162 caml_print_val( SWIG_Field(v,0) );
163 fprintf( stderr, "]\n" );
164 v = SWIG_Field(v,1);
165 }
166 CAMLreturn0;
167 }
168
169 SWIGSTATIC CAML_VALUE caml_list_nth( CAML_VALUE lst, int n ) {
170 CAMLparam1(lst);
171 int i = 0;
172 while( i < n && lst && Is_block(lst) ) {
173 i++; lst = SWIG_Field(lst,1);
174 }
175 if( lst == Val_unit ) CAMLreturn(Val_unit);
176 else CAMLreturn(SWIG_Field(lst,0));
177 }
178
179 SWIGSTATIC CAML_VALUE caml_list_append( CAML_VALUE lst, CAML_VALUE elt ) {
180 CAMLparam2(lst,elt);
181 SWIG_CAMLlocal3(v,vt,lh);
182 lh = Val_unit;
183 v = Val_unit;
184
185 /* Appending C_void should have no effect */
186 if( !Is_block(elt) ) return lst;
187
188 while( lst && Is_block(lst) ) {
189 if( v && v != Val_unit ) {
190 vt = alloc_tuple(2);
191 SWIG_Store_field(v,1,vt);
192 v = vt;
193 } else {
194 v = lh = alloc_tuple(2);
195 }
196 SWIG_Store_field(v,0,SWIG_Field(lst,0));
197 lst = SWIG_Field(lst,1);
198 }
199
200 if( v && Is_block(v) ) {
201 vt = alloc_tuple(2);
202 SWIG_Store_field(v,1,vt);
203 v = vt;
204 } else {
205 v = lh = alloc_tuple(2);
206 }
207 SWIG_Store_field(v,0,elt);
208 SWIG_Store_field(v,1,Val_unit);
209
210 CAMLreturn(lh);
211 }
212
213 SWIGSTATIC int caml_list_length( CAML_VALUE lst ) {
214 CAMLparam1(lst);
215 int i = 0;
216 while( lst && Is_block(lst) ) { i++; lst = SWIG_Field(lst,1); }
217 CAMLreturn(i);
218 }
219
220 SWIGSTATIC void caml_array_set( CAML_VALUE arr, int n, CAML_VALUE item ) {
221 CAMLparam2(arr,item);
222 SWIG_Store_field(SWIG_Field(arr,0),n,item);
223 CAMLreturn0;
224 }
225
226 SWIGSTATIC value caml_array_nth( CAML_VALUE arr, int n ) {
227 CAMLparam1(arr);
228 if( SWIG_Tag_val(arr) == C_array )
229 CAMLreturn(SWIG_Field(SWIG_Field(arr,0),n));
230 else if( SWIG_Tag_val(arr) == C_list )
231 CAMLreturn(caml_list_nth(arr,0));
232 else
233 failwith("Need array or list");
234 }
235
236 SWIGSTATIC int caml_array_len( CAML_VALUE arr ) {
237 CAMLparam1(arr);
238 if( SWIG_Tag_val(arr) == C_array )
239 CAMLreturn(Wosize_val(SWIG_Field(arr,0)));
240 else if( SWIG_Tag_val(arr) == C_list )
241 CAMLreturn(caml_list_length(arr));
242 else
243 failwith("Need array or list");
244 }
245
246 SWIGSTATIC CAML_VALUE caml_swig_alloc(int x,int y) {
247 return caml_alloc(x,y);
248 }
249
250 SWIGSTATIC value caml_array_new( int n ) {
251 CAMLparam0();
252 SWIG_CAMLlocal1(vv);
253 vv = caml_swig_alloc(1,C_array);
254 SWIG_Store_field(vv,0,alloc_tuple(n));
255 CAMLreturn(vv);
256 }
257
258 SWIGSTATIC CAML_VALUE caml_val_bool( int b ) {
259 CAMLparam0();
260 SWIG_CAMLlocal1(bv);
261 bv = caml_swig_alloc(1,C_bool);
262 SWIG_Store_field(bv,0,Val_bool(b));
263 CAMLreturn(bv);
264 }
265
266 SWIGSTATIC CAML_VALUE caml_val_char( char c ) {
267 CAMLparam0();
268 SWIG_CAMLlocal1(cv);
269 cv = caml_swig_alloc(1,C_char);
270 SWIG_Store_field(cv,0,Val_int(c));
271 CAMLreturn(cv);
272 }
273
274 SWIGSTATIC CAML_VALUE caml_val_uchar( unsigned char uc ) {
275 CAMLparam0();
276 SWIG_CAMLlocal1(ucv);
277 ucv = caml_swig_alloc(1,C_uchar);
278 SWIG_Store_field(ucv,0,Val_int(uc));
279 CAMLreturn(ucv);
280 }
281
282 SWIGSTATIC CAML_VALUE caml_val_short( short s ) {
283 CAMLparam0();
284 SWIG_CAMLlocal1(sv);
285 sv = caml_swig_alloc(1,C_short);
286 SWIG_Store_field(sv,0,Val_int(s));
287 CAMLreturn(sv);
288 }
289
290 SWIGSTATIC CAML_VALUE caml_val_ushort( unsigned short us ) {
291 CAMLparam0();
292 SWIG_CAMLlocal1(usv);
293 usv = caml_swig_alloc(1,C_ushort);
294 SWIG_Store_field(usv,0,Val_int(us));
295 CAMLreturn(usv);
296 }
297
298 SWIGSTATIC CAML_VALUE caml_val_int( int i ) {
299 CAMLparam0();
300 SWIG_CAMLlocal1(iv);
301 iv = caml_swig_alloc(1,C_int);
302 SWIG_Store_field(iv,0,Val_int(i));
303 CAMLreturn(iv);
304 }
305
306 SWIGSTATIC CAML_VALUE caml_val_uint( unsigned int ui ) {
307 CAMLparam0();
308 SWIG_CAMLlocal1(uiv);
309 uiv = caml_swig_alloc(1,C_int);
310 SWIG_Store_field(uiv,0,Val_int(ui));
311 CAMLreturn(uiv);
312 }
313
314 SWIGSTATIC CAML_VALUE caml_val_long( long l ) {
315 CAMLparam0();
316 SWIG_CAMLlocal1(lv);
317 lv = caml_swig_alloc(1,C_int64);
318 SWIG_Store_field(lv,0,copy_int64(l));
319 CAMLreturn(lv);
320 }
321
322 SWIGSTATIC CAML_VALUE caml_val_ulong( unsigned long ul ) {
323 CAMLparam0();
324 SWIG_CAMLlocal1(ulv);
325 ulv = caml_swig_alloc(1,C_int64);
326 SWIG_Store_field(ulv,0,copy_int64(ul));
327 CAMLreturn(ulv);
328 }
329
330 SWIGSTATIC CAML_VALUE caml_val_float( float f ) {
331 CAMLparam0();
332 SWIG_CAMLlocal1(fv);
333 fv = caml_swig_alloc(1,C_float);
334 SWIG_Store_field(fv,0,copy_double((double)f));
335 CAMLreturn(fv);
336 }
337
338 SWIGSTATIC CAML_VALUE caml_val_double( double d ) {
339 CAMLparam0();
340 SWIG_CAMLlocal1(fv);
341 fv = caml_swig_alloc(1,C_double);
342 SWIG_Store_field(fv,0,copy_double(d));
343 CAMLreturn(fv);
344 }
345
346 SWIGSTATIC CAML_VALUE caml_val_ptr( void *p, swig_type_info *info ) {
347 CAMLparam0();
348 SWIG_CAMLlocal1(vv);
349 vv = caml_swig_alloc(2,C_ptr);
350 SWIG_Store_field(vv,0,copy_int64((long)p));
351 SWIG_Store_field(vv,1,copy_int64((long)info));
352 CAMLreturn(vv);
353 }
354
355 SWIGSTATIC CAML_VALUE caml_val_string( const char *p ) {
356 CAMLparam0();
357 SWIG_CAMLlocal1(vv);
358 if( !p ) CAMLreturn(caml_val_ptr( (void *)p, 0 ));
359 vv = caml_swig_alloc(1,C_string);
360 SWIG_Store_field(vv,0,copy_string(p));
361 CAMLreturn(vv);
362 }
363
364 SWIGSTATIC CAML_VALUE caml_val_string_len( const char *p, int len ) {
365 CAMLparam0();
366 SWIG_CAMLlocal1(vv);
367 if( !p || len < 0 ) CAMLreturn(caml_val_ptr( (void *)p, 0 ));
368 vv = caml_swig_alloc(1,C_string);
369 SWIG_Store_field(vv,0,alloc_string(len));
370 memcpy(String_val(SWIG_Field(vv,0)),p,len);
371 CAMLreturn(vv);
372 }
373
374 #define caml_val_obj(v, name) caml_val_obj_helper(v, SWIG_TypeQuery((name)), name)
375 SWIGSTATIC CAML_VALUE caml_val_obj_helper( void *v, swig_type_info *type, char *name) {
376 CAMLparam0();
377 CAMLreturn(callback2(*caml_named_value("caml_create_object_fn"),
378 caml_val_ptr(v,type),
379 copy_string(name)));
380 }
381
382 SWIGSTATIC long caml_long_val_full( CAML_VALUE v, char *name ) {
383 CAMLparam1(v);
384 if( !Is_block(v) ) return 0;
385
386 switch( SWIG_Tag_val(v) ) {
387 case C_bool:
388 case C_char:
389 case C_uchar:
390 case C_short:
391 case C_ushort:
392 case C_int:
393 CAMLreturn(Int_val(SWIG_Field(v,0)));
394 case C_uint:
395 case C_int32:
396 CAMLreturn(Int32_val(SWIG_Field(v,0)));
397 case C_int64:
398 CAMLreturn((long)SWIG_Int64_val(SWIG_Field(v,0)));
399 case C_float:
400 case C_double:
401 CAMLreturn((long)Double_val(SWIG_Field(v,0)));
402 case C_string:
403 CAMLreturn((long)String_val(SWIG_Field(v,0)));
404 case C_ptr:
405 CAMLreturn((long)SWIG_Int64_val(SWIG_Field(SWIG_Field(v,0),0)));
406 case C_enum: {
407 SWIG_CAMLlocal1(ret);
408 CAML_VALUE *enum_to_int = caml_named_value(SWIG_MODULE "_enum_to_int");
409 if( !name ) failwith( "Not an enum conversion" );
410 ret = callback2(*enum_to_int,*caml_named_value(name),v);
411 CAMLreturn(caml_long_val(ret));
412 }
413 default:
414 failwith("No conversion to int");
415 }
416 }
417
418 SWIGSTATIC long caml_long_val( CAML_VALUE v ) {
419 return caml_long_val_full(v,0);
420 }
421
422 SWIGSTATIC double caml_double_val( CAML_VALUE v ) {
423 CAMLparam1(v);
424 if( !Is_block(v) ) return 0.0;
425 switch( SWIG_Tag_val(v) ) {
426 case C_bool:
427 case C_char:
428 case C_uchar:
429 case C_short:
430 case C_ushort:
431 case C_int:
432 CAMLreturn(Int_val(SWIG_Field(v,0)));
433 case C_uint:
434 case C_int32:
435 CAMLreturn(Int32_val(SWIG_Field(v,0)));
436 case C_int64:
437 CAMLreturn(SWIG_Int64_val(SWIG_Field(v,0)));
438 case C_float:
439 case C_double:
440 CAMLreturn(Double_val(SWIG_Field(v,0)));
441 default:
442 fprintf( stderr, "Unknown block tag %d\n", SWIG_Tag_val(v) );
443 failwith("No conversion to double");
444 }
445 }
446
447 SWIGSTATIC int caml_ptr_val_internal( CAML_VALUE v, void **out,
448 swig_type_info *descriptor ) {
449 CAMLparam1(v);
450 void *outptr = NULL;
451 swig_type_info *outdescr = NULL;
452
453 if( v == Val_unit ) {
454 *out = 0;
455 CAMLreturn(0);
456 }
457 if( !Is_block(v) ) return -1;
458 switch( SWIG_Tag_val(v) ) {
459 case C_int:
460 if( !caml_long_val( v ) ) {
461 *out = 0;
462 CAMLreturn(0);
463 } else {
464 *out = 0;
465 CAMLreturn(1);
466 }
467 break;
468 case C_obj:
469 CAMLreturn
470 (caml_ptr_val_internal
471 (callback(*caml_named_value("caml_obj_ptr"),v),
472 out,descriptor));
473 case C_string:
474 outptr = (void *)String_val(SWIG_Field(v,0));
475 break;
476 case C_ptr:
477 outptr = (void *)(long)SWIG_Int64_val(SWIG_Field(v,0));
478 outdescr = (swig_type_info *)(long)SWIG_Int64_val(SWIG_Field(v,1));
479 break;
480 default:
481 *out = 0;
482 CAMLreturn(1);
483 break;
484 }
485
486 CAMLreturn(SWIG_GetPtr(outptr,out,outdescr,descriptor));
487 }
488
489 SWIGSTATIC void *caml_ptr_val( CAML_VALUE v, swig_type_info *descriptor ) {
490 CAMLparam0();
491#ifdef TYPE_CAST_VERBOSE
492 caml_print_val( v );
493#endif
494 void *out = NULL;
495 if( !caml_ptr_val_internal( v, &out, descriptor ) )
496 CAMLreturn(out);
497 else
498 failwith( "No appropriate conversion found." );
499 }
500
501 SWIGSTATIC char *caml_string_val( CAML_VALUE v ) {
502 return (char *)caml_ptr_val( v, 0 );
503 }
504
505 SWIGSTATIC int caml_string_len( CAML_VALUE v ) {
506 switch( SWIG_Tag_val(v) ) {
507 case C_string:
508 return string_length(SWIG_Field(v,0));
509 default:
510 return strlen((char *)caml_ptr_val(v,0));
511 }
512 }
513
514 SWIGSTATIC int caml_bool_check( CAML_VALUE v ) {
515 CAMLparam1(v);
516
517 if( !Is_block(v) ) return 0;
518
519 switch( SWIG_Tag_val(v) ) {
520 case C_bool:
521 case C_ptr:
522 case C_string:
523 CAMLreturn(1);
524 default:
525 CAMLreturn(0);
526 }
527 }
528
529 SWIGSTATIC int caml_int_check( CAML_VALUE v ) {
530 CAMLparam1(v);
531
532 if( !Is_block(v) ) return 0;
533
534 switch( SWIG_Tag_val(v) ) {
535 case C_char:
536 case C_uchar:
537 case C_short:
538 case C_ushort:
539 case C_int:
540 case C_uint:
541 case C_int32:
542 case C_int64:
543 CAMLreturn(1);
544
545 default:
546 CAMLreturn(0);
547 }
548 }
549
550 SWIGSTATIC int caml_float_check( CAML_VALUE v ) {
551 CAMLparam1(v);
552 if( !Is_block(v) ) return 0;
553
554 switch( SWIG_Tag_val(v) ) {
555 case C_float:
556 case C_double:
557 CAMLreturn(1);
558
559 default:
560 CAMLreturn(0);
561 }
562 }
563
564 SWIGSTATIC int caml_ptr_check( CAML_VALUE v ) {
565 CAMLparam1(v);
566 if( !Is_block(v) ) return 0;
567
568 switch( SWIG_Tag_val(v) ) {
569 case C_string:
570 case C_ptr:
571 case C_int64:
572 CAMLreturn(1);
573
574 default:
575 CAMLreturn(0);
576 }
577 }
578
579 static swig_module_info *SWIG_Ocaml_GetModule() {
580 CAML_VALUE pointer;
581
582 pointer = callback(*caml_named_value("swig_find_type_info"), caml_val_int(0));
583 if (Is_block(pointer) && SWIG_Tag_val(pointer) == C_ptr) {
584 return (swig_module_info *)(void *)(long)SWIG_Int64_val(SWIG_Field(pointer,0));
585 }
586 return 0;
587 }
588
589 static void SWIG_Ocaml_SetModule(swig_module_info *pointer) {
590 CAML_VALUE mod_pointer;
591
592 mod_pointer = caml_val_ptr(pointer, NULL);
593 callback(*caml_named_value("swig_set_type_info"), mod_pointer);
594 }
595
596#ifdef __cplusplus
597}
598#endif
599#undef value
600
601/* ocaml keywords */
602/* There's no need to use this, because of my rewriting machinery. C++
603 * words never collide with ocaml keywords */
604//%include "ocamlkw.swg"