Initial commit of OpenSPARC T2 architecture model.
[OpenSPARC-T2-SAM] / sam-t2 / devtools / v9 / share / swig / 1.3.26 / ocaml / cstring.i
CommitLineData
920dae64
AT
1/* -*- C++ -*-
2 * cstring.i
3 * $Header: /cvsroot/swig/SWIG/Lib/ocaml/cstring.i,v 1.5 2004/10/06 16:51:20 marcelomatus Exp $
4 *
5 * Author(s): Art Yerkes
6 * Modified from David Beazley (beazley@cs.uchicago.edu)
7 *
8 * This file provides typemaps and macros for dealing with various forms
9 * of C character string handling. The primary use of this module
10 * is in returning character data that has been allocated or changed in
11 * some way.
12 */
13
14%include "fragments.i"
15
16/* %cstring_input_binary(TYPEMAP, SIZE)
17 *
18 * Macro makes a function accept binary string data along with
19 * a size.
20 */
21
22%define %cstring_input_binary(TYPEMAP, SIZE)
23%apply (char *STRING, int LENGTH) { (TYPEMAP, SIZE) };
24%enddef
25
26/*
27 * %cstring_bounded_output(TYPEMAP, MAX)
28 *
29 * This macro is used to return a NULL-terminated output string of
30 * some maximum length. For example:
31 *
32 * %cstring_bounded_output(char *outx, 512);
33 * void foo(char *outx) {
34 * sprintf(outx,"blah blah\n");
35 * }
36 *
37 */
38
39%define %cstring_bounded_output(TYPEMAP,MAX)
40%typemap(ignore) TYPEMAP(char temp[MAX+1]) {
41 $1 = ($1_ltype) temp;
42}
43%typemap(argout,fragment="t_output_helper") TYPEMAP {
44 $1[MAX] = 0;
45 $result = caml_list_append($result,caml_val_string(str));
46}
47%enddef
48
49/*
50 * %cstring_chunk_output(TYPEMAP, SIZE)
51 *
52 * This macro is used to return a chunk of binary string data.
53 * Embedded NULLs are okay. For example:
54 *
55 * %cstring_chunk_output(char *outx, 512);
56 * void foo(char *outx) {
57 * memmove(outx, somedata, 512);
58 * }
59 *
60 */
61
62%define %cstring_chunk_output(TYPEMAP,SIZE)
63%typemap(ignore) TYPEMAP(char temp[SIZE]) {
64 $1 = ($1_ltype) temp;
65}
66%typemap(argout) TYPEMAP {
67 $result = caml_list_append($result,caml_val_string_len($1,SIZE));
68}
69%enddef
70
71/*
72 * %cstring_bounded_mutable(TYPEMAP, SIZE)
73 *
74 * This macro is used to wrap a string that's going to mutate.
75 *
76 * %cstring_bounded_mutable(char *in, 512);
77 * void foo(in *x) {
78 * while (*x) {
79 * *x = toupper(*x);
80 * x++;
81 * }
82 * }
83 *
84 */
85
86
87%define %cstring_bounded_mutable(TYPEMAP,MAX)
88%typemap(in) TYPEMAP(char temp[MAX+1]) {
89 char *t = (char *)caml_ptr_val($input);
90 strncpy(temp,t,MAX);
91 $1 = ($1_ltype) temp;
92}
93%typemap(argout) TYPEMAP {
94 $result = caml_list_append($result,caml_val_string_len($1,MAX));
95}
96%enddef
97
98/*
99 * %cstring_mutable(TYPEMAP [, expansion])
100 *
101 * This macro is used to wrap a string that will mutate in place.
102 * It may change size up to a user-defined expansion.
103 *
104 * %cstring_mutable(char *in);
105 * void foo(in *x) {
106 * while (*x) {
107 * *x = toupper(*x);
108 * x++;
109 * }
110 * }
111 *
112 */
113
114%define %cstring_mutable(TYPEMAP,...)
115%typemap(in) TYPEMAP {
116 char *t = String_val($input);
117 int n = string_length($input);
118 $1 = ($1_ltype) t;
119#if #__VA_ARGS__ == ""
120#ifdef __cplusplus
121 $1 = ($1_ltype) new char[n+1];
122#else
123 $1 = ($1_ltype) malloc(n+1);
124#endif
125#else
126#ifdef __cplusplus
127 $1 = ($1_ltype) new char[n+1+__VA_ARGS__];
128#else
129 $1 = ($1_ltype) malloc(n+1+__VA_ARGS__);
130#endif
131#endif
132 memmove($1,t,n);
133 $1[n] = 0;
134}
135
136%typemap(argout) TYPEMAP {
137 $result = caml_list_append($result,caml_val_string($1));
138#ifdef __cplusplus
139 delete[] $1;
140#else
141 free($1);
142#endif
143}
144%enddef
145
146/*
147 * %cstring_output_maxsize(TYPEMAP, SIZE)
148 *
149 * This macro returns data in a string of some user-defined size.
150 *
151 * %cstring_output_maxsize(char *outx, int max) {
152 * void foo(char *outx, int max) {
153 * sprintf(outx,"blah blah\n");
154 * }
155 */
156
157%define %cstring_output_maxsize(TYPEMAP, SIZE)
158%typemap(in) (TYPEMAP, SIZE) {
159 $2 = caml_val_long($input);
160#ifdef __cplusplus
161 $1 = ($1_ltype) new char[$2+1];
162#else
163 $1 = ($1_ltype) malloc($2+1);
164#endif
165}
166%typemap(argout) (TYPEMAP,SIZE) {
167 $result = caml_list_append($result,caml_val_string($1));
168#ifdef __cplusplus
169 delete [] $1;
170#else
171 free($1);
172#endif
173}
174%enddef
175
176/*
177 * %cstring_output_withsize(TYPEMAP, SIZE)
178 *
179 * This macro is used to return character data along with a size
180 * parameter.
181 *
182 * %cstring_output_maxsize(char *outx, int *max) {
183 * void foo(char *outx, int *max) {
184 * sprintf(outx,"blah blah\n");
185 * *max = strlen(outx);
186 * }
187 */
188
189%define %cstring_output_withsize(TYPEMAP, SIZE)
190%typemap(in) (TYPEMAP, SIZE) {
191 int n = caml_val_long($input);
192#ifdef __cplusplus
193 $1 = ($1_ltype) new char[n+1];
194 $2 = ($2_ltype) new $*1_ltype;
195#else
196 $1 = ($1_ltype) malloc(n+1);
197 $2 = ($2_ltype) malloc(sizeof($*1_ltype));
198#endif
199 *$2 = n;
200}
201%typemap(argout) (TYPEMAP,SIZE) {
202 $result = caml_list_append($result,caml_val_string_len($1,$2));
203#ifdef __cplusplus
204 delete [] $1;
205 delete $2;
206#else
207 free($1);
208 free($2);
209#endif
210}
211%enddef
212
213/*
214 * %cstring_output_allocate(TYPEMAP, RELEASE)
215 *
216 * This macro is used to return character data that was
217 * allocated with new or malloc.
218 *
219 * %cstring_output_allocated(char **outx, free($1));
220 * void foo(char **outx) {
221 * *outx = (char *) malloc(512);
222 * sprintf(outx,"blah blah\n");
223 * }
224 */
225
226%define %cstring_output_allocate(TYPEMAP, RELEASE)
227%typemap(ignore) TYPEMAP($*1_ltype temp = 0) {
228 $1 = &temp;
229}
230
231%typemap(argout) TYPEMAP {
232 if (*$1) {
233 $result = caml_list_append($result,caml_val_string($1));
234 RELEASE;
235 } else {
236 $result = caml_list_append($result,caml_val_ptr($1));
237 }
238}
239%enddef
240
241/*
242 * %cstring_output_allocate_size(TYPEMAP, SIZE, RELEASE)
243 *
244 * This macro is used to return character data that was
245 * allocated with new or malloc.
246 *
247 * %cstring_output_allocated(char **outx, int *sz, free($1));
248 * void foo(char **outx, int *sz) {
249 * *outx = (char *) malloc(512);
250 * sprintf(outx,"blah blah\n");
251 * *sz = strlen(outx);
252 * }
253 */
254
255%define %cstring_output_allocate_size(TYPEMAP, SIZE, RELEASE)
256%typemap(ignore) (TYPEMAP, SIZE) ($*1_ltype temp = 0, $*2_ltype tempn) {
257 $1 = &temp;
258 $2 = &tempn;
259}
260
261%typemap(argout)(TYPEMAP,SIZE) {
262 if (*$1) {
263 $result = caml_list_append($result,caml_val_string_len($1,$2));
264 RELEASE;
265 } else
266 $result = caml_list_append($result,caml_val_ptr($1));
267}
268%enddef
269
270
271
272
273
274