1 /**************************************************************************/
2 /*                                                                        */
3 /*                                 OCaml                                  */
4 /*                                                                        */
5 /*           Damien Doligez, projet Moscova, INRIA Rocquencourt           */
6 /*                                                                        */
7 /*   Copyright 2003 Institut National de Recherche en Informatique et     */
8 /*     en Automatique.                                                    */
9 /*                                                                        */
10 /*   All rights reserved.  This file is distributed under the terms of    */
11 /*   the GNU Lesser General Public License version 2.1, with the          */
12 /*   special exception on linking described in the file LICENSE.          */
13 /*                                                                        */
14 /**************************************************************************/
15 
16 /* definitions for compatibility with old identifiers */
17 
18 #ifndef CAML_COMPATIBILITY_H
19 #define CAML_COMPATIBILITY_H
20 
21 /* internal global variables renamed between 4.02.1 and 4.03.0 */
22 #define caml_stat_top_heap_size Bsize_wsize(caml_stat_top_heap_wsz)
23 #define caml_stat_heap_size Bsize_wsize(caml_stat_heap_wsz)
24 
25 #ifndef CAML_NAME_SPACE
26 
27 /*
28    #define --> CAMLextern  (defined with CAMLexport or CAMLprim)
29    (rien)  --> CAMLprim
30    g       --> global C identifier
31    x       --> special case
32 
33    SP* signals the special cases:
34    - when the identifier was not simply prefixed with [caml_]
35    - when the [caml_] version was already used for something else, and
36      was renamed out of the way (watch out for [caml_alloc] and
37      [caml_array_bound_error] in *.s)
38 */
39 
40 /* a faire:
41    - ui_*   (reverifier que win32.c n'en depend pas)
42 */
43 
44 
45 /* **** alloc.c */
46 #define alloc caml_alloc /*SP*/
47 #define alloc_small caml_alloc_small
48 #define alloc_tuple caml_alloc_tuple
49 #define alloc_string caml_alloc_string
50 #define alloc_final caml_alloc_final
51 #define copy_string caml_copy_string
52 #define alloc_array caml_alloc_array
53 #define copy_string_array caml_copy_string_array
54 #define convert_flag_list caml_convert_flag_list
55 
56 /* **** array.c */
57 
58 /* **** backtrace.c */
59 #define backtrace_active caml_backtrace_active
60 #define backtrace_pos caml_backtrace_pos
61 #define backtrace_buffer caml_backtrace_buffer
62 #define backtrace_last_exn caml_backtrace_last_exn
63 #define print_exception_backtrace caml_print_exception_backtrace
64 
65 /* **** callback.c */
66 #define callback_depth caml_callback_depth
67 #define callbackN_exn caml_callbackN_exn
68 #define callback_exn caml_callback_exn
69 #define callback2_exn caml_callback2_exn
70 #define callback3_exn caml_callback3_exn
71 #define callback caml_callback
72 #define callback2 caml_callback2
73 #define callback3 caml_callback3
74 #define callbackN caml_callbackN
75 
76 /* **** compact.c */
77 
78 /* **** compare.c */
79 #define compare_unordered caml_compare_unordered
80 
81 /* **** custom.c */
82 #define alloc_custom caml_alloc_custom
83 #define register_custom_operations caml_register_custom_operations
84 
85 /* **** debugger.c */
86 
87 /* **** dynlink.c */
88 
89 /* **** extern.c */
90 #define output_val caml_output_val
91 #define output_value_to_malloc caml_output_value_to_malloc
92 #define output_value_to_block caml_output_value_to_block
93 #define serialize_int_1 caml_serialize_int_1
94 #define serialize_int_2 caml_serialize_int_2
95 #define serialize_int_4 caml_serialize_int_4
96 #define serialize_int_8 caml_serialize_int_8
97 #define serialize_float_4 caml_serialize_float_4
98 #define serialize_float_8 caml_serialize_float_8
99 #define serialize_block_1 caml_serialize_block_1
100 #define serialize_block_2 caml_serialize_block_2
101 #define serialize_block_4 caml_serialize_block_4
102 #define serialize_block_8 caml_serialize_block_8
103 #define serialize_block_float_8 caml_serialize_block_float_8
104 
105 /* **** fail.c */
106 #define external_raise caml_external_raise
107 #define mlraise caml_raise /*SP*/
108 #define raise_constant caml_raise_constant
109 #define raise_with_arg caml_raise_with_arg
110 #define raise_with_string caml_raise_with_string
111 #define failwith caml_failwith
112 #define invalid_argument caml_invalid_argument
113 #define array_bound_error caml_array_bound_error /*SP*/
114 #define raise_out_of_memory caml_raise_out_of_memory
115 #define raise_stack_overflow caml_raise_stack_overflow
116 #define raise_sys_error caml_raise_sys_error
117 #define raise_end_of_file caml_raise_end_of_file
118 #define raise_zero_divide caml_raise_zero_divide
119 #define raise_not_found caml_raise_not_found
120 #define raise_sys_blocked_io caml_raise_sys_blocked_io
121 /* **** asmrun/fail.c */
122 /* **** asmrun/<arch>.s */
123 
124 /* **** finalise.c */
125 
126 /* **** fix_code.c */
127 
128 /* **** floats.c */
129 /*#define Double_val caml_Double_val             done in mlvalues.h as needed */
130 /*#define Store_double_val caml_Store_double_val done in mlvalues.h as needed */
131 #define copy_double caml_copy_double
132 
133 /* **** freelist.c */
134 
135 /* **** gc_ctrl.c */
136 
137 /* **** globroots.c */
138 #define register_global_root caml_register_global_root
139 #define remove_global_root caml_remove_global_root
140 
141 /* **** hash.c */
142 #define hash_variant caml_hash_variant
143 
144 /* **** instrtrace.c */
145 
146 /* **** intern.c */
147 #define input_val caml_input_val
148 #define input_val_from_string caml_input_val_from_string
149 #define input_value_from_malloc caml_input_value_from_malloc
150 #define input_value_from_block caml_input_value_from_block
151 #define deserialize_uint_1 caml_deserialize_uint_1
152 #define deserialize_sint_1 caml_deserialize_sint_1
153 #define deserialize_uint_2 caml_deserialize_uint_2
154 #define deserialize_sint_2 caml_deserialize_sint_2
155 #define deserialize_uint_4 caml_deserialize_uint_4
156 #define deserialize_sint_4 caml_deserialize_sint_4
157 #define deserialize_uint_8 caml_deserialize_uint_8
158 #define deserialize_sint_8 caml_deserialize_sint_8
159 #define deserialize_float_4 caml_deserialize_float_4
160 #define deserialize_float_8 caml_deserialize_float_8
161 #define deserialize_block_1 caml_deserialize_block_1
162 #define deserialize_block_2 caml_deserialize_block_2
163 #define deserialize_block_4 caml_deserialize_block_4
164 #define deserialize_block_8 caml_deserialize_block_8
165 #define deserialize_block_float_8 caml_deserialize_block_float_8
166 #define deserialize_error caml_deserialize_error
167 
168 /* **** interp.c */
169 
170 /* **** ints.c */
171 #define int32_ops caml_int32_ops
172 #define copy_int32 caml_copy_int32
173 /*#define Int64_val caml_Int64_val   *** done in mlvalues.h as needed */
174 #define int64_ops caml_int64_ops
175 #define copy_int64 caml_copy_int64
176 #define nativeint_ops caml_nativeint_ops
177 #define copy_nativeint caml_copy_nativeint
178 
179 /* **** io.c */
180 #define channel_mutex_free caml_channel_mutex_free
181 #define channel_mutex_lock caml_channel_mutex_lock
182 #define channel_mutex_unlock caml_channel_mutex_unlock
183 #define channel_mutex_unlock_exn caml_channel_mutex_unlock_exn
184 #define all_opened_channels caml_all_opened_channels
185 #define open_descriptor_in caml_open_descriptor_in /*SP*/
186 #define open_descriptor_out caml_open_descriptor_out /*SP*/
187 #define close_channel caml_close_channel /*SP*/
188 #define channel_size caml_channel_size /*SP*/
189 #define channel_binary_mode caml_channel_binary_mode
190 #define flush_partial caml_flush_partial /*SP*/
191 #define flush caml_flush /*SP*/
192 #define putword caml_putword
193 #define putblock caml_putblock
194 #define really_putblock caml_really_putblock
195 #define seek_out caml_seek_out /*SP*/
196 #define pos_out caml_pos_out /*SP*/
197 #define do_read caml_do_read
198 #define refill caml_refill
199 #define getword caml_getword
200 #define getblock caml_getblock
201 #define really_getblock caml_really_getblock
202 #define seek_in caml_seek_in /*SP*/
203 #define pos_in caml_pos_in /*SP*/
204 #define input_scan_line caml_input_scan_line /*SP*/
205 #define finalize_channel caml_finalize_channel
206 #define alloc_channel caml_alloc_channel
207 /*#define Val_file_offset caml_Val_file_offset   *** done in io.h as needed */
208 /*#define File_offset_val caml_File_offset_val   *** done in io.h as needed */
209 
210 /* **** lexing.c */
211 
212 /* **** main.c */
213 /* *** no change */
214 
215 /* **** major_gc.c */
216 #define heap_start caml_heap_start
217 #define page_table caml_page_table
218 
219 /* **** md5.c */
220 #define md5_string caml_md5_string
221 #define md5_chan caml_md5_chan
222 #define MD5Init caml_MD5Init
223 #define MD5Update caml_MD5Update
224 #define MD5Final caml_MD5Final
225 #define MD5Transform caml_MD5Transform
226 
227 /* **** memory.c */
228 #define alloc_shr caml_alloc_shr
229 #define initialize caml_initialize
230 #define modify caml_modify
231 #define stat_alloc caml_stat_alloc
232 #define stat_free caml_stat_free
233 #define stat_resize caml_stat_resize
234 
235 /* **** meta.c */
236 
237 /* **** minor_gc.c */
238 #define young_start caml_young_start
239 #define young_end caml_young_end
240 #define young_ptr caml_young_ptr
241 #define young_limit caml_young_limit
242 #define ref_table caml_ref_table
243 #define minor_collection caml_minor_collection
244 #define check_urgent_gc caml_check_urgent_gc
245 
246 /* **** misc.c */
247 
248 /* **** obj.c */
249 
250 /* **** parsing.c */
251 
252 /* **** prims.c */
253 
254 /* **** printexc.c */
255 #define format_caml_exception caml_format_exception /*SP*/
256 
257 /* **** roots.c */
258 #define local_roots caml_local_roots
259 #define scan_roots_hook caml_scan_roots_hook
260 #define do_local_roots caml_do_local_roots
261 
262 /* **** signals.c */
263 #define pending_signals caml_pending_signals
264 #define something_to_do caml_something_to_do
265 #define enter_blocking_section_hook caml_enter_blocking_section_hook
266 #define leave_blocking_section_hook caml_leave_blocking_section_hook
267 #define try_leave_blocking_section_hook caml_try_leave_blocking_section_hook
268 #define async_action_hook caml_async_action_hook
269 #define enter_blocking_section caml_enter_blocking_section
270 #define leave_blocking_section caml_leave_blocking_section
271 #define convert_signal_number caml_convert_signal_number
272 /* **** asmrun/signals.c */
273 #define garbage_collection caml_garbage_collection
274 
275 /* **** stacks.c */
276 #define stack_low caml_stack_low
277 #define stack_high caml_stack_high
278 #define stack_threshold caml_stack_threshold
279 #define extern_sp caml_extern_sp
280 #define trapsp caml_trapsp
281 #define trap_barrier caml_trap_barrier
282 
283 /* **** startup.c */
284 #define atom_table caml_atom_table
285 /* **** asmrun/startup.c */
286 #define static_data_start caml_static_data_start
287 #define static_data_end caml_static_data_end
288 
289 /* **** str.c */
290 #define string_length caml_string_length
291 
292 /* **** sys.c */
293 #define sys_error caml_sys_error
294 #define sys_exit caml_sys_exit
295 
296 /* **** terminfo.c */
297 
298 /* **** unix.c  &  win32.c */
299 #define search_exe_in_path caml_search_exe_in_path
300 
301 /* **** weak.c */
302 
303 /* **** asmcomp/asmlink.ml */
304 
305 /* **** asmcomp/cmmgen.ml */
306 
307 /* **** asmcomp/asmlink.ml, asmcomp/cmmgen.ml, asmcomp/compilenv.ml */
308 
309 /* ************************************************************* */
310 
311 /* **** otherlibs/bigarray */
312 #define int8 caml_ba_int8
313 #define uint8 caml_ba_uint8
314 #define int16 caml_ba_int16
315 #define uint16 caml_ba_uint16
316 #define MAX_NUM_DIMS CAML_BA_MAX_NUM_DIMS
317 #define caml_bigarray_kind caml_ba_kind
318 #define BIGARRAY_FLOAT32 CAML_BA_FLOAT32
319 #define BIGARRAY_FLOAT64 CAML_BA_FLOAT64
320 #define BIGARRAY_SINT8 CAML_BA_SINT8
321 #define BIGARRAY_UINT8 CAML_BA_UINT8
322 #define BIGARRAY_SINT16 CAML_BA_SINT16
323 #define BIGARRAY_UINT16 CAML_BA_UINT16
324 #define BIGARRAY_INT32 CAML_BA_INT32
325 #define BIGARRAY_INT64 CAML_BA_INT64
326 #define BIGARRAY_CAML_INT CAML_BA_CAML_INT
327 #define BIGARRAY_NATIVE_INT CAML_BA_NATIVE_INT
328 #define BIGARRAY_COMPLEX32 CAML_BA_COMPLEX32
329 #define BIGARRAY_COMPLEX64 CAML_BA_COMPLEX64
330 #define BIGARRAY_KIND_MASK CAML_BA_KIND_MASK
331 #define caml_bigarray_layout caml_ba_layout
332 #define BIGARRAY_C_LAYOUT CAML_BA_C_LAYOUT
333 #define BIGARRAY_FORTRAN_LAYOUT CAML_BA_FORTRAN_LAYOUT
334 #define BIGARRAY_LAYOUT_MASK CAML_BA_LAYOUT_MASK
335 #define caml_bigarray_managed caml_ba_managed
336 #define BIGARRAY_EXTERNAL CAML_BA_EXTERNAL
337 #define BIGARRAY_MANAGED CAML_BA_MANAGED
338 #define BIGARRAY_MAPPED_FILE CAML_BA_MAPPED_FILE
339 #define BIGARRAY_MANAGED_MASK CAML_BA_MANAGED_MASK
340 #define caml_bigarray_proxy caml_ba_proxy
341 #define caml_bigarray caml_ba_array
342 #define Bigarray_val Caml_ba_array_val
343 #define Data_bigarray_val Caml_ba_data_val
344 #define alloc_bigarray caml_ba_alloc
345 #define alloc_bigarray_dims caml_ba_alloc_dims
346 #define bigarray_map_file caml_ba_map_file
347 #define bigarray_unmap_file caml_ba_unmap_file
348 #define bigarray_element_size caml_ba_element_size
349 #define bigarray_byte_size caml_ba_byte_size
350 #define bigarray_deserialize caml_ba_deserialize
351 #define MAX_BIGARRAY_MEMORY CAML_BA_MAX_MEMORY
352 #define bigarray_create caml_ba_create
353 #define bigarray_get_N caml_ba_get_N
354 #define bigarray_get_1 caml_ba_get_1
355 #define bigarray_get_2 caml_ba_get_2
356 #define bigarray_get_3 caml_ba_get_3
357 #define bigarray_get_generic caml_ba_get_generic
358 #define bigarray_set_1 caml_ba_set_1
359 #define bigarray_set_2 caml_ba_set_2
360 #define bigarray_set_3 caml_ba_set_3
361 #define bigarray_set_N caml_ba_set_N
362 #define bigarray_set_generic caml_ba_set_generic
363 #define bigarray_num_dims caml_ba_num_dims
364 #define bigarray_dim caml_ba_dim
365 #define bigarray_kind caml_ba_kind
366 #define bigarray_layout caml_ba_layout
367 #define bigarray_slice caml_ba_slice
368 #define bigarray_sub caml_ba_sub
369 #define bigarray_blit caml_ba_blit
370 #define bigarray_fill caml_ba_fill
371 #define bigarray_reshape caml_ba_reshape
372 #define bigarray_init caml_ba_init
373 
374 #endif /* CAML_NAME_SPACE */
375 #endif /* CAML_COMPATIBILITY_H */
376