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