Rename: use _os suffix

master
Nicolas Ojeda Bar 2017-09-21 12:29:03 +02:00
parent 99878e4839
commit 799f36d3e6
33 changed files with 255 additions and 255 deletions

View File

@ -69,11 +69,11 @@ CAMLprim value caml_natdynlink_open(value filename, value global)
CAMLlocal3 (res, handle, header); CAMLlocal3 (res, handle, header);
void *sym; void *sym;
void *dlhandle; void *dlhandle;
charnat *p; char_os *p;
/* TODO: dlclose in case of error... */ /* TODO: dlclose in case of error... */
p = caml_stat_strdup_to_utf16(String_val(filename)); p = caml_stat_strdup_to_os(String_val(filename));
caml_enter_blocking_section(); caml_enter_blocking_section();
dlhandle = caml_dlopen(p, 1, Int_val(global)); dlhandle = caml_dlopen(p, 1, Int_val(global));
caml_leave_blocking_section(); caml_leave_blocking_section();
@ -151,11 +151,11 @@ CAMLprim value caml_natdynlink_run_toplevel(value filename, value symbol)
CAMLparam2 (filename, symbol); CAMLparam2 (filename, symbol);
CAMLlocal3 (res, v, handle_v); CAMLlocal3 (res, v, handle_v);
void *handle; void *handle;
charnat *p; char_os *p;
/* TODO: dlclose in case of error... */ /* TODO: dlclose in case of error... */
p = caml_stat_strdup_to_utf16(String_val(filename)); p = caml_stat_strdup_to_os(String_val(filename));
caml_enter_blocking_section(); caml_enter_blocking_section();
handle = caml_dlopen(p, 1, 1); handle = caml_dlopen(p, 1, 1);
caml_leave_blocking_section(); caml_leave_blocking_section();

View File

@ -103,9 +103,9 @@ extern void caml_install_invalid_parameter_handler();
#endif #endif
value caml_startup_common(charnat **argv, int pooling) value caml_startup_common(char_os **argv, int pooling)
{ {
charnat * exe_name, * proc_self_exe; char_os * exe_name, * proc_self_exe;
char tos; char tos;
/* Determine options */ /* Determine options */
@ -156,29 +156,29 @@ value caml_startup_common(charnat **argv, int pooling)
return caml_start_program(); return caml_start_program();
} }
value caml_startup_exn(charnat **argv) value caml_startup_exn(char_os **argv)
{ {
return caml_startup_common(argv, /* pooling */ 0); return caml_startup_common(argv, /* pooling */ 0);
} }
void caml_startup(charnat **argv) void caml_startup(char_os **argv)
{ {
value res = caml_startup_exn(argv); value res = caml_startup_exn(argv);
if (Is_exception_result(res)) if (Is_exception_result(res))
caml_fatal_uncaught_exception(Extract_exception(res)); caml_fatal_uncaught_exception(Extract_exception(res));
} }
void caml_main(charnat **argv) void caml_main(char_os **argv)
{ {
caml_startup(argv); caml_startup(argv);
} }
value caml_startup_pooled_exn(charnat **argv) value caml_startup_pooled_exn(char_os **argv)
{ {
return caml_startup_common(argv, /* pooling */ 1); return caml_startup_common(argv, /* pooling */ 1);
} }
void caml_startup_pooled(charnat **argv) void caml_startup_pooled(char_os **argv)
{ {
value res = caml_startup_pooled_exn(argv); value res = caml_startup_pooled_exn(argv);
if (Is_exception_result(res)) if (Is_exception_result(res))

View File

@ -487,7 +487,7 @@ let link_bytecode_as_c ppf tolink outfile =
Symtable.output_primitive_table outchan; Symtable.output_primitive_table outchan;
(* The entry point *) (* The entry point *)
output_string outchan "\ output_string outchan "\
\nvoid caml_startup(charnat ** argv)\ \nvoid caml_startup(char_os ** argv)\
\n{\ \n{\
\n caml_startup_code(caml_code, sizeof(caml_code),\ \n caml_startup_code(caml_code, sizeof(caml_code),\
\n caml_data, sizeof(caml_data),\ \n caml_data, sizeof(caml_data),\
@ -496,7 +496,7 @@ let link_bytecode_as_c ppf tolink outfile =
\n argv);\ \n argv);\
\n}\ \n}\
\n\ \n\
\nvalue caml_startup_exn(charnat ** argv)\ \nvalue caml_startup_exn(char_os ** argv)\
\n{\ \n{\
\n return caml_startup_code_exn(caml_code, sizeof(caml_code),\ \n return caml_startup_code_exn(caml_code, sizeof(caml_code),\
\n caml_data, sizeof(caml_data),\ \n caml_data, sizeof(caml_data),\
@ -505,7 +505,7 @@ let link_bytecode_as_c ppf tolink outfile =
\n argv);\ \n argv);\
\n}\ \n}\
\n\ \n\
\nvoid caml_startup_pooled(charnat ** argv)\ \nvoid caml_startup_pooled(char_os ** argv)\
\n{\ \n{\
\n caml_startup_code(caml_code, sizeof(caml_code),\ \n caml_startup_code(caml_code, sizeof(caml_code),\
\n caml_data, sizeof(caml_data),\ \n caml_data, sizeof(caml_data),\
@ -514,7 +514,7 @@ let link_bytecode_as_c ppf tolink outfile =
\n argv);\ \n argv);\
\n}\ \n}\
\n\ \n\
\nvalue caml_startup_pooled_exn(charnat ** argv)\ \nvalue caml_startup_pooled_exn(char_os ** argv)\
\n{\ \n{\
\n return caml_startup_code_exn(caml_code, sizeof(caml_code),\ \n return caml_startup_code_exn(caml_code, sizeof(caml_code),\
\n caml_data, sizeof(caml_data),\ \n caml_data, sizeof(caml_data),\

View File

@ -46,7 +46,7 @@
/* The table of debug information fragments */ /* The table of debug information fragments */
struct ext_table caml_debug_info; struct ext_table caml_debug_info;
CAMLexport charnat * caml_cds_file = NULL; CAMLexport char_os * caml_cds_file = NULL;
/* Location of fields in the Instruct.debug_event record */ /* Location of fields in the Instruct.debug_event record */
enum { enum {
@ -329,7 +329,7 @@ static void read_main_debug_info(struct debug_info *di)
{ {
CAMLparam0(); CAMLparam0();
CAMLlocal3(events, evl, l); CAMLlocal3(events, evl, l);
charnat *exec_name; char_os *exec_name;
int fd, num_events, orig, i; int fd, num_events, orig, i;
struct channel *chan; struct channel *chan;
struct exec_trailer trail; struct exec_trailer trail;

View File

@ -109,7 +109,7 @@ CAMLprim value caml_record_backtrace(value vflag);
#ifndef NATIVE_CODE #ifndef NATIVE_CODE
/* Path to the file containing debug information, if any, or NULL. */ /* Path to the file containing debug information, if any, or NULL. */
CAMLextern charnat * caml_cds_file; CAMLextern char_os * caml_cds_file;
/* Primitive called _only_ by runtime to record unwinded frames to /* Primitive called _only_ by runtime to record unwinded frames to
* backtrace. A similar primitive exists for native code, but with a * backtrace. A similar primitive exists for native code, but with a

View File

@ -47,11 +47,11 @@ CAMLextern value * caml_named_value (char const * name);
typedef void (*caml_named_action) (value*, char *); typedef void (*caml_named_action) (value*, char *);
CAMLextern void caml_iterate_named_values(caml_named_action f); CAMLextern void caml_iterate_named_values(caml_named_action f);
CAMLextern void caml_main (charnat ** argv); CAMLextern void caml_main (char_os ** argv);
CAMLextern void caml_startup (charnat ** argv); CAMLextern void caml_startup (char_os ** argv);
CAMLextern value caml_startup_exn (charnat ** argv); CAMLextern value caml_startup_exn (char_os ** argv);
CAMLextern void caml_startup_pooled (charnat ** argv); CAMLextern void caml_startup_pooled (char_os ** argv);
CAMLextern value caml_startup_pooled_exn (charnat ** argv); CAMLextern value caml_startup_pooled_exn (char_os ** argv);
CAMLextern void caml_shutdown (void); CAMLextern void caml_shutdown (void);
CAMLextern int caml_callback_depth; CAMLextern int caml_callback_depth;

View File

@ -27,8 +27,8 @@
(all three 0-separated in char arrays). (all three 0-separated in char arrays).
Abort the runtime system on error. Abort the runtime system on error.
Calling this frees caml_shared_libs_path (not touching its contents). */ Calling this frees caml_shared_libs_path (not touching its contents). */
extern void caml_build_primitive_table(charnat * lib_path, extern void caml_build_primitive_table(char_os * lib_path,
charnat * libs, char_os * libs,
char * req_prims); char * req_prims);
/* The search path for shared libraries */ /* The search path for shared libraries */

View File

@ -169,67 +169,67 @@ extern int caml_umul_overflow(uintnat a, uintnat b, uintnat * res);
#ifdef _WIN32 #ifdef _WIN32
typedef wchar_t charnat; typedef wchar_t char_os;
#define _T(x) L ## x #define _T(x) L ## x
#define _topen _wopen #define open_os _wopen
#define _tstat _wstati64 #define stat_os _wstati64
#define _tunlink _wunlink #define unlink_os _wunlink
#define _trename caml_win32_rename #define rename_os caml_win32_rename
#define _tchdir _wchdir #define chdir_os _wchdir
#define _tgetcwd _wgetcwd #define getcwd_os _wgetcwd
#define _tgetenv _wgetenv #define getenv_os _wgetenv
#define _tsystem _wsystem #define system_os _wsystem
#define _trmdir _wrmdir #define rmdir_os _wrmdir
#define _tutime _wutime #define utime_os _wutime
#define _tputenv _wputenv #define putenv_os _wputenv
#define _tchmod _wchmod #define chmod_os _wchmod
#define _texecv _wexecv #define execv_os _wexecv
#define _texecve _wexecve #define execve_os _wexecve
#define _texecvp _wexecvp #define execvp_os _wexecvp
#define _tcscmp wcscmp #define strcmp_os wcscmp
#define _tcslen wcslen #define strlen_os wcslen
#define _stscanf swscanf #define sscanf_os swscanf
#define caml_stat_tcsdup caml_stat_wcsdup #define caml_stat_strdup_os caml_stat_wcsdup
#define caml_stat_tcsconcat caml_stat_wcsconcat #define caml_stat_strconcat_os caml_stat_wcsconcat
#define caml_stat_strdup_to_utf16 caml_stat_strdup_to_utf16 #define caml_stat_strdup_to_os caml_stat_strdup_to_utf16
#define caml_stat_strdup_of_utf16 caml_stat_strdup_of_utf16 #define caml_stat_strdup_of_os caml_stat_strdup_of_utf16
#define caml_copy_string_of_utf16 caml_copy_string_of_utf16 #define caml_copy_string_of_os caml_copy_string_of_utf16
#else /* _WIN32 */ #else /* _WIN32 */
typedef char charnat; typedef char char_os;
#define _T(x) x #define _T(x) x
#define _topen open #define open_os open
#define _tstat stat #define stat_os stat
#define _tunlink unlink #define unlink_os unlink
#define _trename rename #define rename_os rename
#define _tchdir chdir #define chdir_os chdir
#define _tgetcwd getcwd #define getcwd_os getcwd
#define _tgetenv getenv #define getenv_os getenv
#define _tsystem system #define system_os system
#define _trmdir rmdir #define rmdir_os rmdir
#define _tutime utime #define utime_os utime
#define _tputenv putenv #define putenv_os putenv
#define _tchmod chmod #define chmod_os chmod
#define _texecv execv #define execv_os execv
#define _texecve execve #define execve_os execve
#define _texecvp execvp #define execvp_os execvp
#define _tcscmp strcmp #define strcmp_os strcmp
#define _tcslen strlen #define strlen_os strlen
#define _stscanf sscanf #define sscanf_os sscanf
#define caml_stat_tcsdup caml_stat_strdup #define caml_stat_strdup_os caml_stat_strdup
#define caml_stat_tcsconcat caml_stat_strconcat #define caml_stat_strconcat_os caml_stat_strconcat
#define caml_stat_strdup_to_utf16 caml_stat_strdup #define caml_stat_strdup_to_os caml_stat_strdup
#define caml_stat_strdup_of_utf16 caml_stat_strdup #define caml_stat_strdup_of_os caml_stat_strdup
#define caml_copy_string_of_utf16 caml_copy_string #define caml_copy_string_of_os caml_copy_string
#endif /* _WIN32 */ #endif /* _WIN32 */
@ -242,14 +242,14 @@ typedef char charnat;
#ifndef CAML_WITH_CPLUGINS #ifndef CAML_WITH_CPLUGINS
#define CAML_SYS_EXIT(retcode) exit(retcode) #define CAML_SYS_EXIT(retcode) exit(retcode)
#define CAML_SYS_OPEN(filename,flags,perm) _topen(filename,flags,perm) #define CAML_SYS_OPEN(filename,flags,perm) open_os(filename,flags,perm)
#define CAML_SYS_CLOSE(fd) close(fd) #define CAML_SYS_CLOSE(fd) close(fd)
#define CAML_SYS_STAT(filename,st) _tstat(filename,st) #define CAML_SYS_STAT(filename,st) stat_os(filename,st)
#define CAML_SYS_UNLINK(filename) _tunlink(filename) #define CAML_SYS_UNLINK(filename) unlink_os(filename)
#define CAML_SYS_RENAME(old_name,new_name) _trename(old_name, new_name) #define CAML_SYS_RENAME(old_name,new_name) rename_os(old_name, new_name)
#define CAML_SYS_CHDIR(dirname) _tchdir(dirname) #define CAML_SYS_CHDIR(dirname) chdir_os(dirname)
#define CAML_SYS_GETENV(varname) _tgetenv(varname) #define CAML_SYS_GETENV(varname) getenv_os(varname)
#define CAML_SYS_SYSTEM(command) _tsystem(command) #define CAML_SYS_SYSTEM(command) system_os(command)
#define CAML_SYS_READ_DIRECTORY(dirname,tbl) caml_read_directory(dirname,tbl) #define CAML_SYS_READ_DIRECTORY(dirname,tbl) caml_read_directory(dirname,tbl)
#else #else
@ -276,7 +276,7 @@ extern intnat (*caml_cplugins_prim)(int,intnat,intnat,intnat);
caml_cplugins_prim(code,(intnat) (arg1),0,0) caml_cplugins_prim(code,(intnat) (arg1),0,0)
#define CAML_SYS_STRING_PRIM_1(code,prim,arg1) \ #define CAML_SYS_STRING_PRIM_1(code,prim,arg1) \
(caml_cplugins_prim == NULL) ? prim(arg1) : \ (caml_cplugins_prim == NULL) ? prim(arg1) : \
(charnat*)caml_cplugins_prim(code,(intnat) (arg1),0,0) (char_os*)caml_cplugins_prim(code,(intnat) (arg1),0,0)
#define CAML_SYS_VOID_PRIM_1(code,prim,arg1) \ #define CAML_SYS_VOID_PRIM_1(code,prim,arg1) \
(caml_cplugins_prim == NULL) ? prim(arg1) : \ (caml_cplugins_prim == NULL) ? prim(arg1) : \
(void)caml_cplugins_prim(code,(intnat) (arg1),0,0) (void)caml_cplugins_prim(code,(intnat) (arg1),0,0)
@ -290,21 +290,21 @@ extern intnat (*caml_cplugins_prim)(int,intnat,intnat,intnat);
#define CAML_SYS_EXIT(retcode) \ #define CAML_SYS_EXIT(retcode) \
CAML_SYS_VOID_PRIM_1(CAML_CPLUGINS_EXIT,exit,retcode) CAML_SYS_VOID_PRIM_1(CAML_CPLUGINS_EXIT,exit,retcode)
#define CAML_SYS_OPEN(filename,flags,perm) \ #define CAML_SYS_OPEN(filename,flags,perm) \
CAML_SYS_PRIM_3(CAML_CPLUGINS_OPEN,_topen,filename,flags,perm) CAML_SYS_PRIM_3(CAML_CPLUGINS_OPEN,open_os,filename,flags,perm)
#define CAML_SYS_CLOSE(fd) \ #define CAML_SYS_CLOSE(fd) \
CAML_SYS_PRIM_1(CAML_CPLUGINS_CLOSE,close,fd) CAML_SYS_PRIM_1(CAML_CPLUGINS_CLOSE,close,fd)
#define CAML_SYS_STAT(filename,st) \ #define CAML_SYS_STAT(filename,st) \
CAML_SYS_PRIM_2(CAML_CPLUGINS_STAT,_tstat,filename,st) CAML_SYS_PRIM_2(CAML_CPLUGINS_STAT,stat_os,filename,st)
#define CAML_SYS_UNLINK(filename) \ #define CAML_SYS_UNLINK(filename) \
CAML_SYS_PRIM_1(CAML_CPLUGINS_UNLINK,_tunlink,filename) CAML_SYS_PRIM_1(CAML_CPLUGINS_UNLINK,unlink_os,filename)
#define CAML_SYS_RENAME(old_name,new_name) \ #define CAML_SYS_RENAME(old_name,new_name) \
CAML_SYS_PRIM_2(CAML_CPLUGINS_RENAME,_trename,old_name,new_name) CAML_SYS_PRIM_2(CAML_CPLUGINS_RENAME,rename_os,old_name,new_name)
#define CAML_SYS_CHDIR(dirname) \ #define CAML_SYS_CHDIR(dirname) \
CAML_SYS_PRIM_1(CAML_CPLUGINS_CHDIR,_tchdir,dirname) CAML_SYS_PRIM_1(CAML_CPLUGINS_CHDIR,chdir_os,dirname)
#define CAML_SYS_GETENV(varname) \ #define CAML_SYS_GETENV(varname) \
CAML_SYS_STRING_PRIM_1(CAML_CPLUGINS_GETENV,_tgetenv,varname) CAML_SYS_STRING_PRIM_1(CAML_CPLUGINS_GETENV,getenv_os,varname)
#define CAML_SYS_SYSTEM(command) \ #define CAML_SYS_SYSTEM(command) \
CAML_SYS_PRIM_1(CAML_CPLUGINS_SYSTEM,_tsystem,command) CAML_SYS_PRIM_1(CAML_CPLUGINS_SYSTEM,system_os,command)
#define CAML_SYS_READ_DIRECTORY(dirname,tbl) \ #define CAML_SYS_READ_DIRECTORY(dirname,tbl) \
CAML_SYS_PRIM_2(CAML_CPLUGINS_READ_DIRECTORY,caml_read_directory, \ CAML_SYS_PRIM_2(CAML_CPLUGINS_READ_DIRECTORY,caml_read_directory, \
dirname,tbl) dirname,tbl)
@ -314,14 +314,14 @@ extern intnat (*caml_cplugins_prim)(int,intnat,intnat,intnat);
struct cplugin_context { struct cplugin_context {
int api_version; int api_version;
int prims_bitmap; int prims_bitmap;
charnat *exe_name; char_os *exe_name;
charnat** argv; char_os** argv;
charnat *plugin; /* absolute filename of plugin, do a copy if you need it ! */ char_os *plugin; /* absolute filename of plugin, do a copy if you need it ! */
char *ocaml_version; char *ocaml_version;
/* end of CAML_CPLUGIN_CONTEXT_API version 0 */ /* end of CAML_CPLUGIN_CONTEXT_API version 0 */
}; };
extern void caml_cplugins_init(charnat * exe_name, charnat **argv); extern void caml_cplugins_init(char_os * exe_name, char_os **argv);
/* A plugin MUST define a symbol "caml_cplugin_init" with the prototype: /* A plugin MUST define a symbol "caml_cplugin_init" with the prototype:
@ -347,7 +347,7 @@ extern void caml_ext_table_remove(struct ext_table * tbl, void * data);
extern void caml_ext_table_free(struct ext_table * tbl, int free_entries); extern void caml_ext_table_free(struct ext_table * tbl, int free_entries);
extern void caml_ext_table_clear(struct ext_table * tbl, int free_entries); extern void caml_ext_table_clear(struct ext_table * tbl, int free_entries);
CAMLextern int caml_read_directory(charnat * dirname, struct ext_table * contents); CAMLextern int caml_read_directory(char_os * dirname, struct ext_table * contents);
#ifdef CAML_INTERNALS #ifdef CAML_INTERNALS

View File

@ -41,17 +41,17 @@ extern int caml_write_fd(int fd, int flags, void * buf, int n);
/* Decompose the given path into a list of directories, and add them /* Decompose the given path into a list of directories, and add them
to the given table. */ to the given table. */
extern charnat * caml_decompose_path(struct ext_table * tbl, charnat * path); extern char_os * caml_decompose_path(struct ext_table * tbl, char_os * path);
/* Search the given file in the given list of directories. /* Search the given file in the given list of directories.
If not found, return a copy of [name]. */ If not found, return a copy of [name]. */
extern charnat * caml_search_in_path(struct ext_table * path, const charnat * name); extern char_os * caml_search_in_path(struct ext_table * path, const char_os * name);
/* Same, but search an executable name in the system path for executables. */ /* Same, but search an executable name in the system path for executables. */
CAMLextern charnat * caml_search_exe_in_path(const charnat * name); CAMLextern char_os * caml_search_exe_in_path(const char_os * name);
/* Same, but search a shared library in the given path. */ /* Same, but search a shared library in the given path. */
extern charnat * caml_search_dll_in_path(struct ext_table * path, const charnat * name); extern char_os * caml_search_dll_in_path(struct ext_table * path, const char_os * name);
/* Open a shared library and return a handle on it. /* Open a shared library and return a handle on it.
If [for_execution] is true, perform full symbol resolution and If [for_execution] is true, perform full symbol resolution and
@ -62,7 +62,7 @@ extern charnat * caml_search_dll_in_path(struct ext_table * path, const charnat
If [global] is true, symbols from the shared library can be used If [global] is true, symbols from the shared library can be used
to resolve for other libraries to be opened later on. to resolve for other libraries to be opened later on.
Return [NULL] on error. */ Return [NULL] on error. */
extern void * caml_dlopen(charnat * libname, int for_execution, int global); extern void * caml_dlopen(char_os * libname, int for_execution, int global);
/* Close a shared library handle */ /* Close a shared library handle */
extern void caml_dlclose(void * handle); extern void caml_dlclose(void * handle);
@ -79,17 +79,17 @@ extern char * caml_dlerror(void);
/* Add to [contents] the (short) names of the files contained in /* Add to [contents] the (short) names of the files contained in
the directory named [dirname]. No entries are added for [.] and [..]. the directory named [dirname]. No entries are added for [.] and [..].
Return 0 on success, -1 on error; set errno in the case of error. */ Return 0 on success, -1 on error; set errno in the case of error. */
extern int caml_read_directory(charnat * dirname, struct ext_table * contents); extern int caml_read_directory(char_os * dirname, struct ext_table * contents);
/* Recover executable name if possible (/proc/sef/exe under Linux, /* Recover executable name if possible (/proc/sef/exe under Linux,
GetModuleFileName under Windows). Return NULL on error, GetModuleFileName under Windows). Return NULL on error,
string allocated with [caml_stat_alloc] on success. */ string allocated with [caml_stat_alloc] on success. */
extern charnat * caml_executable_name(void); extern char_os * caml_executable_name(void);
/* Secure version of [getenv]: returns NULL if the process has special /* Secure version of [getenv]: returns NULL if the process has special
privileges (setuid bit, setgid bit, capabilities). privileges (setuid bit, setgid bit, capabilities).
*/ */
extern charnat *caml_secure_getenv(charnat const *var); extern char_os *caml_secure_getenv(char_os const *var);
/* Windows Unicode support */ /* Windows Unicode support */

View File

@ -21,25 +21,25 @@
#include "mlvalues.h" #include "mlvalues.h"
#include "exec.h" #include "exec.h"
CAMLextern void caml_main(charnat **argv); CAMLextern void caml_main(char_os **argv);
CAMLextern void caml_startup_code( CAMLextern void caml_startup_code(
code_t code, asize_t code_size, code_t code, asize_t code_size,
char *data, asize_t data_size, char *data, asize_t data_size,
char *section_table, asize_t section_table_size, char *section_table, asize_t section_table_size,
int pooling, int pooling,
charnat **argv); char_os **argv);
CAMLextern value caml_startup_code_exn( CAMLextern value caml_startup_code_exn(
code_t code, asize_t code_size, code_t code, asize_t code_size,
char *data, asize_t data_size, char *data, asize_t data_size,
char *section_table, asize_t section_table_size, char *section_table, asize_t section_table_size,
int pooling, int pooling,
charnat **argv); char_os **argv);
enum { FILE_NOT_FOUND = -1, BAD_BYTECODE = -2 }; enum { FILE_NOT_FOUND = -1, BAD_BYTECODE = -2 };
extern int caml_attempt_open(charnat **name, struct exec_trailer *trail, extern int caml_attempt_open(char_os **name, struct exec_trailer *trail,
int do_open_script); int do_open_script);
extern void caml_read_section_descriptors(int fd, struct exec_trailer *trail); extern void caml_read_section_descriptors(int fd, struct exec_trailer *trail);
extern int32_t caml_seek_optional_section(int fd, struct exec_trailer *trail, extern int32_t caml_seek_optional_section(int fd, struct exec_trailer *trail,

View File

@ -29,12 +29,12 @@ extern "C" {
CAMLextern void caml_sys_error (value); CAMLextern void caml_sys_error (value);
CAMLextern void caml_sys_io_error (value); CAMLextern void caml_sys_io_error (value);
CAMLextern double caml_sys_time_unboxed(value); CAMLextern double caml_sys_time_unboxed(value);
CAMLextern void caml_sys_init (charnat * exe_name, charnat ** argv); CAMLextern void caml_sys_init (char_os * exe_name, char_os ** argv);
CAMLextern value caml_sys_exit (value); CAMLextern value caml_sys_exit (value);
extern double caml_sys_time_unboxed(value); extern double caml_sys_time_unboxed(value);
CAMLextern value caml_sys_get_argv(value unit); CAMLextern value caml_sys_get_argv(value unit);
extern charnat * caml_exe_name; extern char_os * caml_exe_name;
#ifdef __cplusplus #ifdef __cplusplus
} }

View File

@ -164,7 +164,7 @@ static void winsock_cleanup(void)
void caml_debugger_init(void) void caml_debugger_init(void)
{ {
char * address; char * address;
charnat * a; char_os * a;
char * port, * p; char * port, * p;
struct hostent * host; struct hostent * host;
int n; int n;
@ -175,7 +175,7 @@ void caml_debugger_init(void)
Store_field(marshal_flags, 1, Val_emptylist); Store_field(marshal_flags, 1, Val_emptylist);
a = caml_secure_getenv(_T("CAML_DEBUG_SOCKET")); a = caml_secure_getenv(_T("CAML_DEBUG_SOCKET"));
address = a ? caml_stat_strdup_of_utf16(a) : NULL; address = a ? caml_stat_strdup_of_os(a) : NULL;
if (address == NULL) return; if (address == NULL) return;
if (dbg_addr != NULL) caml_stat_free(dbg_addr); if (dbg_addr != NULL) caml_stat_free(dbg_addr);
dbg_addr = address; dbg_addr = address;

View File

@ -75,9 +75,9 @@ static c_primitive lookup_primitive(char * name)
#define LD_CONF_NAME _T("ld.conf") #define LD_CONF_NAME _T("ld.conf")
static charnat * parse_ld_conf(void) static char_os * parse_ld_conf(void)
{ {
charnat * stdlib, * ldconfname, * wconfig, * p, * q, * tofree = NULL; char_os * stdlib, * ldconfname, * wconfig, * p, * q, * tofree = NULL;
char * config; char * config;
#ifdef _WIN32 #ifdef _WIN32
struct _stati64 st; struct _stati64 st;
@ -88,25 +88,25 @@ static charnat * parse_ld_conf(void)
stdlib = caml_secure_getenv(_T("OCAMLLIB")); stdlib = caml_secure_getenv(_T("OCAMLLIB"));
if (stdlib == NULL) stdlib = caml_secure_getenv(_T("CAMLLIB")); if (stdlib == NULL) stdlib = caml_secure_getenv(_T("CAMLLIB"));
if (stdlib == NULL) stdlib = tofree = caml_stat_strdup_to_utf16(OCAML_STDLIB_DIR); if (stdlib == NULL) stdlib = tofree = caml_stat_strdup_to_os(OCAML_STDLIB_DIR);
ldconfname = caml_stat_tcsconcat(3, stdlib, _T("/"), LD_CONF_NAME); ldconfname = caml_stat_strconcat_os(3, stdlib, _T("/"), LD_CONF_NAME);
if (tofree != NULL) caml_stat_free(tofree); if (tofree != NULL) caml_stat_free(tofree);
if (_tstat(ldconfname, &st) == -1) { if (stat_os(ldconfname, &st) == -1) {
caml_stat_free(ldconfname); caml_stat_free(ldconfname);
return NULL; return NULL;
} }
ldconf = _topen(ldconfname, O_RDONLY, 0); ldconf = open_os(ldconfname, O_RDONLY, 0);
if (ldconf == -1) if (ldconf == -1)
caml_fatal_error_arg("Fatal error: cannot read loader config file %s\n", caml_fatal_error_arg("Fatal error: cannot read loader config file %s\n",
caml_stat_strdup_of_utf16(ldconfname)); caml_stat_strdup_of_os(ldconfname));
config = caml_stat_alloc(st.st_size + 1); config = caml_stat_alloc(st.st_size + 1);
nread = read(ldconf, config, st.st_size); nread = read(ldconf, config, st.st_size);
if (nread == -1) if (nread == -1)
caml_fatal_error_arg caml_fatal_error_arg
("Fatal error: error while reading loader config file %s\n", ("Fatal error: error while reading loader config file %s\n",
caml_stat_strdup_of_utf16(ldconfname)); caml_stat_strdup_of_os(ldconfname));
config[nread] = 0; config[nread] = 0;
wconfig = caml_stat_strdup_to_utf16(config); wconfig = caml_stat_strdup_to_os(config);
caml_stat_free(config); caml_stat_free(config);
q = wconfig; q = wconfig;
for (p = wconfig; *p != 0; p++) { for (p = wconfig; *p != 0; p++) {
@ -124,9 +124,9 @@ static charnat * parse_ld_conf(void)
/* Open the given shared library and add it to shared_libs. /* Open the given shared library and add it to shared_libs.
Abort on error. */ Abort on error. */
static void open_shared_lib(charnat * name) static void open_shared_lib(char_os * name)
{ {
charnat * realname; char_os * realname;
void * handle; void * handle;
realname = caml_search_dll_in_path(&caml_shared_libs_path, name); realname = caml_search_dll_in_path(&caml_shared_libs_path, name);
@ -137,7 +137,7 @@ static void open_shared_lib(charnat * name)
caml_leave_blocking_section(); caml_leave_blocking_section();
if (handle == NULL) if (handle == NULL)
caml_fatal_error_arg2("Fatal error: cannot load shared library %s\n", caml_fatal_error_arg2("Fatal error: cannot load shared library %s\n",
caml_stat_strdup_of_utf16(name), caml_stat_strdup_of_os(name),
"Reason: %s\n", caml_dlerror()); "Reason: %s\n", caml_dlerror());
caml_ext_table_add(&shared_libs, handle); caml_ext_table_add(&shared_libs, handle);
caml_stat_free(realname); caml_stat_free(realname);
@ -146,12 +146,12 @@ static void open_shared_lib(charnat * name)
/* Build the table of primitives, given a search path and a list /* Build the table of primitives, given a search path and a list
of shared libraries (both 0-separated in a char array). of shared libraries (both 0-separated in a char array).
Abort the runtime system on error. */ Abort the runtime system on error. */
void caml_build_primitive_table(charnat * lib_path, void caml_build_primitive_table(char_os * lib_path,
charnat * libs, char_os * libs,
char * req_prims) char * req_prims)
{ {
charnat * tofree1, * tofree2; char_os * tofree1, * tofree2;
charnat * p; char_os * p;
char * q; char * q;
/* Initialize the search path for dynamic libraries: /* Initialize the search path for dynamic libraries:
@ -162,13 +162,13 @@ void caml_build_primitive_table(charnat * lib_path,
tofree1 = caml_decompose_path(&caml_shared_libs_path, tofree1 = caml_decompose_path(&caml_shared_libs_path,
caml_secure_getenv(_T("CAML_LD_LIBRARY_PATH"))); caml_secure_getenv(_T("CAML_LD_LIBRARY_PATH")));
if (lib_path != NULL) if (lib_path != NULL)
for (p = lib_path; *p != 0; p += _tcslen(p) + 1) for (p = lib_path; *p != 0; p += strlen_os(p) + 1)
caml_ext_table_add(&caml_shared_libs_path, p); caml_ext_table_add(&caml_shared_libs_path, p);
tofree2 = parse_ld_conf(); tofree2 = parse_ld_conf();
/* Open the shared libraries */ /* Open the shared libraries */
caml_ext_table_init(&shared_libs, 8); caml_ext_table_init(&shared_libs, 8);
if (libs != NULL) if (libs != NULL)
for (p = libs; *p != 0; p += _tcslen(p) + 1) for (p = libs; *p != 0; p += strlen_os(p) + 1)
open_shared_lib(p); open_shared_lib(p);
/* Build the primitive table */ /* Build the primitive table */
caml_ext_table_init(&caml_prim_table, 0x180); caml_ext_table_init(&caml_prim_table, 0x180);
@ -225,11 +225,11 @@ CAMLprim value caml_dynlink_open_lib(value mode, value filename)
{ {
void * handle; void * handle;
value result; value result;
charnat * p; char_os * p;
caml_gc_message(0x100, "Opening shared library %s\n", caml_gc_message(0x100, "Opening shared library %s\n",
String_val(filename)); String_val(filename));
p = caml_stat_strdup_to_utf16(String_val(filename)); p = caml_stat_strdup_to_os(String_val(filename));
caml_enter_blocking_section(); caml_enter_blocking_section();
handle = caml_dlopen(p, Int_val(mode), 1); handle = caml_dlopen(p, Int_val(mode), 1);
caml_leave_blocking_section(); caml_leave_blocking_section();

View File

@ -26,7 +26,7 @@
#include <windows.h> #include <windows.h>
#endif #endif
CAMLextern void caml_main (charnat **); CAMLextern void caml_main (char_os **);
#ifdef _WIN32 #ifdef _WIN32
CAMLextern void caml_expand_command_line (int *, wchar_t ***); CAMLextern void caml_expand_command_line (int *, wchar_t ***);

View File

@ -88,10 +88,10 @@ static int read_trailer(int fd, struct exec_trailer *trail)
return BAD_BYTECODE; return BAD_BYTECODE;
} }
int caml_attempt_open(charnat **name, struct exec_trailer *trail, int caml_attempt_open(char_os **name, struct exec_trailer *trail,
int do_open_script) int do_open_script)
{ {
charnat * truename; char_os * truename;
int fd; int fd;
int err; int err;
char buf [2]; char buf [2];
@ -99,7 +99,7 @@ int caml_attempt_open(charnat **name, struct exec_trailer *trail,
truename = caml_search_exe_in_path(*name); truename = caml_search_exe_in_path(*name);
caml_gc_message(0x100, "Opening bytecode executable %" caml_gc_message(0x100, "Opening bytecode executable %"
ARCH_CHARNATSTR_PRINTF_FORMAT "\n", truename); ARCH_CHARNATSTR_PRINTF_FORMAT "\n", truename);
fd = _topen(truename, O_RDONLY | O_BINARY); fd = open_os(truename, O_RDONLY | O_BINARY);
if (fd == -1) { if (fd == -1) {
caml_stat_free(truename); caml_stat_free(truename);
caml_gc_message(0x100, "Cannot open file\n"); caml_gc_message(0x100, "Cannot open file\n");
@ -192,7 +192,7 @@ static char * read_section(int fd, struct exec_trailer *trail, char *name)
#ifdef _WIN32 #ifdef _WIN32
static wchar_t * read_section_to_utf16(int fd, struct exec_trailer *trail, char *name) static char_os * read_section_to_os(int fd, struct exec_trailer *trail, char *name)
{ {
int32_t len, wlen; int32_t len, wlen;
char * data; char * data;
@ -214,7 +214,7 @@ static wchar_t * read_section_to_utf16(int fd, struct exec_trailer *trail, char
#else #else
#define read_section_to_utf16 read_section #define read_section_to_os read_section
#endif #endif
@ -245,7 +245,7 @@ Algorithm:
/* Parse options on the command line */ /* Parse options on the command line */
static int parse_command_line(charnat **argv) static int parse_command_line(char_os **argv)
{ {
int i, j; int i, j;
@ -255,10 +255,10 @@ static int parse_command_line(charnat **argv)
++ caml_trace_level; /* ignored unless DEBUG mode */ ++ caml_trace_level; /* ignored unless DEBUG mode */
break; break;
case _T('v'): case _T('v'):
if (!_tcscmp (argv[i], _T("-version"))){ if (!strcmp_os (argv[i], _T("-version"))){
printf ("The OCaml runtime, version " OCAML_VERSION_STRING "\n"); printf ("The OCaml runtime, version " OCAML_VERSION_STRING "\n");
exit (0); exit (0);
}else if (!_tcscmp (argv[i], _T("-vnum"))){ }else if (!strcmp_os (argv[i], _T("-vnum"))){
printf (OCAML_VERSION_STRING "\n"); printf (OCAML_VERSION_STRING "\n");
exit (0); exit (0);
}else{ }else{
@ -280,7 +280,7 @@ static int parse_command_line(charnat **argv)
} }
break; break;
default: default:
caml_fatal_error_arg("Unknown option %s.\n", caml_stat_strdup_of_utf16(argv[i])); caml_fatal_error_arg("Unknown option %s.\n", caml_stat_strdup_of_os(argv[i]));
} }
} }
return i; return i;
@ -303,15 +303,15 @@ extern int caml_ensure_spacetime_dot_o_is_included;
/* Main entry point when loading code from a file */ /* Main entry point when loading code from a file */
CAMLexport void caml_main(charnat **argv) CAMLexport void caml_main(char_os **argv)
{ {
int fd, pos; int fd, pos;
struct exec_trailer trail; struct exec_trailer trail;
struct channel * chan; struct channel * chan;
value res; value res;
char * req_prims; char * req_prims;
charnat * shared_lib_path, * shared_libs; char_os * shared_lib_path, * shared_libs;
charnat * exe_name, * proc_self_exe; char_os * exe_name, * proc_self_exe;
caml_ensure_spacetime_dot_o_is_included++; caml_ensure_spacetime_dot_o_is_included++;
@ -362,12 +362,12 @@ CAMLexport void caml_main(charnat **argv)
fd = caml_attempt_open(&exe_name, &trail, 1); fd = caml_attempt_open(&exe_name, &trail, 1);
switch(fd) { switch(fd) {
case FILE_NOT_FOUND: case FILE_NOT_FOUND:
caml_fatal_error_arg("Fatal error: cannot find file '%s'\n", caml_stat_strdup_of_utf16(argv[pos])); caml_fatal_error_arg("Fatal error: cannot find file '%s'\n", caml_stat_strdup_of_os(argv[pos]));
break; break;
case BAD_BYTECODE: case BAD_BYTECODE:
caml_fatal_error_arg( caml_fatal_error_arg(
"Fatal error: the file '%s' is not a bytecode executable file\n", "Fatal error: the file '%s' is not a bytecode executable file\n",
caml_stat_strdup_of_utf16(exe_name)); caml_stat_strdup_of_os(exe_name));
break; break;
} }
} }
@ -389,8 +389,8 @@ CAMLexport void caml_main(charnat **argv)
caml_load_code(fd, caml_code_size); caml_load_code(fd, caml_code_size);
caml_init_debug_info(); caml_init_debug_info();
/* Build the table of primitives */ /* Build the table of primitives */
shared_lib_path = read_section_to_utf16(fd, &trail, "DLPT"); shared_lib_path = read_section_to_os(fd, &trail, "DLPT");
shared_libs = read_section_to_utf16(fd, &trail, "DLLS"); shared_libs = read_section_to_os(fd, &trail, "DLLS");
req_prims = read_section(fd, &trail, "PRIM"); req_prims = read_section(fd, &trail, "PRIM");
if (req_prims == NULL) caml_fatal_error("Fatal error: no PRIM section\n"); if (req_prims == NULL) caml_fatal_error("Fatal error: no PRIM section\n");
caml_build_primitive_table(shared_lib_path, shared_libs, req_prims); caml_build_primitive_table(shared_lib_path, shared_libs, req_prims);
@ -434,10 +434,10 @@ CAMLexport value caml_startup_code_exn(
char *data, asize_t data_size, char *data, asize_t data_size,
char *section_table, asize_t section_table_size, char *section_table, asize_t section_table_size,
int pooling, int pooling,
charnat **argv) char_os **argv)
{ {
charnat * cds_file; char_os * cds_file;
charnat * exe_name; char_os * exe_name;
/* Determine options */ /* Determine options */
#ifdef DEBUG #ifdef DEBUG
@ -459,7 +459,7 @@ CAMLexport value caml_startup_code_exn(
caml_init_custom_operations(); caml_init_custom_operations();
cds_file = caml_secure_getenv(_T("CAML_DEBUG_FILE")); cds_file = caml_secure_getenv(_T("CAML_DEBUG_FILE"));
if (cds_file != NULL) { if (cds_file != NULL) {
caml_cds_file = caml_stat_tcsdup(cds_file); caml_cds_file = caml_stat_strdup_os(cds_file);
} }
exe_name = caml_executable_name(); exe_name = caml_executable_name();
if (exe_name == NULL) exe_name = caml_search_exe_in_path(argv[0]); if (exe_name == NULL) exe_name = caml_search_exe_in_path(argv[0]);
@ -511,7 +511,7 @@ CAMLexport void caml_startup_code(
char *data, asize_t data_size, char *data, asize_t data_size,
char *section_table, asize_t section_table_size, char *section_table, asize_t section_table_size,
int pooling, int pooling,
charnat **argv) char_os **argv)
{ {
value res; value res;

View File

@ -64,12 +64,12 @@ uintnat caml_trace_level = 0;
uintnat caml_cleanup_on_exit = 0; uintnat caml_cleanup_on_exit = 0;
static void scanmult (charnat *opt, uintnat *var) static void scanmult (char_os *opt, uintnat *var)
{ {
charnat mult = _T(' '); char_os mult = _T(' ');
unsigned int val = 1; unsigned int val = 1;
_stscanf (opt, _T("=%u%c"), &val, &mult); sscanf_os (opt, _T("=%u%c"), &val, &mult);
_stscanf (opt, _T("=0x%x%c"), &val, &mult); sscanf_os (opt, _T("=0x%x%c"), &val, &mult);
switch (mult) { switch (mult) {
case _T('k'): *var = (uintnat) val * 1024; break; case _T('k'): *var = (uintnat) val * 1024; break;
case _T('M'): *var = (uintnat) val * (1024 * 1024); break; case _T('M'): *var = (uintnat) val * (1024 * 1024); break;
@ -80,7 +80,7 @@ static void scanmult (charnat *opt, uintnat *var)
void caml_parse_ocamlrunparam(void) void caml_parse_ocamlrunparam(void)
{ {
charnat *opt = caml_secure_getenv (_T("OCAMLRUNPARAM")); char_os *opt = caml_secure_getenv (_T("OCAMLRUNPARAM"));
uintnat p; uintnat p;
if (opt == NULL) opt = caml_secure_getenv (_T("CAMLRUNPARAM")); if (opt == NULL) opt = caml_secure_getenv (_T("CAMLRUNPARAM"));

View File

@ -181,7 +181,7 @@ CAMLprim value caml_sys_open(value path, value vflags, value vperm)
{ {
CAMLparam3(path, vflags, vperm); CAMLparam3(path, vflags, vperm);
int fd, flags, perm; int fd, flags, perm;
charnat * p; char_os * p;
#if defined(O_CLOEXEC) #if defined(O_CLOEXEC)
flags = O_CLOEXEC; flags = O_CLOEXEC;
@ -192,7 +192,7 @@ CAMLprim value caml_sys_open(value path, value vflags, value vperm)
#endif #endif
caml_sys_check_path(path); caml_sys_check_path(path);
p = caml_stat_strdup_to_utf16(String_val(path)); p = caml_stat_strdup_to_os(String_val(path));
flags |= caml_convert_flag_list(vflags, sys_open_flags); flags |= caml_convert_flag_list(vflags, sys_open_flags);
perm = Int_val(vperm); perm = Int_val(vperm);
/* open on a named FIFO can block (PR#1533) */ /* open on a named FIFO can block (PR#1533) */
@ -226,11 +226,11 @@ CAMLprim value caml_sys_file_exists(value name)
#else #else
struct stat st; struct stat st;
#endif #endif
charnat * p; char_os * p;
int ret; int ret;
if (! caml_string_is_c_safe(name)) return Val_false; if (! caml_string_is_c_safe(name)) return Val_false;
p = caml_stat_strdup_to_utf16(String_val(name)); p = caml_stat_strdup_to_os(String_val(name));
caml_enter_blocking_section(); caml_enter_blocking_section();
ret = CAML_SYS_STAT(p, &st); ret = CAML_SYS_STAT(p, &st);
caml_leave_blocking_section(); caml_leave_blocking_section();
@ -247,11 +247,11 @@ CAMLprim value caml_sys_is_directory(value name)
#else #else
struct stat st; struct stat st;
#endif #endif
charnat * p; char_os * p;
int ret; int ret;
caml_sys_check_path(name); caml_sys_check_path(name);
p = caml_stat_strdup_to_utf16(String_val(name)); p = caml_stat_strdup_to_os(String_val(name));
caml_enter_blocking_section(); caml_enter_blocking_section();
ret = CAML_SYS_STAT(p, &st); ret = CAML_SYS_STAT(p, &st);
caml_leave_blocking_section(); caml_leave_blocking_section();
@ -268,10 +268,10 @@ CAMLprim value caml_sys_is_directory(value name)
CAMLprim value caml_sys_remove(value name) CAMLprim value caml_sys_remove(value name)
{ {
CAMLparam1(name); CAMLparam1(name);
charnat * p; char_os * p;
int ret; int ret;
caml_sys_check_path(name); caml_sys_check_path(name);
p = caml_stat_strdup_to_utf16(String_val(name)); p = caml_stat_strdup_to_os(String_val(name));
caml_enter_blocking_section(); caml_enter_blocking_section();
ret = CAML_SYS_UNLINK(p); ret = CAML_SYS_UNLINK(p);
caml_leave_blocking_section(); caml_leave_blocking_section();
@ -282,13 +282,13 @@ CAMLprim value caml_sys_remove(value name)
CAMLprim value caml_sys_rename(value oldname, value newname) CAMLprim value caml_sys_rename(value oldname, value newname)
{ {
charnat * p_old; char_os * p_old;
charnat * p_new; char_os * p_new;
int ret; int ret;
caml_sys_check_path(oldname); caml_sys_check_path(oldname);
caml_sys_check_path(newname); caml_sys_check_path(newname);
p_old = caml_stat_strdup_to_utf16(String_val(oldname)); p_old = caml_stat_strdup_to_os(String_val(oldname));
p_new = caml_stat_strdup_to_utf16(String_val(newname)); p_new = caml_stat_strdup_to_os(String_val(newname));
caml_enter_blocking_section(); caml_enter_blocking_section();
ret = CAML_SYS_RENAME(p_old, p_new); ret = CAML_SYS_RENAME(p_old, p_new);
caml_leave_blocking_section(); caml_leave_blocking_section();
@ -302,10 +302,10 @@ CAMLprim value caml_sys_rename(value oldname, value newname)
CAMLprim value caml_sys_chdir(value dirname) CAMLprim value caml_sys_chdir(value dirname)
{ {
CAMLparam1(dirname); CAMLparam1(dirname);
charnat * p; char_os * p;
int ret; int ret;
caml_sys_check_path(dirname); caml_sys_check_path(dirname);
p = caml_stat_strdup_to_utf16(String_val(dirname)); p = caml_stat_strdup_to_os(String_val(dirname));
caml_enter_blocking_section(); caml_enter_blocking_section();
ret = CAML_SYS_CHDIR(p); ret = CAML_SYS_CHDIR(p);
caml_leave_blocking_section(); caml_leave_blocking_section();
@ -316,57 +316,57 @@ CAMLprim value caml_sys_chdir(value dirname)
CAMLprim value caml_sys_getcwd(value unit) CAMLprim value caml_sys_getcwd(value unit)
{ {
charnat buff[4096]; char_os buff[4096];
charnat * ret; char_os * ret;
#ifdef HAS_GETCWD #ifdef HAS_GETCWD
ret = _tgetcwd(buff, sizeof(buff)/sizeof(*buff)); ret = getcwd_os(buff, sizeof(buff)/sizeof(*buff));
#else #else
ret = getwd(buff); ret = getwd(buff);
#endif /* HAS_GETCWD */ #endif /* HAS_GETCWD */
if (ret == 0) caml_sys_error(NO_ARG); if (ret == 0) caml_sys_error(NO_ARG);
return caml_copy_string_of_utf16(buff); return caml_copy_string_of_os(buff);
} }
CAMLprim value caml_sys_unsafe_getenv(value var) CAMLprim value caml_sys_unsafe_getenv(value var)
{ {
charnat * res, * p; char_os * res, * p;
if (! caml_string_is_c_safe(var)) caml_raise_not_found(); if (! caml_string_is_c_safe(var)) caml_raise_not_found();
p = caml_stat_strdup_to_utf16(String_val(var)); p = caml_stat_strdup_to_os(String_val(var));
res = CAML_SYS_GETENV(p); res = CAML_SYS_GETENV(p);
caml_stat_free(p); caml_stat_free(p);
if (res == 0) caml_raise_not_found(); if (res == 0) caml_raise_not_found();
return caml_copy_string_of_utf16(res); return caml_copy_string_of_os(res);
} }
CAMLprim value caml_sys_getenv(value var) CAMLprim value caml_sys_getenv(value var)
{ {
charnat * res, * p; char_os * res, * p;
if (! caml_string_is_c_safe(var)) caml_raise_not_found(); if (! caml_string_is_c_safe(var)) caml_raise_not_found();
p = caml_stat_strdup_to_utf16(String_val(var)); p = caml_stat_strdup_to_os(String_val(var));
res = caml_secure_getenv(p); res = caml_secure_getenv(p);
caml_stat_free(p); caml_stat_free(p);
if (res == 0) caml_raise_not_found(); if (res == 0) caml_raise_not_found();
return caml_copy_string_of_utf16(res); return caml_copy_string_of_os(res);
} }
charnat * caml_exe_name; char_os * caml_exe_name;
charnat ** caml_main_argv; char_os ** caml_main_argv;
CAMLprim value caml_sys_get_argv(value unit) CAMLprim value caml_sys_get_argv(value unit)
{ {
CAMLparam0 (); /* unit is unused */ CAMLparam0 (); /* unit is unused */
CAMLlocal3 (exe_name, argv, res); CAMLlocal3 (exe_name, argv, res);
exe_name = caml_copy_string_of_utf16(caml_exe_name); exe_name = caml_copy_string_of_os(caml_exe_name);
argv = caml_alloc_array((void *)caml_copy_string_of_utf16, (char const **) caml_main_argv); argv = caml_alloc_array((void *)caml_copy_string_of_os, (char const **) caml_main_argv);
res = caml_alloc_small(2, 0); res = caml_alloc_small(2, 0);
Field(res, 0) = exe_name; Field(res, 0) = exe_name;
Field(res, 1) = argv; Field(res, 1) = argv;
CAMLreturn(res); CAMLreturn(res);
} }
void caml_sys_init(charnat * exe_name, charnat **argv) void caml_sys_init(char_os * exe_name, char_os **argv)
{ {
#ifdef CAML_WITH_CPLUGINS #ifdef CAML_WITH_CPLUGINS
caml_cplugins_init(exe_name, argv); caml_cplugins_init(exe_name, argv);
@ -390,13 +390,13 @@ CAMLprim value caml_sys_system_command(value command)
{ {
CAMLparam1 (command); CAMLparam1 (command);
int status, retcode; int status, retcode;
charnat *buf; char_os *buf;
if (! caml_string_is_c_safe (command)) { if (! caml_string_is_c_safe (command)) {
errno = EINVAL; errno = EINVAL;
caml_sys_error(command); caml_sys_error(command);
} }
buf = caml_stat_strdup_to_utf16(String_val(command)); buf = caml_stat_strdup_to_os(String_val(command));
caml_enter_blocking_section (); caml_enter_blocking_section ();
status = CAML_SYS_SYSTEM(buf); status = CAML_SYS_SYSTEM(buf);
caml_leave_blocking_section (); caml_leave_blocking_section ();
@ -579,12 +579,12 @@ CAMLprim value caml_sys_read_directory(value path)
CAMLparam1(path); CAMLparam1(path);
CAMLlocal1(result); CAMLlocal1(result);
struct ext_table tbl; struct ext_table tbl;
charnat * p; char_os * p;
int ret; int ret;
caml_sys_check_path(path); caml_sys_check_path(path);
caml_ext_table_init(&tbl, 50); caml_ext_table_init(&tbl, 50);
p = caml_stat_strdup_to_utf16(String_val(path)); p = caml_stat_strdup_to_os(String_val(path));
caml_enter_blocking_section(); caml_enter_blocking_section();
ret = CAML_SYS_READ_DIRECTORY(p, &tbl); ret = CAML_SYS_READ_DIRECTORY(p, &tbl);
caml_leave_blocking_section(); caml_leave_blocking_section();
@ -631,7 +631,7 @@ value (*caml_cplugins_prim)(int,value,value,value) = NULL;
static struct cplugin_context cplugin_context; static struct cplugin_context cplugin_context;
void caml_load_plugin(charnat *plugin) void caml_load_plugin(char_os *plugin)
{ {
void* dll_handle = NULL; void* dll_handle = NULL;
@ -647,15 +647,15 @@ void caml_load_plugin(charnat *plugin)
} }
} else { } else {
fprintf(stderr, "Cannot load C plugin %s\nReason: %s\n", fprintf(stderr, "Cannot load C plugin %s\nReason: %s\n",
caml_stat_strdup_of_utf16(plugin), caml_dlerror()); caml_stat_strdup_of_os(plugin), caml_dlerror());
} }
} }
void caml_cplugins_load(charnat *env_variable) void caml_cplugins_load(char_os *env_variable)
{ {
charnat *plugins = caml_secure_getenv(env_variable); char_os *plugins = caml_secure_getenv(env_variable);
if(plugins != NULL){ if(plugins != NULL){
charnat* curs = plugins; char_os* curs = plugins;
while(*curs != 0){ while(*curs != 0){
if(*curs == _T(',')){ if(*curs == _T(',')){
if(curs > plugins){ if(curs > plugins){
@ -670,7 +670,7 @@ void caml_cplugins_load(charnat *env_variable)
} }
} }
void caml_cplugins_init(charnat * exe_name, charnat **argv) void caml_cplugins_init(char_os * exe_name, char_os **argv)
{ {
cplugin_context.api_version = CAML_CPLUGIN_CONTEXT_API; cplugin_context.api_version = CAML_CPLUGIN_CONTEXT_API;
cplugin_context.prims_bitmap = CAML_CPLUGINS_PRIMS_BITMAP; cplugin_context.prims_bitmap = CAML_CPLUGINS_PRIMS_BITMAP;

View File

@ -190,7 +190,7 @@ CAMLexport wchar_t * caml_search_exe_in_path(const wchar_t * name)
if (retcode == 0) { if (retcode == 0) {
caml_gc_message(0x100, "%" ARCH_CHARNATSTR_PRINTF_FORMAT " not found in search path\n", name); caml_gc_message(0x100, "%" ARCH_CHARNATSTR_PRINTF_FORMAT " not found in search path\n", name);
caml_stat_free(fullname); caml_stat_free(fullname);
return caml_stat_tcsdup(name); return caml_stat_strdup_os(name);
} }
if (retcode < fullnamelen) if (retcode < fullnamelen)
return fullname; return fullname;

View File

@ -22,17 +22,17 @@
#include <stdarg.h> #include <stdarg.h>
#include <caml/misc.h> #include <caml/misc.h>
typedef charnat **array; typedef char_os **array;
typedef void Logger(void *, const char *, va_list ap); typedef void Logger(void *, const char *, va_list ap);
typedef struct { typedef struct {
charnat *program; char_os *program;
array argv; array argv;
/* array envp; */ /* array envp; */
charnat *stdin_filename; char_os *stdin_filename;
charnat *stdout_filename; char_os *stdout_filename;
charnat *stderr_filename; char_os *stderr_filename;
int append; int append;
int timeout; int timeout;
Logger *logger; Logger *logger;

View File

@ -20,7 +20,7 @@
/* is_defined(str) returns 1 iff str points to a non-empty string */ /* is_defined(str) returns 1 iff str points to a non-empty string */
/* Otherwise returns 0 */ /* Otherwise returns 0 */
static int is_defined(const charnat *str) static int is_defined(const char_os *str)
{ {
return (str != NULL) && (*str != 0); return (str != NULL) && (*str != 0);
} }

View File

@ -37,16 +37,16 @@ static array cstringvect(value arg)
mlsize_t size, i; mlsize_t size, i;
size = Wosize_val(arg); size = Wosize_val(arg);
res = (array) caml_stat_alloc((size + 1) * sizeof(charnat *)); res = (array) caml_stat_alloc((size + 1) * sizeof(char_os *));
for (i = 0; i < size; i++) for (i = 0; i < size; i++)
res[i] = caml_stat_strdup_to_utf16(String_val(Field(arg, i))); res[i] = caml_stat_strdup_to_os(String_val(Field(arg, i)));
res[size] = NULL; res[size] = NULL;
return res; return res;
} }
static void free_cstringvect(array v) static void free_cstringvect(array v)
{ {
charnat **p; char_os **p;
for (p = v; *p != NULL; p++) for (p = v; *p != NULL; p++)
caml_stat_free(*p); caml_stat_free(*p);
caml_stat_free(v); caml_stat_free(v);
@ -79,12 +79,12 @@ CAMLprim value caml_run_command(value caml_settings)
command_settings settings; command_settings settings;
CAMLparam1(caml_settings); CAMLparam1(caml_settings);
settings.program = caml_stat_strdup_to_utf16(String_val(Field(caml_settings, 0))); settings.program = caml_stat_strdup_to_os(String_val(Field(caml_settings, 0)));
settings.argv = cstringvect(Field(caml_settings, 1)); settings.argv = cstringvect(Field(caml_settings, 1));
/* settings.envp = cstringvect(Field(caml_settings, 2)); */ /* settings.envp = cstringvect(Field(caml_settings, 2)); */
settings.stdin_filename = caml_stat_strdup_to_utf16(String_val(Field(caml_settings, 2))); settings.stdin_filename = caml_stat_strdup_to_os(String_val(Field(caml_settings, 2)));
settings.stdout_filename = caml_stat_strdup_to_utf16(String_val(Field(caml_settings, 4))); settings.stdout_filename = caml_stat_strdup_to_os(String_val(Field(caml_settings, 4)));
settings.stderr_filename = caml_stat_strdup_to_utf16(String_val(Field(caml_settings, 4))); settings.stderr_filename = caml_stat_strdup_to_os(String_val(Field(caml_settings, 4)));
settings.append = Bool_val(Field(caml_settings, 5)); settings.append = Bool_val(Field(caml_settings, 5));
settings.timeout = Int_val(Field(caml_settings, 6)); settings.timeout = Int_val(Field(caml_settings, 6));
settings.logger = logToChannel; settings.logger = logToChannel;

View File

@ -24,12 +24,12 @@
CAMLprim value unix_chdir(value path) CAMLprim value unix_chdir(value path)
{ {
CAMLparam1(path); CAMLparam1(path);
charnat * p; char_os * p;
int ret; int ret;
caml_unix_check_path(path, "chdir"); caml_unix_check_path(path, "chdir");
p = caml_stat_strdup_to_utf16(String_val(path)); p = caml_stat_strdup_to_os(String_val(path));
caml_enter_blocking_section(); caml_enter_blocking_section();
ret = _tchdir(p); ret = chdir_os(p);
caml_leave_blocking_section(); caml_leave_blocking_section();
caml_stat_free(p); caml_stat_free(p);
if (ret == -1) uerror("chdir", path); if (ret == -1) uerror("chdir", path);

View File

@ -26,12 +26,12 @@
CAMLprim value unix_chmod(value path, value perm) CAMLprim value unix_chmod(value path, value perm)
{ {
CAMLparam2(path, perm); CAMLparam2(path, perm);
charnat * p; char_os * p;
int ret; int ret;
caml_unix_check_path(path, "chmod"); caml_unix_check_path(path, "chmod");
p = caml_stat_strdup_to_utf16(String_val(path)); p = caml_stat_strdup_to_os(String_val(path));
caml_enter_blocking_section(); caml_enter_blocking_section();
ret = _tchmod(p, Int_val(perm)); ret = chmod_os(p, Int_val(perm));
caml_leave_blocking_section(); caml_leave_blocking_section();
caml_stat_free(p); caml_stat_free(p);
if (ret == -1) uerror("chmod", path); if (ret == -1) uerror("chmod", path);

View File

@ -21,22 +21,22 @@
#include <caml/osdeps.h> #include <caml/osdeps.h>
#include "unixsupport.h" #include "unixsupport.h"
charnat ** cstringvect(value arg, char * cmdname) char_os ** cstringvect(value arg, char * cmdname)
{ {
charnat ** res; char_os ** res;
mlsize_t size, i; mlsize_t size, i;
size = Wosize_val(arg); size = Wosize_val(arg);
for (i = 0; i < size; i++) for (i = 0; i < size; i++)
if (! caml_string_is_c_safe(Field(arg, i))) if (! caml_string_is_c_safe(Field(arg, i)))
unix_error(EINVAL, cmdname, Field(arg, i)); unix_error(EINVAL, cmdname, Field(arg, i));
res = (charnat **) caml_stat_alloc((size + 1) * sizeof(charnat *)); res = (char_os **) caml_stat_alloc((size + 1) * sizeof(char_os *));
for (i = 0; i < size; i++) res[i] = caml_stat_strdup_to_utf16(String_val(Field(arg, i))); for (i = 0; i < size; i++) res[i] = caml_stat_strdup_to_os(String_val(Field(arg, i)));
res[size] = NULL; res[size] = NULL;
return res; return res;
} }
void cstringvect_free(charnat ** v) void cstringvect_free(char_os ** v)
{ {
int i = 0; int i = 0;
while (v[i]) caml_stat_free(v[i++]); while (v[i]) caml_stat_free(v[i++]);

View File

@ -22,12 +22,12 @@
CAMLprim value unix_execv(value path, value args) CAMLprim value unix_execv(value path, value args)
{ {
charnat * wpath; char_os * wpath;
charnat ** argv; char_os ** argv;
caml_unix_check_path(path, "execv"); caml_unix_check_path(path, "execv");
argv = cstringvect(args, "execv"); argv = cstringvect(args, "execv");
wpath = caml_stat_strdup_to_utf16(String_val(path)); wpath = caml_stat_strdup_to_os(String_val(path));
(void) _texecv(wpath, EXECV_CAST argv); (void) execv_os(wpath, EXECV_CAST argv);
caml_stat_free(wpath); caml_stat_free(wpath);
cstringvect_free(argv); cstringvect_free(argv);
uerror("execv", path); uerror("execv", path);

View File

@ -22,14 +22,14 @@
CAMLprim value unix_execve(value path, value args, value env) CAMLprim value unix_execve(value path, value args, value env)
{ {
charnat ** argv; char_os ** argv;
charnat ** envp; char_os ** envp;
charnat * wpath; char_os * wpath;
caml_unix_check_path(path, "execve"); caml_unix_check_path(path, "execve");
argv = cstringvect(args, "execve"); argv = cstringvect(args, "execve");
envp = cstringvect(env, "execve"); envp = cstringvect(env, "execve");
wpath = caml_stat_strdup_to_utf16(String_val(path)); wpath = caml_stat_strdup_to_os(String_val(path));
(void) _texecve(wpath, EXECV_CAST argv, EXECV_CAST envp); (void) execve_os(wpath, EXECV_CAST argv, EXECV_CAST envp);
caml_stat_free(wpath); caml_stat_free(wpath);
cstringvect_free(argv); cstringvect_free(argv);
cstringvect_free(envp); cstringvect_free(envp);

View File

@ -21,12 +21,12 @@
CAMLprim value unix_execvp(value path, value args) CAMLprim value unix_execvp(value path, value args)
{ {
charnat ** argv; char_os ** argv;
charnat * wpath; char_os * wpath;
caml_unix_check_path(path, "execvp"); caml_unix_check_path(path, "execvp");
argv = cstringvect(args, "execvp"); argv = cstringvect(args, "execvp");
wpath = caml_stat_strdup_to_utf16(String_val(path)); wpath = caml_stat_strdup_to_os(String_val(path));
(void) _texecvp((const charnat *)wpath, EXECV_CAST argv); (void) execvp_os((const char_os *)wpath, EXECV_CAST argv);
caml_stat_free(wpath); caml_stat_free(wpath);
cstringvect_free(argv); cstringvect_free(argv);
uerror("execvp", path); uerror("execvp", path);
@ -36,16 +36,16 @@ CAMLprim value unix_execvp(value path, value args)
CAMLprim value unix_execvpe(value path, value args, value env) CAMLprim value unix_execvpe(value path, value args, value env)
{ {
charnat * exefile, * wpath; char_os * exefile, * wpath;
charnat ** argv; char_os ** argv;
charnat ** envp; char_os ** envp;
caml_unix_check_path(path, "execvpe"); caml_unix_check_path(path, "execvpe");
wpath = caml_stat_strdup_to_utf16(String_val(path)); wpath = caml_stat_strdup_to_os(String_val(path));
exefile = caml_search_exe_in_path(wpath); exefile = caml_search_exe_in_path(wpath);
caml_stat_free(wpath); caml_stat_free(wpath);
argv = cstringvect(args, "execvpe"); argv = cstringvect(args, "execvpe");
envp = cstringvect(env, "execvpe"); envp = cstringvect(env, "execvpe");
(void) _texecve((const charnat *)exefile, EXECV_CAST argv, EXECV_CAST envp); (void) execve_os((const char_os *)exefile, EXECV_CAST argv, EXECV_CAST envp);
caml_stat_free(exefile); caml_stat_free(exefile);
cstringvect_free(argv); cstringvect_free(argv);
cstringvect_free(envp); cstringvect_free(envp);

View File

@ -37,11 +37,11 @@
CAMLprim value unix_getcwd(value unit) CAMLprim value unix_getcwd(value unit)
{ {
charnat buff[PATH_MAX]; char_os buff[PATH_MAX];
charnat * ret; char_os * ret;
ret = _tgetcwd(buff, sizeof(buff)/sizeof(*buff)); ret = getcwd_os(buff, sizeof(buff)/sizeof(*buff));
if (ret == 0) uerror("getcwd", Nothing); if (ret == 0) uerror("getcwd", Nothing);
return caml_copy_string_of_utf16(buff); return caml_copy_string_of_os(buff);
} }
#else #else

View File

@ -31,15 +31,15 @@
CAMLprim value unix_putenv(value name, value val) CAMLprim value unix_putenv(value name, value val)
{ {
char * s; char * s;
charnat * p; char_os * p;
int ret; int ret;
if (! (caml_string_is_c_safe(name) && caml_string_is_c_safe(val))) if (! (caml_string_is_c_safe(name) && caml_string_is_c_safe(val)))
unix_error(EINVAL, "putenv", name); unix_error(EINVAL, "putenv", name);
s = caml_stat_strconcat(3, name, "=", val); s = caml_stat_strconcat(3, name, "=", val);
p = caml_stat_strdup_to_utf16(s); p = caml_stat_strdup_to_os(s);
caml_stat_free(s); caml_stat_free(s);
ret = _tputenv(p); ret = putenv_os(p);
if (ret == -1) { if (ret == -1) {
caml_stat_free(p); caml_stat_free(p);
uerror("putenv", name); uerror("putenv", name);

View File

@ -24,12 +24,12 @@
CAMLprim value unix_rmdir(value path) CAMLprim value unix_rmdir(value path)
{ {
CAMLparam1(path); CAMLparam1(path);
charnat * p; char_os * p;
int ret; int ret;
caml_unix_check_path(path, "rmdir"); caml_unix_check_path(path, "rmdir");
p = caml_stat_strdup_to_utf16(String_val(path)); p = caml_stat_strdup_to_os(String_val(path));
caml_enter_blocking_section(); caml_enter_blocking_section();
ret = _trmdir(p); ret = rmdir_os(p);
caml_leave_blocking_section(); caml_leave_blocking_section();
caml_stat_free(p); caml_stat_free(p);
if (ret == -1) uerror("rmdir", path); if (ret == -1) uerror("rmdir", path);

View File

@ -24,12 +24,12 @@
CAMLprim value unix_unlink(value path) CAMLprim value unix_unlink(value path)
{ {
CAMLparam1(path); CAMLparam1(path);
charnat * p; char_os * p;
int ret; int ret;
caml_unix_check_path(path, "unlink"); caml_unix_check_path(path, "unlink");
p = caml_stat_strdup_to_utf16(String_val(path)); p = caml_stat_strdup_to_os(String_val(path));
caml_enter_blocking_section(); caml_enter_blocking_section();
ret = _tunlink(p); ret = unlink_os(p);
caml_leave_blocking_section(); caml_leave_blocking_section();
caml_stat_free(p); caml_stat_free(p);
if (ret == -1) uerror("unlink", path); if (ret == -1) uerror("unlink", path);

View File

@ -72,7 +72,7 @@ CAMLprim value unix_utimes(value path, value atime, value mtime)
#else #else
struct utimbuf times, * t; struct utimbuf times, * t;
#endif #endif
charnat * p; char_os * p;
int ret; int ret;
double at, mt; double at, mt;
caml_unix_check_path(path, "utimes"); caml_unix_check_path(path, "utimes");
@ -85,9 +85,9 @@ CAMLprim value unix_utimes(value path, value atime, value mtime)
times.modtime = mt; times.modtime = mt;
t = &times; t = &times;
} }
p = caml_stat_strdup_to_utf16(String_val(path)); p = caml_stat_strdup_to_os(String_val(path));
caml_enter_blocking_section(); caml_enter_blocking_section();
ret = _tutime(p, t); ret = utime_os(p, t);
caml_leave_blocking_section(); caml_leave_blocking_section();
caml_stat_free(p); caml_stat_free(p);
if (ret == -1) uerror("utimes", path); if (ret == -1) uerror("utimes", path);

View File

@ -128,6 +128,6 @@ typedef struct _REPARSE_DATA_BUFFER
} REPARSE_DATA_BUFFER, *PREPARSE_DATA_BUFFER; } REPARSE_DATA_BUFFER, *PREPARSE_DATA_BUFFER;
#endif #endif
#define EXECV_CAST (const charnat * const *) #define EXECV_CAST (const char_os * const *)
#endif /* CAML_UNIXSUPPORT_H */ #endif /* CAML_UNIXSUPPORT_H */