Skip to content

Commit

Permalink
Rename renaming win_ primitives to unix_
Browse files Browse the repository at this point in the history
  • Loading branch information
dra27 committed May 25, 2022
1 parent de7cae3 commit 06a1b50
Show file tree
Hide file tree
Showing 5 changed files with 24 additions and 28 deletions.
2 changes: 1 addition & 1 deletion otherlibs/unix/channels_win32.c
Original file line number Diff line number Diff line change
Expand Up @@ -118,7 +118,7 @@ CAMLprim value unix_outchannel_of_filedescr(value handle)
CAMLreturn(vchan);
}

CAMLprim value win_filedescr_of_channel(value vchan)
CAMLprim value unix_filedescr_of_channel(value vchan)
{
CAMLparam1(vchan);
CAMLlocal1(fd);
Expand Down
12 changes: 6 additions & 6 deletions otherlibs/unix/createprocess.c
Original file line number Diff line number Diff line change
Expand Up @@ -99,8 +99,8 @@ static DWORD do_create_process_native(wchar_t * exefile, wchar_t * cmdline,
return err;
}

value win_create_process_native(value cmd, value cmdline, value env,
value fd1, value fd2, value fd3)
value unix_create_process_native(value cmd, value cmdline, value env,
value fd1, value fd2, value fd3)
{
wchar_t * exefile, * wcmdline, * wenv, * wcmd;
HANDLE hProcess;
Expand Down Expand Up @@ -146,10 +146,10 @@ value win_create_process_native(value cmd, value cmdline, value env,
return Val_long(hProcess);
}

CAMLprim value win_create_process(value * argv, int argn)
CAMLprim value unix_create_process(value * argv, int argn)
{
return win_create_process_native(argv[0], argv[1], argv[2],
argv[3], argv[4], argv[5]);
return unix_create_process_native(argv[0], argv[1], argv[2],
argv[3], argv[4], argv[5]);
}

static int has_console(void)
Expand All @@ -167,7 +167,7 @@ static int has_console(void)
}
}

CAMLprim value win_terminate_process(value v_pid)
CAMLprim value unix_terminate_process(value v_pid)
{
return (Val_bool(TerminateProcess((HANDLE) Long_val(v_pid), 0)));
}
30 changes: 14 additions & 16 deletions otherlibs/unix/unix_win32.ml
Original file line number Diff line number Diff line change
Expand Up @@ -313,9 +313,9 @@ external in_channel_of_descr: file_descr -> in_channel
external out_channel_of_descr: file_descr -> out_channel
= "unix_outchannel_of_filedescr"
external descr_of_in_channel : in_channel -> file_descr
= "win_filedescr_of_channel"
= "unix_filedescr_of_channel"
external descr_of_out_channel : out_channel -> file_descr
= "win_filedescr_of_channel"
= "unix_filedescr_of_channel"

(* Seeking and truncating *)

Expand Down Expand Up @@ -465,8 +465,8 @@ type dir_entry =
type dir_handle =
{ dirname: string; mutable handle: int; mutable entry_read: dir_entry }

external findfirst : string -> string * int = "win_findfirst"
external findnext : int -> string= "win_findnext"
external findfirst : string -> string * int = "unix_findfirst"
external findnext : int -> string= "unix_findnext"

let opendir dirname =
try
Expand All @@ -481,12 +481,12 @@ let readdir d =
| Dir_read name -> d.entry_read <- Dir_toread; name
| Dir_toread -> findnext d.handle

external win_findclose : int -> unit = "win_findclose"
external findclose : int -> unit = "unix_findclose"

let closedir d =
match d.entry_read with
Dir_empty -> ()
| _ -> win_findclose d.handle
| _ -> findclose d.handle

let rewinddir d =
closedir d;
Expand Down Expand Up @@ -549,7 +549,7 @@ type lock_command =

external lockf : file_descr -> lock_command -> int -> unit = "unix_lockf"

external terminate_process: int -> bool = "win_terminate_process"
external terminate_process: int -> bool = "unix_terminate_process"

let kill pid signo =
if signo <> Sys.sigkill then
Expand Down Expand Up @@ -972,9 +972,9 @@ let getnameinfo addr opts =

(* High-level process management (system, popen) *)

external win_create_process : string -> string -> string option ->
external create_process_stub: string -> string -> string option ->
file_descr -> file_descr -> file_descr -> int
= "win_create_process" "win_create_process_native"
= "unix_create_process" "unix_create_process_native"

let make_cmdline args =
String.concat " " (List.map maybe_quote (Array.to_list args))
Expand All @@ -986,12 +986,12 @@ let make_process_env env =
String.concat "\000" (Array.to_list env) ^ "\000"

let create_process prog args fd1 fd2 fd3 =
win_create_process prog (make_cmdline args) None fd1 fd2 fd3
create_process_stub prog (make_cmdline args) None fd1 fd2 fd3

let create_process_env prog args env fd1 fd2 fd3 =
win_create_process prog (make_cmdline args)
(Some(make_process_env env))
fd1 fd2 fd3
create_process_stub prog (make_cmdline args)
(Some(make_process_env env))
fd1 fd2 fd3

external system: string -> process_status = "unix_system"

Expand All @@ -1004,9 +1004,7 @@ type popen_process =
let popen_processes = (Hashtbl.create 7 : (popen_process, int) Hashtbl.t)

let open_proc prog cmdline optenv proc input output error =
let pid =
win_create_process prog cmdline optenv
input output error in
let pid = create_process_stub prog cmdline optenv input output error in
Hashtbl.add popen_processes proc pid

let open_process_cmdline_in prog cmdline =
Expand Down
6 changes: 3 additions & 3 deletions otherlibs/unix/windir.c
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@
#include <caml/osdeps.h>
#include "unixsupport.h"

CAMLprim value win_findfirst(value name)
CAMLprim value unix_findfirst(value name)
{
CAMLparam0();
CAMLlocal2(valname, valh);
Expand Down Expand Up @@ -53,7 +53,7 @@ CAMLprim value win_findfirst(value name)
CAMLreturn(v);
}

CAMLprim value win_findnext(value valh)
CAMLprim value unix_findnext(value valh)
{
WIN32_FIND_DATAW fileinfo;
BOOL retcode;
Expand All @@ -71,7 +71,7 @@ CAMLprim value win_findnext(value valh)
return caml_copy_string_of_utf16(fileinfo.cFileName);
}

CAMLprim value win_findclose(value valh)
CAMLprim value unix_findclose(value valh)
{
if (! FindClose(Handle_val(valh))) {
caml_win32_maperr(GetLastError());
Expand Down
2 changes: 0 additions & 2 deletions tools/check-symbol-names
Original file line number Diff line number Diff line change
Expand Up @@ -28,8 +28,6 @@ $3 ~ /^[a-zU]$/ { next }
# ignore "main", which should be externally linked
$2 ~ /^_?main$/ { next }
$2 ~ /^_?wmain$/ { next }
# Ignore win_ in Unix library
$1 ~ /\/unix/ && $2 ~/^_?win_/ { next }
# uerror is too widely known!
$2 ~ /^_?uerror$/ { next }
# for x86 PIC mode
Expand Down

0 comments on commit 06a1b50

Please sign in to comment.