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