Initial commit of OpenSPARC T2 architecture model.
[OpenSPARC-T2-SAM] / sam-t2 / devtools / amd64 / share / swig / 1.3.26 / ocaml / ocamldec.swg
CommitLineData
920dae64
AT
1/* -*-c-*-
2 * -----------------------------------------------------------------------
3 * ocaml/ocamldec.swg
4 * Copyright (C) 2000, 2001 Matthias Koeppe
5 *
6 * Ocaml runtime code -- declarations
7 * ----------------------------------------------------------------------- */
8
9#include <stdio.h>
10#include <string.h>
11#include <stdlib.h>
12
13#ifdef __cplusplus
14#define SWIGEXT extern "C"
15SWIGEXT {
16#else
17#define SWIGEXT
18#endif
19#define value caml_value_t
20#define CAML_VALUE caml_value_t
21#include <caml/alloc.h>
22#include <caml/custom.h>
23#include <caml/mlvalues.h>
24#include <caml/memory.h>
25#include <caml/callback.h>
26#include <caml/fail.h>
27#include <caml/misc.h>
28
29#define caml_array_set swig_caml_array_set
30
31// Adapted from memory.h and mlvalues.h
32
33#define SWIG_CAMLlocal1(x) \
34 caml_value_t x = 0; \
35 CAMLxparam1 (x)
36
37#define SWIG_CAMLlocal2(x, y) \
38 caml_value_t x = 0, y = 0; \
39 CAMLxparam2 (x, y)
40
41#define SWIG_CAMLlocal3(x, y, z) \
42 caml_value_t x = 0, y = 0, z = 0; \
43 CAMLxparam3 (x, y, z)
44
45#define SWIG_CAMLlocal4(x, y, z, t) \
46 caml_value_t x = 0, y = 0, z = 0, t = 0; \
47 CAMLxparam4 (x, y, z, t)
48
49#define SWIG_CAMLlocal5(x, y, z, t, u) \
50 caml_value_t x = 0, y = 0, z = 0, t = 0, u = 0; \
51 CAMLxparam5 (x, y, z, t, u)
52
53#define SWIG_CAMLlocalN(x, size) \
54 caml_value_t x [(size)] = { 0, /* 0, 0, ... */ }; \
55 CAMLxparamN (x, (size))
56
57#define SWIG_Field(x, i) (((caml_value_t *)(x)) [i]) /* Also an l-value. */
58#define SWIG_Store_field(block, offset, val) do{ \
59 mlsize_t caml__temp_offset = (offset); \
60 caml_value_t caml__temp_val = (val); \
61 modify (&SWIG_Field ((block), caml__temp_offset), caml__temp_val); \
62}while(0)
63
64#define SWIG_Data_custom_val(v) ((void *) &SWIG_Field((v), 1))
65#ifdef ARCH_BIG_ENDIAN
66#define SWIG_Tag_val(val) (((unsigned char *) (val)) [-1])
67 /* Also an l-value. */
68#define SWIG_Tag_hp(hp) (((unsigned char *) (hp)) [sizeof(caml_value_t)-1])
69 /* Also an l-value. */
70#else
71#define SWIG_Tag_val(val) (((unsigned char *) (val)) [-sizeof(caml_value_t)])
72 /* Also an l-value. */
73#define SWIG_Tag_hp(hp) (((unsigned char *) (hp)) [0])
74 /* Also an l-value. */
75#endif
76
77#ifndef ARCH_ALIGN_INT64
78#define SWIG_Int64_val(v) (*((int64 *) SWIG_Data_custom_val(v)))
79#else
80CAMLextern int64 Int64_val(caml_value_t v);
81#define SWIG_Int64_val(v) Int64_val(v)
82#endif
83
84#define SWIG_NewPointerObj(p,type,flags) caml_val_ptr(p,type)
85#define SWIG_GetModule(clientdata) SWIG_Ocaml_GetModule()
86#define SWIG_SetModule(clientdata, pointer) SWIG_Ocaml_SetModule(pointer)
87
88#define SWIG_contract_assert(expr, msg) if(!(expr)) {failwith(msg);} else
89
90 SWIGSTATIC int
91 SWIG_GetPtr(void *source, void **result, swig_type_info *type, swig_type_info *result_type);
92
93 SWIGSTATIC void *
94 SWIG_MustGetPtr (CAML_VALUE v, swig_type_info *type);
95
96 SWIGSTATIC CAML_VALUE _wrap_delete_void( CAML_VALUE );
97
98 SWIGSTATIC int enum_to_int( char *name, CAML_VALUE v );
99 SWIGSTATIC CAML_VALUE int_to_enum( char *name, int v );
100
101 SWIGSTATIC CAML_VALUE caml_list_nth( CAML_VALUE lst, int n );
102 SWIGSTATIC CAML_VALUE caml_list_append( CAML_VALUE lst, CAML_VALUE elt );
103 SWIGSTATIC int caml_list_length( CAML_VALUE lst );
104 SWIGSTATIC CAML_VALUE caml_array_new( int n );
105 SWIGSTATIC void caml_array_set( CAML_VALUE arr, int n, CAML_VALUE item );
106 SWIGSTATIC CAML_VALUE caml_array_nth( CAML_VALUE arr, int n );
107 SWIGSTATIC int caml_array_length( CAML_VALUE arr );
108
109 SWIGSTATIC CAML_VALUE caml_val_char( char c );
110 SWIGSTATIC CAML_VALUE caml_val_uchar( unsigned char c );
111
112 SWIGSTATIC CAML_VALUE caml_val_short( short s );
113 SWIGSTATIC CAML_VALUE caml_val_ushort( unsigned short s );
114
115 SWIGSTATIC CAML_VALUE caml_val_int( int x );
116 SWIGSTATIC CAML_VALUE caml_val_uint( unsigned int x );
117
118 SWIGSTATIC CAML_VALUE caml_val_long( long x );
119 SWIGSTATIC CAML_VALUE caml_val_ulong( unsigned long x );
120
121 SWIGSTATIC CAML_VALUE caml_val_float( float f );
122 SWIGSTATIC CAML_VALUE caml_val_double( double d );
123
124 SWIGSTATIC CAML_VALUE caml_val_ptr( void *p, swig_type_info *descriptor );
125
126 SWIGSTATIC CAML_VALUE caml_val_string( const char *str );
127 SWIGSTATIC CAML_VALUE caml_val_string_len( const char *str, int len );
128
129 SWIGSTATIC long caml_long_val( CAML_VALUE v );
130 SWIGSTATIC double caml_double_val( CAML_VALUE v );
131
132 SWIGSTATIC int caml_ptr_val_internal( CAML_VALUE v, void **out,
133 swig_type_info *descriptor );
134 SWIGSTATIC void *caml_ptr_val( CAML_VALUE v, swig_type_info *descriptor );
135
136 SWIGSTATIC char *caml_string_val( CAML_VALUE v );
137 SWIGSTATIC int caml_string_len( CAML_VALUE v );
138
139#ifdef __cplusplus
140}
141#endif
142
143/* mzschemedec.swg ends here */