diff options
-rw-r--r-- | byterun/win32.c | 4 | ||||
-rw-r--r-- | otherlibs/graph/fill.c | 2 | ||||
-rw-r--r-- | otherlibs/graph/make_img.c | 4 | ||||
-rw-r--r-- | otherlibs/graph/open.c | 2 | ||||
-rw-r--r-- | otherlibs/labltk/support/cltkDMain.c | 4 | ||||
-rw-r--r-- | otherlibs/labltk/support/cltkEval.c | 8 | ||||
-rw-r--r-- | otherlibs/labltk/support/cltkMain.c | 4 | ||||
-rw-r--r-- | otherlibs/labltk/support/cltkMisc.c | 2 | ||||
-rw-r--r-- | otherlibs/labltk/support/cltkUtf.c | 4 | ||||
-rw-r--r-- | otherlibs/labltk/support/cltkWait.c | 4 | ||||
-rw-r--r-- | otherlibs/str/strstubs.c | 2 | ||||
-rw-r--r-- | otherlibs/systhreads/st_stubs.c | 4 | ||||
-rw-r--r-- | otherlibs/threads/scheduler.c | 2 | ||||
-rw-r--r-- | otherlibs/unix/cstringv.c | 2 | ||||
-rw-r--r-- | otherlibs/unix/getaddrinfo.c | 4 | ||||
-rw-r--r-- | otherlibs/unix/gethost.c | 2 | ||||
-rw-r--r-- | otherlibs/unix/open.c | 2 | ||||
-rw-r--r-- | otherlibs/unix/setgroups.c | 2 | ||||
-rw-r--r-- | testsuite/tests/gc-roots/globrootsprim.c | 4 |
19 files changed, 31 insertions, 31 deletions
diff --git a/byterun/win32.c b/byterun/win32.c index 8d437ee4a..2b4aacced 100644 --- a/byterun/win32.c +++ b/byterun/win32.c @@ -91,7 +91,7 @@ CAMLexport char * caml_search_exe_in_path(char * name) pathlen = strlen(name) + 1; if (pathlen < 256) pathlen = 256; while (1) { - fullname = stat_alloc(pathlen); + fullname = caml_stat_alloc(pathlen); retcode = SearchPath(NULL, /* use system search path */ name, ".exe", /* add .exe extension if needed */ @@ -105,7 +105,7 @@ CAMLexport char * caml_search_exe_in_path(char * name) break; } if (retcode < pathlen) break; - stat_free(fullname); + caml_stat_free(fullname); pathlen = retcode + 1; } return fullname; diff --git a/otherlibs/graph/fill.c b/otherlibs/graph/fill.c index ba14e2cdd..4eb9f3474 100644 --- a/otherlibs/graph/fill.c +++ b/otherlibs/graph/fill.c @@ -40,7 +40,7 @@ value caml_gr_fill_poly(value array) caml_gr_check_open(); npoints = Wosize_val(array); - points = (XPoint *) stat_alloc(npoints * sizeof(XPoint)); + points = (XPoint *) caml_stat_alloc(npoints * sizeof(XPoint)); for (i = 0; i < npoints; i++) { points[i].x = Int_val(Field(Field(array, i), 0)); points[i].y = Bcvt(Int_val(Field(Field(array, i), 1))); diff --git a/otherlibs/graph/make_img.c b/otherlibs/graph/make_img.c index 56f37bd30..e65c7a00d 100644 --- a/otherlibs/graph/make_img.c +++ b/otherlibs/graph/make_img.c @@ -41,7 +41,7 @@ value caml_gr_make_image(value m) ZPixmap, 0, NULL, width, height, BitmapPad(caml_gr_display), 0); - bdata = (char *) stat_alloc(height * idata->bytes_per_line); + bdata = (char *) caml_stat_alloc(height * idata->bytes_per_line); idata->data = bdata; has_transp = False; @@ -61,7 +61,7 @@ value caml_gr_make_image(value m) XCreateImage(caml_gr_display, DefaultVisual(caml_gr_display, caml_gr_screen), 1, ZPixmap, 0, NULL, width, height, BitmapPad(caml_gr_display), 0); - bmask = (char *) stat_alloc(height * imask->bytes_per_line); + bmask = (char *) caml_stat_alloc(height * imask->bytes_per_line); imask->data = bmask; for (i = 0; i < height; i++) { diff --git a/otherlibs/graph/open.c b/otherlibs/graph/open.c index 00ae2a314..9cb4ba5c2 100644 --- a/otherlibs/graph/open.c +++ b/otherlibs/graph/open.c @@ -240,7 +240,7 @@ value caml_gr_window_id(void) value caml_gr_set_window_title(value n) { if (window_name != NULL) stat_free(window_name); - window_name = stat_alloc(strlen(String_val(n))+1); + window_name = caml_stat_alloc(strlen(String_val(n))+1); strcpy(window_name, String_val(n)); if (caml_gr_initialized) { XStoreName(caml_gr_display, caml_gr_window.win, window_name); diff --git a/otherlibs/labltk/support/cltkDMain.c b/otherlibs/labltk/support/cltkDMain.c index 04af209de..58374d8a3 100644 --- a/otherlibs/labltk/support/cltkDMain.c +++ b/otherlibs/labltk/support/cltkDMain.c @@ -162,7 +162,7 @@ int CamlRunCmd(dummy, interp, argc, argv) + trail.symbol_size + trail.debug_size), 2); code_size = trail.code_size; - start_code = (code_t) stat_alloc(code_size); + start_code = (code_t) caml_stat_alloc(code_size); if (read(fd, (char *) start_code, code_size) != code_size) fatal_error("Fatal error: truncated bytecode file.\n"); @@ -215,7 +215,7 @@ int Caml_Init(interp) { char *home = getenv("HOME"); if (home != NULL) { - char *f = stat_alloc(strlen(home)+strlen(RCNAME)+2); + char *f = caml_stat_alloc(strlen(home)+strlen(RCNAME)+2); f[0]='\0'; strcat(f, home); strcat(f, "/"); diff --git a/otherlibs/labltk/support/cltkEval.c b/otherlibs/labltk/support/cltkEval.c index 69ba6d8a1..c7a43481c 100644 --- a/otherlibs/labltk/support/cltkEval.c +++ b/otherlibs/labltk/support/cltkEval.c @@ -139,14 +139,14 @@ int fill_args (char **argv, int where, value v) char *merged; int i; int size = argv_size(Field(v,0)); - tmpargv = (char **)stat_alloc((size + 1) * sizeof(char *)); + tmpargv = (char **)caml_stat_alloc((size + 1) * sizeof(char *)); fill_args(tmpargv,0,Field(v,0)); tmpargv[size] = NULL; merged = Tcl_Merge(size,(const char *const*)tmpargv); for(i = 0; i<size; i++){ stat_free(tmpargv[i]); } stat_free((char *)tmpargv); /* must be freed by stat_free */ - argv[where] = (char*)stat_alloc(strlen(merged)+1); + argv[where] = (char*)caml_stat_alloc(strlen(merged)+1); strcpy(argv[where], merged); Tcl_Free(merged); return (where + 1); @@ -173,8 +173,8 @@ CAMLprim value camltk_tcl_direct_eval(value v) /* +2: one slot for NULL one slot for "unknown" if command not found */ - argv = (char **)stat_alloc((size + 2) * sizeof(char *)); - allocated = (char **)stat_alloc(size * sizeof(char *)); + argv = (char **)caml_stat_alloc((size + 2) * sizeof(char *)); + allocated = (char **)caml_stat_alloc(size * sizeof(char *)); /* Copy -- argv[i] must be freed by stat_free */ { diff --git a/otherlibs/labltk/support/cltkMain.c b/otherlibs/labltk/support/cltkMain.c index 8751334c5..871a47ac1 100644 --- a/otherlibs/labltk/support/cltkMain.c +++ b/otherlibs/labltk/support/cltkMain.c @@ -113,7 +113,7 @@ CAMLprim value camltk_opentk(value argv) char **tkargv; char argcstr[256]; /* string of argc */ - tkargv = (char**)stat_alloc(sizeof( char* ) * argc ); + tkargv = (char**)caml_stat_alloc(sizeof( char* ) * argc ); tmp = Field(argv, 1); /* starts from argv[1] */ i = 0; @@ -157,7 +157,7 @@ CAMLprim value camltk_opentk(value argv) { char *home = getenv("HOME"); if (home != NULL) { - char *f = stat_alloc(strlen(home)+strlen(RCNAME)+2); + char *f = caml_stat_alloc(strlen(home)+strlen(RCNAME)+2); f[0]='\0'; strcat(f, home); strcat(f, "/"); diff --git a/otherlibs/labltk/support/cltkMisc.c b/otherlibs/labltk/support/cltkMisc.c index a89ea341f..52c5d4846 100644 --- a/otherlibs/labltk/support/cltkMisc.c +++ b/otherlibs/labltk/support/cltkMisc.c @@ -55,7 +55,7 @@ CAMLprim value camltk_splitlist (value v) char *string_to_c(value s) { int l = string_length(s); - char *res = stat_alloc(l + 1); + char *res = caml_stat_alloc(l + 1); memmove (res, String_val (s), l); res[l] = '\0'; return res; diff --git a/otherlibs/labltk/support/cltkUtf.c b/otherlibs/labltk/support/cltkUtf.c index 448e06a1c..61dbfb2f5 100644 --- a/otherlibs/labltk/support/cltkUtf.c +++ b/otherlibs/labltk/support/cltkUtf.c @@ -43,7 +43,7 @@ char *external_to_utf( char *str ){ Tcl_ExternalToUtfDString(NULL, str, strlen(str), &dstr); length = Tcl_DStringLength(&dstr); - res = stat_alloc(length + 1); + res = caml_stat_alloc(length + 1); memmove( res, Tcl_DStringValue(&dstr), length+1); Tcl_DStringFree(&dstr); @@ -57,7 +57,7 @@ char *utf_to_external( char *str ){ Tcl_UtfToExternalDString(NULL, str, strlen(str), &dstr); length = Tcl_DStringLength(&dstr); - res = stat_alloc(length + 1); + res = caml_stat_alloc(length + 1); memmove( res, Tcl_DStringValue(&dstr), length+1); Tcl_DStringFree(&dstr); diff --git a/otherlibs/labltk/support/cltkWait.c b/otherlibs/labltk/support/cltkWait.c index a46860b85..e13091f2d 100644 --- a/otherlibs/labltk/support/cltkWait.c +++ b/otherlibs/labltk/support/cltkWait.c @@ -62,7 +62,7 @@ static void WaitVisibilityProc(clientData, eventPtr) CAMLprim value camltk_wait_vis(value win, value cbid) { struct WinCBData *vis = - (struct WinCBData *)stat_alloc(sizeof(struct WinCBData)); + (struct WinCBData *)caml_stat_alloc(sizeof(struct WinCBData)); vis->win = Tk_NameToWindow(cltclinterp, String_val(win), cltk_mainWindow); if (vis -> win == NULL) { stat_free((char *)vis); @@ -89,7 +89,7 @@ static void WaitWindowProc(ClientData clientData, XEvent *eventPtr) CAMLprim value camltk_wait_des(value win, value cbid) { struct WinCBData *vis = - (struct WinCBData *)stat_alloc(sizeof(struct WinCBData)); + (struct WinCBData *)caml_stat_alloc(sizeof(struct WinCBData)); vis->win = Tk_NameToWindow(cltclinterp, String_val(win), cltk_mainWindow); if (vis -> win == NULL) { stat_free((char *)vis); diff --git a/otherlibs/str/strstubs.c b/otherlibs/str/strstubs.c index b25ecef34..9de349a9d 100644 --- a/otherlibs/str/strstubs.c +++ b/otherlibs/str/strstubs.c @@ -298,7 +298,7 @@ static int re_match(value re, /* Push an item on the backtrack stack and continue with next instr */ if (sp == stack->point + BACKTRACK_STACK_BLOCK_SIZE) { struct backtrack_stack * newstack = - stat_alloc(sizeof(struct backtrack_stack)); + caml_stat_alloc(sizeof(struct backtrack_stack)); newstack->previous = stack; stack = newstack; sp = stack->point; diff --git a/otherlibs/systhreads/st_stubs.c b/otherlibs/systhreads/st_stubs.c index 7e420191e..02d4c54fc 100644 --- a/otherlibs/systhreads/st_stubs.c +++ b/otherlibs/systhreads/st_stubs.c @@ -304,7 +304,7 @@ static caml_thread_t caml_thread_new_info(void) th->exit_buf = NULL; #else /* Allocate the stacks */ - th->stack_low = (value *) stat_alloc(Thread_stack_size); + th->stack_low = (value *) caml_stat_alloc(Thread_stack_size); th->stack_high = th->stack_low + Thread_stack_size / sizeof(value); th->stack_threshold = th->stack_low + Stack_threshold / sizeof(value); th->sp = th->stack_high; @@ -406,7 +406,7 @@ CAMLprim value caml_thread_initialize(value unit) /* ML */ st_tls_newkey(&last_channel_locked_key); /* Set up a thread info block for the current thread */ curr_thread = - (caml_thread_t) stat_alloc(sizeof(struct caml_thread_struct)); + (caml_thread_t) caml_stat_alloc(sizeof(struct caml_thread_struct)); curr_thread->descr = caml_thread_new_descriptor(Val_unit); curr_thread->next = curr_thread; curr_thread->prev = curr_thread; diff --git a/otherlibs/threads/scheduler.c b/otherlibs/threads/scheduler.c index 5b14eb2e1..45ef854db 100644 --- a/otherlibs/threads/scheduler.c +++ b/otherlibs/threads/scheduler.c @@ -225,7 +225,7 @@ value thread_new(value clos) /* ML */ End_roots(); th->ident = next_ident; next_ident = Val_int(Int_val(next_ident) + 1); - th->stack_low = (value *) stat_alloc(Thread_stack_size); + th->stack_low = (value *) caml_stat_alloc(Thread_stack_size); th->stack_high = th->stack_low + Thread_stack_size / sizeof(value); th->stack_threshold = th->stack_low + Stack_threshold / sizeof(value); th->sp = th->stack_high; diff --git a/otherlibs/unix/cstringv.c b/otherlibs/unix/cstringv.c index 04da30c24..d85411007 100644 --- a/otherlibs/unix/cstringv.c +++ b/otherlibs/unix/cstringv.c @@ -21,7 +21,7 @@ char ** cstringvect(value arg) mlsize_t size, i; size = Wosize_val(arg); - res = (char **) stat_alloc((size + 1) * sizeof(char *)); + res = (char **) caml_stat_alloc((size + 1) * sizeof(char *)); for (i = 0; i < size; i++) res[i] = String_val(Field(arg, i)); res[size] = NULL; return res; diff --git a/otherlibs/unix/getaddrinfo.c b/otherlibs/unix/getaddrinfo.c index f79bdffff..cf3bb4a52 100644 --- a/otherlibs/unix/getaddrinfo.c +++ b/otherlibs/unix/getaddrinfo.c @@ -67,7 +67,7 @@ CAMLprim value unix_getaddrinfo(value vnode, value vserv, value vopts) if (len == 0) { node = NULL; } else { - node = stat_alloc(len + 1); + node = caml_stat_alloc(len + 1); strcpy(node, String_val(vnode)); } /* Extract "service" parameter */ @@ -75,7 +75,7 @@ CAMLprim value unix_getaddrinfo(value vnode, value vserv, value vopts) if (len == 0) { serv = NULL; } else { - serv = stat_alloc(len + 1); + serv = caml_stat_alloc(len + 1); strcpy(serv, String_val(vserv)); } /* Parse options, set hints */ diff --git a/otherlibs/unix/gethost.c b/otherlibs/unix/gethost.c index 35a53f082..e155152f8 100644 --- a/otherlibs/unix/gethost.c +++ b/otherlibs/unix/gethost.c @@ -127,7 +127,7 @@ CAMLprim value unix_gethostbyname(value name) char * hostname; #if HAS_GETHOSTBYNAME_R || GETHOSTBYNAME_IS_REENTRANT - hostname = stat_alloc(string_length(name) + 1); + hostname = caml_stat_alloc(string_length(name) + 1); strcpy(hostname, String_val(name)); #else hostname = String_val(name); diff --git a/otherlibs/unix/open.c b/otherlibs/unix/open.c index e96cdc88c..097a0455b 100644 --- a/otherlibs/unix/open.c +++ b/otherlibs/unix/open.c @@ -44,7 +44,7 @@ CAMLprim value unix_open(value path, value flags, value perm) char * p; cv_flags = convert_flag_list(flags, open_flag_table); - p = stat_alloc(string_length(path) + 1); + p = caml_stat_alloc(string_length(path) + 1); strcpy(p, String_val(path)); /* open on a named FIFO can block (PR#1533) */ enter_blocking_section(); diff --git a/otherlibs/unix/setgroups.c b/otherlibs/unix/setgroups.c index 026c67632..2279a6b36 100644 --- a/otherlibs/unix/setgroups.c +++ b/otherlibs/unix/setgroups.c @@ -33,7 +33,7 @@ CAMLprim value unix_setgroups(value groups) int n; size = Wosize_val(groups); - gidset = (gid_t *) stat_alloc(size * sizeof(gid_t)); + gidset = (gid_t *) caml_stat_alloc(size * sizeof(gid_t)); for (i = 0; i < size; i++) gidset[i] = Int_val(Field(groups, i)); n = setgroups(size, gidset); diff --git a/testsuite/tests/gc-roots/globrootsprim.c b/testsuite/tests/gc-roots/globrootsprim.c index ff1685fc0..9a1cc843a 100644 --- a/testsuite/tests/gc-roots/globrootsprim.c +++ b/testsuite/tests/gc-roots/globrootsprim.c @@ -28,7 +28,7 @@ value gb_get(value vblock) value gb_classic_register(value v) { - struct block * b = stat_alloc(sizeof(struct block)); + struct block * b = caml_stat_alloc(sizeof(struct block)); b->v = v; caml_register_global_root(&(b->v)); return (value) b; @@ -48,7 +48,7 @@ value gb_classic_remove(value vblock) value gb_generational_register(value v) { - struct block * b = stat_alloc(sizeof(struct block)); + struct block * b = caml_stat_alloc(sizeof(struct block)); b->v = v; caml_register_generational_global_root(&(b->v)); return (value) b; |