summaryrefslogtreecommitdiffstats
path: root/otherlibs/win32unix
diff options
context:
space:
mode:
Diffstat (limited to 'otherlibs/win32unix')
-rw-r--r--otherlibs/win32unix/.depend10
-rw-r--r--otherlibs/win32unix/accept.c5
-rw-r--r--otherlibs/win32unix/bind.c2
-rw-r--r--otherlibs/win32unix/channels.c4
-rw-r--r--otherlibs/win32unix/dup.c1
-rw-r--r--otherlibs/win32unix/errmsg.c5
-rw-r--r--otherlibs/win32unix/gettimeofday.c2
-rw-r--r--otherlibs/win32unix/link.c14
-rw-r--r--otherlibs/win32unix/lseek.c4
-rw-r--r--otherlibs/win32unix/rename.c6
-rw-r--r--otherlibs/win32unix/select.c99
-rw-r--r--otherlibs/win32unix/socket.c4
-rw-r--r--otherlibs/win32unix/system.c3
-rw-r--r--otherlibs/win32unix/unix.ml12
-rw-r--r--otherlibs/win32unix/windbug.h3
-rw-r--r--otherlibs/win32unix/windir.c1
-rw-r--r--otherlibs/win32unix/winworker.c20
-rw-r--r--otherlibs/win32unix/winworker.h12
18 files changed, 100 insertions, 107 deletions
diff --git a/otherlibs/win32unix/.depend b/otherlibs/win32unix/.depend
index 6e1130b18..a608240cd 100644
--- a/otherlibs/win32unix/.depend
+++ b/otherlibs/win32unix/.depend
@@ -1,5 +1,5 @@
-unix.cmo: unix.cmi
-unix.cmx: unix.cmi
-unixLabels.cmo: unix.cmi unixLabels.cmi
-unixLabels.cmx: unix.cmx unixLabels.cmi
-unixLabels.cmi: unix.cmi
+unix.cmo: unix.cmi
+unix.cmx: unix.cmi
+unixLabels.cmo: unix.cmi unixLabels.cmi
+unixLabels.cmx: unix.cmx unixLabels.cmi
+unixLabels.cmi: unix.cmi
diff --git a/otherlibs/win32unix/accept.c b/otherlibs/win32unix/accept.c
index 05fd731e5..1d54b89b3 100644
--- a/otherlibs/win32unix/accept.c
+++ b/otherlibs/win32unix/accept.c
@@ -37,7 +37,7 @@ CAMLprim value unix_accept(sock)
if (retcode == 0) {
/* Set sockets to synchronous mode */
newvalue = SO_SYNCHRONOUS_NONALERT;
- setsockopt(INVALID_SOCKET, SOL_SOCKET, SO_OPENTYPE,
+ setsockopt(INVALID_SOCKET, SOL_SOCKET, SO_OPENTYPE,
(char *) &newvalue, sizeof(newvalue));
}
addr_len = sizeof(sock_addr);
@@ -47,7 +47,7 @@ CAMLprim value unix_accept(sock)
leave_blocking_section();
if (retcode == 0) {
/* Restore initial mode */
- setsockopt(INVALID_SOCKET, SOL_SOCKET, SO_OPENTYPE,
+ setsockopt(INVALID_SOCKET, SOL_SOCKET, SO_OPENTYPE,
(char *) &oldvalue, oldvaluelen);
}
if (snew == INVALID_SOCKET) {
@@ -63,4 +63,3 @@ CAMLprim value unix_accept(sock)
End_roots();
return res;
}
-
diff --git a/otherlibs/win32unix/bind.c b/otherlibs/win32unix/bind.c
index 0a17c8d51..fca969489 100644
--- a/otherlibs/win32unix/bind.c
+++ b/otherlibs/win32unix/bind.c
@@ -16,7 +16,7 @@
#include <mlvalues.h>
#include "unixsupport.h"
#include "socketaddr.h"
-
+
CAMLprim value unix_bind(socket, address)
value socket, address;
{
diff --git a/otherlibs/win32unix/channels.c b/otherlibs/win32unix/channels.c
index 6e6b10139..1c2cd2734 100644
--- a/otherlibs/win32unix/channels.c
+++ b/otherlibs/win32unix/channels.c
@@ -44,7 +44,7 @@ CAMLprim value win_inchannel_of_filedescr(value handle)
if (Descr_kind_val(handle) == KIND_SOCKET)
chan->flags |= CHANNEL_FLAG_FROM_SOCKET;
vchan = caml_alloc_channel(chan);
- CAMLreturn(vchan);
+ CAMLreturn(vchan);
}
CAMLprim value win_outchannel_of_filedescr(value handle)
@@ -58,7 +58,7 @@ CAMLprim value win_outchannel_of_filedescr(value handle)
if (Descr_kind_val(handle) == KIND_SOCKET)
chan->flags |= CHANNEL_FLAG_FROM_SOCKET;
vchan = caml_alloc_channel(chan);
- CAMLreturn(vchan);
+ CAMLreturn(vchan);
}
CAMLprim value win_filedescr_of_channel(value vchan)
diff --git a/otherlibs/win32unix/dup.c b/otherlibs/win32unix/dup.c
index de2ea7449..2668e75bf 100644
--- a/otherlibs/win32unix/dup.c
+++ b/otherlibs/win32unix/dup.c
@@ -31,4 +31,3 @@ CAMLprim value unix_dup(value fd)
Descr_kind_val(newfd) = kind;
return newfd;
}
-
diff --git a/otherlibs/win32unix/errmsg.c b/otherlibs/win32unix/errmsg.c
index 20a8c8d58..9ce9dddb2 100644
--- a/otherlibs/win32unix/errmsg.c
+++ b/otherlibs/win32unix/errmsg.c
@@ -26,7 +26,7 @@ CAMLprim value unix_error_message(value err)
{
int errnum;
char buffer[512];
-
+
errnum = Is_block(err) ? Int_val(Field(err, 0)) : error_table[Int_val(err)];
if (errnum > 0)
return copy_string(strerror(errnum));
@@ -38,7 +38,6 @@ CAMLprim value unix_error_message(value err)
sizeof(buffer),
NULL))
return copy_string(buffer);
- sprintf(buffer, "unknown error #%d", errnum);
+ sprintf(buffer, "unknown error #%d", errnum);
return copy_string(buffer);
}
-
diff --git a/otherlibs/win32unix/gettimeofday.c b/otherlibs/win32unix/gettimeofday.c
index 0c581321a..f1313f061 100644
--- a/otherlibs/win32unix/gettimeofday.c
+++ b/otherlibs/win32unix/gettimeofday.c
@@ -31,6 +31,6 @@ CAMLprim value unix_gettimeofday(value unit)
return copy_double((double) initial_time);
} else {
return copy_double((double) initial_time +
- (double) (tickcount - initial_tickcount) * 1e-3);
+ (double) (tickcount - initial_tickcount) * 1e-3);
}
}
diff --git a/otherlibs/win32unix/link.c b/otherlibs/win32unix/link.c
index 26202ed98..892143423 100644
--- a/otherlibs/win32unix/link.c
+++ b/otherlibs/win32unix/link.c
@@ -17,18 +17,18 @@
#include <mlvalues.h>
#include <fail.h>
#include "unixsupport.h"
-
-typedef
+
+typedef
BOOL (WINAPI *tCreateHardLink)(
LPCTSTR lpFileName,
LPCTSTR lpExistingFileName,
- LPSECURITY_ATTRIBUTES lpSecurityAttributes
+ LPSECURITY_ATTRIBUTES lpSecurityAttributes
);
-
+
CAMLprim value unix_link(value path1, value path2)
-{
+{
HMODULE hModKernel32;
- tCreateHardLink pCreateHardLink;
+ tCreateHardLink pCreateHardLink;
hModKernel32 = GetModuleHandle("KERNEL32.DLL");
pCreateHardLink =
(tCreateHardLink) GetProcAddress(hModKernel32, "CreateHardLinkA");
@@ -39,4 +39,4 @@ CAMLprim value unix_link(value path1, value path2)
uerror("link", path2);
}
return Val_unit;
-}
+}
diff --git a/otherlibs/win32unix/lseek.c b/otherlibs/win32unix/lseek.c
index 2df3a86dc..9619fcc92 100644
--- a/otherlibs/win32unix/lseek.c
+++ b/otherlibs/win32unix/lseek.c
@@ -52,7 +52,7 @@ CAMLprim value unix_lseek(value fd, value ofs, value cmd)
__int64 ret;
ret = caml_set_file_pointer(Handle_val(fd), Long_val(ofs),
- seek_command_table[Int_val(cmd)]);
+ seek_command_table[Int_val(cmd)]);
if (ret > Max_long) {
win32_maperr(ERROR_ARITHMETIC_OVERFLOW);
uerror("lseek", Nothing);
@@ -65,6 +65,6 @@ CAMLprim value unix_lseek_64(value fd, value ofs, value cmd)
__int64 ret;
ret = caml_set_file_pointer(Handle_val(fd), Int64_val(ofs),
- seek_command_table[Int_val(cmd)]);
+ seek_command_table[Int_val(cmd)]);
return copy_int64(ret);
}
diff --git a/otherlibs/win32unix/rename.c b/otherlibs/win32unix/rename.c
index 3bfdf4770..9ab43fca8 100644
--- a/otherlibs/win32unix/rename.c
+++ b/otherlibs/win32unix/rename.c
@@ -31,13 +31,13 @@ CAMLprim value unix_rename(value path1, value path2)
}
if (supports_MoveFileEx > 0)
ok = MoveFileEx(String_val(path1), String_val(path2),
- MOVEFILE_REPLACE_EXISTING | MOVEFILE_WRITE_THROUGH |
- MOVEFILE_COPY_ALLOWED);
+ MOVEFILE_REPLACE_EXISTING | MOVEFILE_WRITE_THROUGH |
+ MOVEFILE_COPY_ALLOWED);
else
ok = MoveFile(String_val(path1), String_val(path2));
if (! ok) {
win32_maperr(GetLastError());
uerror("rename", path1);
- }
+ }
return Val_unit;
}
diff --git a/otherlibs/win32unix/select.c b/otherlibs/win32unix/select.c
index 0c7760bb7..efe3a32e8 100644
--- a/otherlibs/win32unix/select.c
+++ b/otherlibs/win32unix/select.c
@@ -29,7 +29,7 @@
* It takes the following parameters into account:
* - limitation on number of objects is mostly due to limitation
* a WaitForMultipleObjects
- * - there is always an event "hStop" to watch
+ * - there is always an event "hStop" to watch
*
* This lead to pick the following value as the biggest possible
* value
@@ -115,7 +115,7 @@ typedef enum _SELECTHANDLETYPE {
typedef enum _SELECTMODE {
SELECT_MODE_NONE = 0,
SELECT_MODE_READ,
- SELECT_MODE_WRITE,
+ SELECT_MODE_WRITE,
SELECT_MODE_EXCEPT,
} SELECTMODE;
@@ -188,13 +188,13 @@ LPSELECTDATA select_data_new (LPSELECTDATA lpSelectData, SELECTTYPE EType)
/* Allocate the data structure */
LPSELECTDATA res;
DWORD i;
-
+
if (!HeapLock(GetProcessHeap()))
{
win32_maperr(GetLastError());
uerror("select", Nothing);
}
- res = (LPSELECTDATA)HeapAlloc(GetProcessHeap(), 0, sizeof(SELECTDATA));
+ res = (LPSELECTDATA)HeapAlloc(GetProcessHeap(), 0, sizeof(SELECTDATA));
HeapUnlock(GetProcessHeap());
/* Init common data */
@@ -202,10 +202,10 @@ LPSELECTDATA select_data_new (LPSELECTDATA lpSelectData, SELECTTYPE EType)
list_next_set((LPLIST)res, (LPLIST)lpSelectData);
res->EType = EType;
res->nResultsCount = 0;
-
+
/* Data following are dedicated to APC like call, they
- will be initialized if required. For now they are set to
+ will be initialized if required. For now they are set to
invalid values.
*/
res->funcWorker = NULL;
@@ -269,7 +269,7 @@ DWORD select_data_result_add (LPSELECTDATA lpSelectData, SELECTMODE EMode, LPVOI
DWORD select_data_query_add (LPSELECTDATA lpSelectData, SELECTMODE EMode, HANDLE hFileDescr, LPVOID lpOrig)
{
DWORD res;
- DWORD i;
+ DWORD i;
res = 0;
if (lpSelectData->nQueriesCount < MAXIMUM_SELECT_OBJECTS)
@@ -286,15 +286,16 @@ DWORD select_data_query_add (LPSELECTDATA lpSelectData, SELECTMODE EMode, HANDLE
}
/* Search for a job that has available query slots and that match provided type.
- * If none is found, create a new one. Return the corresponding SELECTDATA, and
+ * If none is found, create a new one. Return the corresponding SELECTDATA, and
* update provided SELECTDATA head, if required.
*/
-LPSELECTDATA select_data_job_search (LPSELECTDATA *lppSelectData, SELECTTYPE EType)
+LPSELECTDATA select_data_job_search (LPSELECTDATA *lppSelectData,
+ SELECTTYPE EType)
{
LPSELECTDATA res;
-
+
res = NULL;
-
+
/* Search for job */
#ifdef DBUG
dbug_print("Searching an available job for type %d", EType);
@@ -303,7 +304,7 @@ LPSELECTDATA select_data_job_search (LPSELECTDATA *lppSelectData, SELECTTYPE ETy
while (
res != NULL
&& !(
- res->EType == EType
+ res->EType == EType
&& res->nQueriesCount < MAXIMUM_SELECT_OBJECTS
)
)
@@ -336,7 +337,7 @@ void read_console_poll(HANDLE hStop, void *_data)
DWORD n;
LPSELECTDATA lpSelectData;
LPSELECTQUERY lpQuery;
-
+
#ifdef DBUG
dbug_print("Waiting for data on console");
#endif
@@ -350,7 +351,7 @@ void read_console_poll(HANDLE hStop, void *_data)
events[0] = hStop;
events[1] = lpQuery->hFileDescr;
while (lpSelectData->EState == SELECT_STATE_NONE)
- {
+ {
waitRes = WaitForMultipleObjects(2, events, FALSE, INFINITE);
if (waitRes == WAIT_OBJECT_0 || check_error(lpSelectData, waitRes == WAIT_FAILED))
{
@@ -371,7 +372,7 @@ void read_console_poll(HANDLE hStop, void *_data)
lpSelectData->EState = SELECT_STATE_SIGNALED;
break;
}
- else
+ else
{
/* discard everything else and try again */
if (check_error(lpSelectData, ReadConsoleInput(lpQuery->hFileDescr, &record, 1, &n) == 0))
@@ -421,13 +422,13 @@ void read_pipe_poll (HANDLE hStop, void *_data)
{
iterQuery = &(lpSelectData->aQueries[i]);
if (check_error(
- lpSelectData,
+ lpSelectData,
PeekNamedPipe(
- iterQuery->hFileDescr,
- NULL,
- 0,
- NULL,
- &n,
+ iterQuery->hFileDescr,
+ NULL,
+ 0,
+ NULL,
+ &n,
NULL) == 0))
{
break;
@@ -441,7 +442,7 @@ void read_pipe_poll (HANDLE hStop, void *_data)
};
/* Alas, nothing except polling seems to work for pipes.
- Check the state & stop_worker_event every 10 ms
+ Check the state & stop_worker_event every 10 ms
*/
if (lpSelectData->EState == SELECT_STATE_NONE)
{
@@ -462,17 +463,17 @@ LPSELECTDATA read_pipe_poll_add (LPSELECTDATA lpSelectData, SELECTMODE EMode, HA
{
LPSELECTDATA res;
LPSELECTDATA hd;
-
+
hd = lpSelectData;
/* Polling pipe is a non blocking operation by default. This means that each
- worker can handle many pipe. We begin to try to find a worker that is
+ worker can handle many pipe. We begin to try to find a worker that is
polling pipe, but for which there is under the limit of pipe per worker.
*/
#ifdef DBUG
dbug_print("Searching an available worker handling pipe");
#endif
res = select_data_job_search(&hd, SELECT_TYPE_PIPE_READ);
-
+
/* Add a new pipe to poll */
res->funcWorker = read_pipe_poll;
select_data_query_add(res, EMode, hFileDescr, lpOrig);
@@ -516,22 +517,22 @@ void socket_poll (HANDLE hStop, void *_data)
}
check_error(lpSelectData,
WSAEventSelect(
- (SOCKET)(iterQuery->hFileDescr),
- aEvents[nEvents],
+ (SOCKET)(iterQuery->hFileDescr),
+ aEvents[nEvents],
maskEvents) == SOCKET_ERROR);
}
-
+
/* Add stop event */
aEvents[nEvents] = hStop;
nEvents++;
if (lpSelectData->nError == 0)
{
- check_error(lpSelectData,
+ check_error(lpSelectData,
WaitForMultipleObjects(
- nEvents,
- aEvents,
- FALSE,
+ nEvents,
+ aEvents,
+ FALSE,
INFINITE) == WAIT_FAILED);
};
@@ -568,7 +569,7 @@ LPSELECTDATA socket_poll_add (LPSELECTDATA lpSelectData, SELECTMODE EMode, HANDL
{
LPSELECTDATA res;
LPSELECTDATA hd;
-
+
hd = lpSelectData;
/* Polling socket can be done mulitple handle at the same time. You just
need one worker to use it. Try to find if there is already a worker
@@ -578,7 +579,7 @@ LPSELECTDATA socket_poll_add (LPSELECTDATA lpSelectData, SELECTMODE EMode, HANDL
dbug_print("Scanning list of worker to find one that already handle socket");
#endif
res = select_data_job_search(&hd, SELECT_TYPE_SOCKET);
-
+
/* Add a new socket to poll */
res->funcWorker = socket_poll;
#ifdef DBUG
@@ -601,11 +602,11 @@ LPSELECTDATA static_poll_add (LPSELECTDATA lpSelectData, SELECTMODE EMode, HANDL
{
LPSELECTDATA res;
LPSELECTDATA hd;
-
+
/* Look for an already initialized static element */
hd = lpSelectData;
res = select_data_job_search(&hd, SELECT_TYPE_STATIC);
-
+
/* Add a new query/result */
select_data_query_add(res, EMode, hFileDescr, lpOrig);
select_data_result_add(res, EMode, lpOrig);
@@ -636,7 +637,7 @@ static SELECTHANDLETYPE get_handle_type(value fd)
{
switch(GetFileType(Handle_val(fd)))
{
- case FILE_TYPE_DISK:
+ case FILE_TYPE_DISK:
res = SELECT_HANDLE_DISK;
break;
@@ -685,8 +686,8 @@ LPSELECTDATA select_data_dispatch (LPSELECTDATA lpSelectData, SELECTMODE EMode,
#ifdef DBUG
dbug_print("Waiting for %d on handle %x", EMode, hFileDescr);
#endif
-
- /* There is only 2 way to have except mode: transmission of OOB data through
+
+ /* There is only 2 way to have except mode: transmission of OOB data through
a socket TCP/IP and through a strange interaction with a TTY.
With windows, we only consider the TCP/IP except condition
*/
@@ -795,12 +796,12 @@ static DWORD caml_list_length (value lst)
#define MAX(a, b) ((a) > (b) ? (a) : (b))
CAMLprim value unix_select(value readfds, value writefds, value exceptfds, value timeout)
-{
+{
/* Event associated to handle */
DWORD nEventsCount;
DWORD nEventsMax;
HANDLE *lpEventsDone;
-
+
/* Data for all handles */
LPSELECTDATA lpSelectData;
LPSELECTDATA iterSelectData;
@@ -861,8 +862,8 @@ CAMLprim value unix_select(value readfds, value writefds, value exceptfds, value
uerror("select", Nothing);
}
hdsData = (HANDLE *)HeapAlloc(
- GetProcessHeap(),
- 0,
+ GetProcessHeap(),
+ 0,
sizeof(HANDLE) * hdsMax);
HeapUnlock(GetProcessHeap());
@@ -973,12 +974,12 @@ CAMLprim value unix_select(value readfds, value writefds, value exceptfds, value
/* Execute APC */
if (iterSelectData->funcWorker != NULL)
{
- iterSelectData->lpWorker =
+ iterSelectData->lpWorker =
worker_job_submit(
- iterSelectData->funcWorker,
+ iterSelectData->funcWorker,
(void *)iterSelectData);
#ifdef DBUG
- dbug_print("Job submitted to worker %x", iterSelectData->lpWorker);
+ dbug_print("Job submitted to worker %x", iterSelectData->lpWorker);
#endif
lpEventsDone[nEventsCount] = worker_job_event_done(iterSelectData->lpWorker);
nEventsCount++;
@@ -1034,7 +1035,7 @@ CAMLprim value unix_select(value readfds, value writefds, value exceptfds, value
};
iterSelectData = LIST_NEXT(LPSELECTDATA, iterSelectData);
};
-
+
#ifdef DBUG
dbug_print("Waiting for every select worker to be done");
#endif
@@ -1067,7 +1068,7 @@ CAMLprim value unix_select(value readfds, value writefds, value exceptfds, value
#ifdef DBUG
dbug_print("Building result");
#endif
- read_list = Val_unit;
+ read_list = Val_unit;
write_list = Val_unit;
except_list = Val_unit;
@@ -1116,7 +1117,7 @@ CAMLprim value unix_select(value readfds, value writefds, value exceptfds, value
select_data_free(lpSelectData);
}
lpSelectData = NULL;
-
+
/* Free allocated events/handle set array */
#ifdef DBUG
dbug_print("Free local allocated resources");
diff --git a/otherlibs/win32unix/socket.c b/otherlibs/win32unix/socket.c
index 079473f81..3cd55ec29 100644
--- a/otherlibs/win32unix/socket.c
+++ b/otherlibs/win32unix/socket.c
@@ -36,7 +36,7 @@ CAMLprim value unix_socket(domain, type, proto)
if (retcode == 0) {
/* Set sockets to synchronous mode */
newvalue = SO_SYNCHRONOUS_NONALERT;
- setsockopt(INVALID_SOCKET, SOL_SOCKET, SO_OPENTYPE,
+ setsockopt(INVALID_SOCKET, SOL_SOCKET, SO_OPENTYPE,
(char *) &newvalue, sizeof(newvalue));
}
s = socket(socket_domain_table[Int_val(domain)],
@@ -44,7 +44,7 @@ CAMLprim value unix_socket(domain, type, proto)
Int_val(proto));
if (retcode == 0) {
/* Restore initial mode */
- setsockopt(INVALID_SOCKET, SOL_SOCKET, SO_OPENTYPE,
+ setsockopt(INVALID_SOCKET, SOL_SOCKET, SO_OPENTYPE,
(char *) &oldvalue, oldvaluelen);
}
if (s == INVALID_SOCKET) {
diff --git a/otherlibs/win32unix/system.c b/otherlibs/win32unix/system.c
index 9cf3e89cc..51dc9bfb7 100644
--- a/otherlibs/win32unix/system.c
+++ b/otherlibs/win32unix/system.c
@@ -42,6 +42,3 @@ CAMLprim value win_system(cmd)
Field(st, 0) = Val_int(ret);
return st;
}
-
-
-
diff --git a/otherlibs/win32unix/unix.ml b/otherlibs/win32unix/unix.ml
index f8d663170..c8396d7fd 100644
--- a/otherlibs/win32unix/unix.ml
+++ b/otherlibs/win32unix/unix.ml
@@ -145,7 +145,7 @@ external waitpid : wait_flag list -> int -> int * process_status
external getpid : unit -> int = "unix_getpid"
let fork () = invalid_arg "Unix.fork not implemented"
-let wait () = invalid_arg "Unix.wait not implemented"
+let wait () = invalid_arg "Unix.wait not implemented"
let getppid () = invalid_arg "Unix.getppid not implemented"
let nice prio = invalid_arg "Unix.nice not implemented"
@@ -515,7 +515,7 @@ external accept : file_descr -> file_descr * sockaddr = "unix_accept"
external bind : file_descr -> sockaddr -> unit = "unix_bind"
external connect : file_descr -> sockaddr -> unit = "unix_connect"
external listen : file_descr -> int -> unit = "unix_listen"
-external shutdown : file_descr -> shutdown_command -> unit = "unix_shutdown"
+external shutdown : file_descr -> shutdown_command -> unit = "unix_shutdown"
external getsockname : file_descr -> sockaddr = "unix_getsockname"
external getpeername : file_descr -> sockaddr = "unix_getpeername"
@@ -592,7 +592,7 @@ end = struct
let optint = 2
let float = 3
let error = 4
- external get: ('opt, 'v) t -> file_descr -> 'opt -> 'v
+ external get: ('opt, 'v) t -> file_descr -> 'opt -> 'v
= "unix_getsockopt"
external set: ('opt, 'v) t -> file_descr -> 'opt -> 'v -> unit
= "unix_setsockopt"
@@ -678,7 +678,7 @@ let getaddrinfo node service opts =
with Failure _ ->
try
[ty, (getservbyname service kind).s_port]
- with Not_found -> []
+ with Not_found -> []
in
let ports =
match !opt_socktype with
@@ -709,7 +709,7 @@ let getaddrinfo node service opts =
[] in
(* Cross-product of addresses and ports *)
List.flatten
- (List.map
+ (List.map
(fun (ty, port) ->
List.map
(fun (addr, name) ->
@@ -772,7 +772,7 @@ let create_process prog args fd1 fd2 fd3 =
let create_process_env prog args env fd1 fd2 fd3 =
win_create_process prog (make_cmdline args)
(Some(String.concat "\000" (Array.to_list env) ^ "\000"))
- fd1 fd2 fd3
+ fd1 fd2 fd3
external system: string -> process_status = "win_system"
diff --git a/otherlibs/win32unix/windbug.h b/otherlibs/win32unix/windbug.h
index a0085a90f..232bb1989 100644
--- a/otherlibs/win32unix/windbug.h
+++ b/otherlibs/win32unix/windbug.h
@@ -43,8 +43,7 @@ int dbug_test (void);
#define DBUG_CLEANUP dbug_cleanup()
#else
-#define DBUG_PRINT(fmt, ...)
+#define DBUG_PRINT(fmt, ...)
#define DBUG_INIT
#define DBUG_CLEANUP
#endif
-
diff --git a/otherlibs/win32unix/windir.c b/otherlibs/win32unix/windir.c
index 0a681e76c..8b96589ec 100644
--- a/otherlibs/win32unix/windir.c
+++ b/otherlibs/win32unix/windir.c
@@ -77,4 +77,3 @@ CAMLprim value win_findclose(valh)
}
return Val_unit;
}
-
diff --git a/otherlibs/win32unix/winworker.c b/otherlibs/win32unix/winworker.c
index 7358b203c..aa83684b2 100644
--- a/otherlibs/win32unix/winworker.c
+++ b/otherlibs/win32unix/winworker.c
@@ -53,17 +53,17 @@ DWORD WINAPI worker_wait (LPVOID _data)
{
BOOL bExit;
LPWORKER lpWorker;
-
+
lpWorker = (LPWORKER )_data;
bExit = FALSE;
DBUG_PRINT("Worker %x starting", lpWorker);
while (
- !bExit
+ !bExit
&& SignalObjectAndWait(
- lpWorker->hWorkerReady,
+ lpWorker->hWorkerReady,
lpWorker->hCommandReady,
- INFINITE,
+ INFINITE,
TRUE) == WAIT_OBJECT_0)
{
DBUG_PRINT("Worker %x running", lpWorker);
@@ -111,11 +111,11 @@ LPWORKER worker_new (void)
lpWorker->hCommandReady = CreateEvent(NULL, FALSE, FALSE, NULL);
lpWorker->ECommand = WORKER_CMD_NONE;
lpWorker->hThread = CreateThread(
- NULL,
- THREAD_WORKERS_MEM,
- worker_wait,
- (LPVOID)lpWorker,
- 0,
+ NULL,
+ THREAD_WORKERS_MEM,
+ worker_wait,
+ (LPVOID)lpWorker,
+ 0,
NULL);
return lpWorker;
@@ -287,7 +287,7 @@ void worker_cleanup(void)
worker_free(lpWorker);
};
ReleaseMutex(hWorkersMutex);
-
+
/* Destroy associated mutex */
CloseHandle(hWorkersMutex);
hWorkersMutex = INVALID_HANDLE_VALUE;
diff --git a/otherlibs/win32unix/winworker.h b/otherlibs/win32unix/winworker.h
index d0b829002..06450a4ec 100644
--- a/otherlibs/win32unix/winworker.h
+++ b/otherlibs/win32unix/winworker.h
@@ -18,12 +18,12 @@
#define _WIN32_WINNT 0x0400
#include <windows.h>
-/* Pool of worker threads.
+/* Pool of worker threads.
*
* These functions help to manage a pool of worker thread and submit task to
* the pool. It helps to reduce the number of thread creation.
*
- * Each worker are started in alertable wait state and jobs are submitted as
+ * Each worker are started in alertable wait state and jobs are submitted as
* APC (asynchronous procedure call).
*/
@@ -42,16 +42,16 @@ typedef WORKER *LPWORKER;
*/
typedef void (*WORKERFUNC) (HANDLE, void *);
-/* Initialize global data structure for worker
+/* Initialize global data structure for worker
*/
void worker_init (void);
-/* Free global data structure for worker
+/* Free global data structure for worker
*/
void worker_cleanup (void);
/* Submit a job to worker. Use returned data to synchronize with the procedure
- * submitted.
+ * submitted.
*/
LPWORKER worker_job_submit (WORKERFUNC f, void *data);
@@ -63,7 +63,7 @@ HANDLE worker_job_event_done (LPWORKER);
*/
void worker_job_stop (LPWORKER);
-/* End a job submitted to worker.
+/* End a job submitted to worker.
*/
void worker_job_finish (LPWORKER);