Skip to content

Commit 31943ba

Browse files
author
Damien Doligez
committed
depollution suite (PR#1914 et PR#1956); byterun/weak.c: PR#1929 suite
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@6041 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
1 parent dbf40e0 commit 31943ba

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

65 files changed

+638
-511
lines changed

Diff for: asmcomp/cmmgen.ml

+4-3
Original file line numberDiff line numberDiff line change
@@ -332,7 +332,7 @@ let make_alloc_generic set_fn tag wordsize args =
332332
| e1::el -> Csequence(set_fn (Cvar id) (Cconst_int idx) e1,
333333
fill_fields (idx + 2) el) in
334334
Clet(id,
335-
Cop(Cextcall("alloc", typ_addr, true),
335+
Cop(Cextcall("caml_alloc", typ_addr, true),
336336
[Cconst_int wordsize; Cconst_int tag]),
337337
fill_fields 1 args)
338338
end
@@ -1451,7 +1451,8 @@ and transl_letrec bindings cont =
14511451
let rec init_blocks = function
14521452
| [] -> fill_nonrec bsz
14531453
| (id, exp, RHS_block sz) :: rem ->
1454-
Clet(id, Cop(Cextcall("alloc_dummy", typ_addr, true), [int_const sz]),
1454+
Clet(id, Cop(Cextcall("caml_alloc_dummy", typ_addr, true),
1455+
[int_const sz]),
14551456
init_blocks rem)
14561457
| (id, exp, RHS_nonrec) :: rem ->
14571458
Clet (id, Cconst_int 0, init_blocks rem)
@@ -1463,7 +1464,7 @@ and transl_letrec bindings cont =
14631464
and fill_blocks = function
14641465
| [] -> cont
14651466
| (id, exp, RHS_block _) :: rem ->
1466-
Csequence(Cop(Cextcall("update_dummy", typ_void, false),
1467+
Csequence(Cop(Cextcall("caml_update_dummy", typ_void, false),
14671468
[Cvar id; transl exp]),
14681469
fill_blocks rem)
14691470
| (id, exp, RHS_nonrec) :: rem ->

Diff for: asmrun/Makefile

+2-1
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,8 @@
1616
include ../config/Makefile
1717

1818
CC=$(NATIVECC)
19-
FLAGS=-I../byterun -DNATIVE_CODE -DTARGET_$(ARCH) -DSYS_$(SYSTEM)
19+
FLAGS=-I../byterun -DCAML_NAME_SPACE -DNATIVE_CODE \
20+
-DTARGET_$(ARCH) -DSYS_$(SYSTEM)
2021
CFLAGS=$(FLAGS) -O $(NATIVECCCOMPOPTS)
2122
DFLAGS=$(FLAGS) -g -DDEBUG $(NATIVECCCOMPOPTS)
2223
PFLAGS=$(FLAGS) -pg -O -DPROFILING $(NATIVECCPROFOPTS)

Diff for: asmrun/fail.c

+3-3
Original file line numberDiff line numberDiff line change
@@ -66,7 +66,7 @@ void raise_constant(value tag)
6666
{
6767
value bucket;
6868
Begin_root (tag);
69-
bucket = alloc_small (1, 0);
69+
bucket = caml_alloc_small (1, 0);
7070
Field(bucket, 0) = tag;
7171
End_roots ();
7272
mlraise(bucket);
@@ -76,7 +76,7 @@ void raise_with_arg(value tag, value arg)
7676
{
7777
value bucket;
7878
Begin_roots2 (tag, arg);
79-
bucket = alloc_small (2, 0);
79+
bucket = caml_alloc_small (2, 0);
8080
Field(bucket, 0) = tag;
8181
Field(bucket, 1) = arg;
8282
End_roots ();
@@ -85,7 +85,7 @@ void raise_with_arg(value tag, value arg)
8585

8686
void raise_with_string(value tag, char *msg)
8787
{
88-
raise_with_arg(tag, copy_string(msg));
88+
raise_with_arg(tag, caml_copy_string(msg));
8989
}
9090

9191
void failwith (char *msg)

Diff for: asmrun/signals.c

+6-6
Original file line numberDiff line numberDiff line change
@@ -62,7 +62,7 @@ extern sighandler win32_signal(int sig, sighandler action);
6262
ctx_version = 2;
6363
}
6464
}else{
65-
fatal_error ("cannot determine SIGCONTEXT format");
65+
caml_fatal_error ("cannot determine SIGCONTEXT format");
6666
}
6767
}
6868

@@ -440,14 +440,14 @@ value install_signal_handler(value signal_number, value action) /* ML */
440440
#else
441441
sigact.sa_flags = 0;
442442
#endif
443-
if (sigaction(sig, &sigact, &oldsigact) == -1) sys_error(NO_ARG);
443+
if (sigaction(sig, &sigact, &oldsigact) == -1) caml_sys_error(NO_ARG);
444444
oldact = oldsigact.sa_handler;
445445
#else
446446
oldact = signal(sig, act);
447-
if (oldact == SIG_ERR) sys_error(NO_ARG);
447+
if (oldact == SIG_ERR) caml_sys_error(NO_ARG);
448448
#endif
449449
if (oldact == (void (*)(int)) handle_signal) {
450-
res = alloc_small(1, 0); /* Signal_handle */
450+
res = caml_alloc_small(1, 0); /* Signal_handle */
451451
Field(res, 0) = Field(signal_handlers, sig);
452452
}
453453
else if (oldact == SIG_IGN)
@@ -456,7 +456,7 @@ value install_signal_handler(value signal_number, value action) /* ML */
456456
res = Val_int(0); /* Signal_default */
457457
if (Is_block(action)) {
458458
if (signal_handlers == 0) {
459-
signal_handlers = alloc(NSIG, 0);
459+
signal_handlers = caml_alloc(NSIG, 0);
460460
register_global_root(&signal_handlers);
461461
}
462462
modify(&Field(signal_handlers, sig), Field(action, 0));
@@ -510,7 +510,7 @@ static void trap_handler(int sig, siginfo_t * info, void * context)
510510
static void trap_handler(int sig)
511511
{
512512
/* TODO: recover registers from context and call array_bound_error */
513-
fatal_error("Fatal error: out-of-bound access in array or string\n");
513+
caml_fatal_error("Fatal error: out-of-bound access in array or string\n");
514514
}
515515
#endif
516516

Diff for: asmrun/startup.c

+2-2
Original file line numberDiff line numberDiff line change
@@ -104,7 +104,7 @@ static void parse_camlrunparam(void)
104104
case 'l': scanmult (opt, &max_stack_init); break;
105105
case 'o': scanmult (opt, &percent_free_init); break;
106106
case 'O': scanmult (opt, &max_percent_free_init); break;
107-
case 'v': scanmult (opt, &verb_gc); break;
107+
case 'v': scanmult (opt, &caml_verb_gc); break;
108108
case 'p': parser_trace = 1; break;
109109
}
110110
}
@@ -130,7 +130,7 @@ void caml_main(char **argv)
130130
init_ieee_floats();
131131
init_custom_operations();
132132
#ifdef DEBUG
133-
verb_gc = 63;
133+
caml_verb_gc = 63;
134134
#endif
135135
parse_camlrunparam();
136136
init_gc (minor_heap_init, heap_size_init, heap_chunk_init,

Diff for: boot/ocamlc

223 Bytes
Binary file not shown.

Diff for: boot/ocamllex

90 Bytes
Binary file not shown.

Diff for: bytecomp/bytegen.ml

+2-2
Original file line numberDiff line numberDiff line change
@@ -467,7 +467,7 @@ let rec comp_expr env exp sz cont =
467467
| [] -> comp_nonrec new_env sz ndecl decl_size
468468
| (id, exp, RHS_block blocksize) :: rem ->
469469
Kconst(Const_base(Const_int blocksize)) ::
470-
Kccall("alloc_dummy", 1) :: Kpush ::
470+
Kccall("caml_alloc_dummy", 1) :: Kpush ::
471471
comp_init (add_var id (sz+1) new_env) (sz+1) rem
472472
| (id, exp, RHS_nonrec) :: rem ->
473473
Kconst(Const_base(Const_int 0)) :: Kpush ::
@@ -483,7 +483,7 @@ let rec comp_expr env exp sz cont =
483483
| [] -> comp_expr new_env body sz (add_pop ndecl cont)
484484
| (id, exp, RHS_block blocksize) :: rem ->
485485
comp_expr new_env exp sz
486-
(Kpush :: Kacc i :: Kccall("update_dummy", 2) ::
486+
(Kpush :: Kacc i :: Kccall("caml_update_dummy", 2) ::
487487
comp_rec new_env sz (i-1) rem)
488488
| (id, exp, RHS_nonrec) :: rem ->
489489
comp_rec new_env sz (i-1) rem

Diff for: bytecomp/translmod.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -198,7 +198,7 @@ let reorder_rec_bindings bindings =
198198
(* Generate lambda-code for a reordered list of bindings *)
199199

200200
let prim_update =
201-
{ prim_name = "update_dummy";
201+
{ prim_name = "caml_update_dummy";
202202
prim_arity = 2;
203203
prim_alloc = true;
204204
prim_native_name = "";

Diff for: byterun/alloc.c

+18-17
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@
2929
#define Setup_for_gc
3030
#define Restore_after_gc
3131

32-
CAMLexport value alloc (mlsize_t wosize, tag_t tag)
32+
CAMLexport value caml_alloc (mlsize_t wosize, tag_t tag)
3333
{
3434
value result;
3535
mlsize_t i;
@@ -51,7 +51,7 @@ CAMLexport value alloc (mlsize_t wosize, tag_t tag)
5151
return result;
5252
}
5353

54-
CAMLexport value alloc_small (mlsize_t wosize, tag_t tag)
54+
CAMLexport value caml_alloc_small (mlsize_t wosize, tag_t tag)
5555
{
5656
value result;
5757

@@ -62,12 +62,12 @@ CAMLexport value alloc_small (mlsize_t wosize, tag_t tag)
6262
return result;
6363
}
6464

65-
CAMLexport value alloc_tuple(mlsize_t n)
65+
CAMLexport value caml_alloc_tuple(mlsize_t n)
6666
{
67-
return alloc(n, 0);
67+
return caml_alloc(n, 0);
6868
}
6969

70-
CAMLexport value alloc_string (mlsize_t len)
70+
CAMLexport value caml_alloc_string (mlsize_t len)
7171
{
7272
value result;
7373
mlsize_t offset_index;
@@ -85,25 +85,26 @@ CAMLexport value alloc_string (mlsize_t len)
8585
return result;
8686
}
8787

88-
CAMLexport value alloc_final (mlsize_t len, final_fun fun,
89-
mlsize_t mem, mlsize_t max)
88+
CAMLexport value caml_alloc_final (mlsize_t len, final_fun fun,
89+
mlsize_t mem, mlsize_t max)
9090
{
9191
return alloc_custom(final_custom_operations(fun),
9292
len * sizeof(value), mem, max);
9393
}
9494

95-
CAMLexport value copy_string(char const *s)
95+
CAMLexport value caml_copy_string(char const *s)
9696
{
9797
int len;
9898
value res;
9999

100100
len = strlen(s);
101-
res = alloc_string(len);
101+
res = caml_alloc_string(len);
102102
memmove(String_val(res), s, len);
103103
return res;
104104
}
105105

106-
CAMLexport value alloc_array(value (*funct)(char const *), char const ** arr)
106+
CAMLexport value caml_alloc_array(value (*funct)(char const *),
107+
char const ** arr)
107108
{
108109
CAMLparam0 ();
109110
mlsize_t nbr, n;
@@ -114,7 +115,7 @@ CAMLexport value alloc_array(value (*funct)(char const *), char const ** arr)
114115
if (nbr == 0) {
115116
CAMLreturn (Atom(0));
116117
} else {
117-
result = alloc (nbr, 0);
118+
result = caml_alloc (nbr, 0);
118119
for (n = 0; n < nbr; n++) {
119120
/* The two statements below must be separate because of evaluation
120121
order (don't take the address &Field(result, n) before
@@ -126,12 +127,12 @@ CAMLexport value alloc_array(value (*funct)(char const *), char const ** arr)
126127
}
127128
}
128129

129-
CAMLexport value copy_string_array(char const ** arr)
130+
CAMLexport value caml_copy_string_array(char const ** arr)
130131
{
131-
return alloc_array(copy_string, arr);
132+
return caml_alloc_array(caml_copy_string, arr);
132133
}
133134

134-
CAMLexport int convert_flag_list(value list, int *flags)
135+
CAMLexport int caml_convert_flag_list(value list, int *flags)
135136
{
136137
int res;
137138
res = 0;
@@ -144,15 +145,15 @@ CAMLexport int convert_flag_list(value list, int *flags)
144145

145146
/* For compiling let rec over values */
146147

147-
CAMLprim value alloc_dummy(value size)
148+
CAMLprim value caml_alloc_dummy(value size)
148149
{
149150
mlsize_t wosize = Int_val(size);
150151

151152
if (wosize == 0) return Atom(0);
152-
return alloc (wosize, 0);
153+
return caml_alloc (wosize, 0);
153154
}
154155

155-
CAMLprim value update_dummy(value dummy, value newval)
156+
CAMLprim value caml_update_dummy(value dummy, value newval)
156157
{
157158
mlsize_t size, i;
158159
size = Wosize_val(newval);

Diff for: byterun/alloc.h

+15-13
Original file line numberDiff line numberDiff line change
@@ -17,29 +17,31 @@
1717
#define CAML_ALLOC_H
1818

1919

20+
#ifndef CAML_NAME_SPACE
2021
#include "compatibility.h"
22+
#endif
2123
#include "misc.h"
2224
#include "mlvalues.h"
2325

24-
CAMLextern value alloc (mlsize_t, tag_t);
25-
CAMLextern value alloc_small (mlsize_t, tag_t);
26-
CAMLextern value alloc_tuple (mlsize_t);
27-
CAMLextern value alloc_string (mlsize_t); /* size in bytes */
28-
CAMLextern value copy_string (char const *);
29-
CAMLextern value copy_string_array (char const **);
26+
CAMLextern value caml_alloc (mlsize_t, tag_t);
27+
CAMLextern value caml_alloc_small (mlsize_t, tag_t);
28+
CAMLextern value caml_alloc_tuple (mlsize_t);
29+
CAMLextern value caml_alloc_string (mlsize_t); /* size in bytes */
30+
CAMLextern value caml_copy_string (char const *);
31+
CAMLextern value caml_copy_string_array (char const **);
3032
CAMLextern value copy_double (double);
3133
CAMLextern value copy_int32 (int32); /* defined in [ints.c] */
3234
CAMLextern value copy_int64 (int64); /* defined in [ints.c] */
3335
CAMLextern value copy_nativeint (long); /* defined in [ints.c] */
34-
CAMLextern value alloc_array (value (*funct) (char const *),
35-
char const ** array);
36+
CAMLextern value caml_alloc_array (value (*funct) (char const *),
37+
char const ** array);
3638

3739
typedef void (*final_fun)(value);
38-
CAMLextern value alloc_final (mlsize_t, /*size in words*/
39-
final_fun, /*finalization function*/
40-
mlsize_t, /*resources consumed*/
41-
mlsize_t /*max resources*/);
40+
CAMLextern value caml_alloc_final (mlsize_t, /*size in words*/
41+
final_fun, /*finalization function*/
42+
mlsize_t, /*resources consumed*/
43+
mlsize_t /*max resources*/);
4244

43-
CAMLextern int convert_flag_list (value, int *);
45+
CAMLextern int caml_convert_flag_list (value, int *);
4446

4547
#endif /* CAML_ALLOC_H */

Diff for: byterun/array.c

+3-3
Original file line numberDiff line numberDiff line change
@@ -144,14 +144,14 @@ CAMLprim value make_vect(value len, value init)
144144
d = Double_val(init);
145145
wsize = size * Double_wosize;
146146
if (wsize > Max_wosize) invalid_argument("Array.make");
147-
res = alloc(wsize, Double_array_tag);
147+
res = caml_alloc(wsize, Double_array_tag);
148148
for (i = 0; i < size; i++) {
149149
Store_double_field(res, i, d);
150150
}
151151
} else {
152152
if (size > Max_wosize) invalid_argument("Array.make");
153153
if (size < Max_young_wosize) {
154-
res = alloc_small(size, 0);
154+
res = caml_alloc_small(size, 0);
155155
for (i = 0; i < size; i++) Field(res, i) = init;
156156
}
157157
else if (Is_block(init) && Is_young(init)) {
@@ -187,7 +187,7 @@ CAMLprim value make_array(value init)
187187
} else {
188188
Assert(size < Max_young_wosize);
189189
wsize = size * Double_wosize;
190-
res = alloc_small(wsize, Double_array_tag);
190+
res = caml_alloc_small(wsize, Double_array_tag);
191191
for (i = 0; i < size; i++) {
192192
Store_double_field(res, i, Double_val(Field(init, i)));
193193
}

Diff for: byterun/backtrace.c

+5-5
Original file line numberDiff line numberDiff line change
@@ -119,11 +119,11 @@ static value read_debug_info(void)
119119
close(fd);
120120
CAMLreturn(Val_false);
121121
}
122-
chan = open_descriptor_in(fd);
123-
num_events = getword(chan);
124-
events = alloc(num_events, 0);
122+
chan = caml_open_descriptor_in(fd);
123+
num_events = caml_getword(chan);
124+
events = caml_alloc(num_events, 0);
125125
for (i = 0; i < num_events; i++) {
126-
orig = getword(chan);
126+
orig = caml_getword(chan);
127127
evl = input_val(chan);
128128
/* Relocate events in event list */
129129
for (l = evl; l != Val_int(0); l = Field(l, 1)) {
@@ -133,7 +133,7 @@ static value read_debug_info(void)
133133
/* Record event list */
134134
Store_field(events, i, evl);
135135
}
136-
close_channel(chan);
136+
caml_close_channel(chan);
137137
CAMLreturn(events);
138138
}
139139

Diff for: byterun/callback.h

+2
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,9 @@
1818
#ifndef CAML_CALLBACK_H
1919
#define CAML_CALLBACK_H
2020

21+
#ifndef CAML_NAME_SPACE
2122
#include "compatibility.h"
23+
#endif
2224
#include "mlvalues.h"
2325

2426
CAMLextern value callback (value closure, value arg);

0 commit comments

Comments
 (0)