Skip to content

Commit

Permalink
MAJ portage Windows
Browse files Browse the repository at this point in the history
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@2052 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
  • Loading branch information
xavierleroy committed Aug 14, 1998
1 parent dc2e566 commit 059e11a
Show file tree
Hide file tree
Showing 8 changed files with 31 additions and 24 deletions.
12 changes: 7 additions & 5 deletions Makefile.nt
Expand Up @@ -29,8 +29,8 @@ TYPING=typing\ident.cmo typing\path.cmo \
typing\btype.cmo \
typing\subst.cmo typing\predef.cmo \
typing\datarepr.cmo typing\env.cmo \
typing\typedtree.cmo \
typing\ctype.cmo typing\printtyp.cmo \
typing\typedtree.cmo typing\ctype.cmo \
typing\printtyp.cmo typing\includeclass.cmo \
typing\mtype.cmo typing\includecore.cmo \
typing\includemod.cmo typing\parmatch.cmo \
typing\typetexp.cmo typing\typecore.cmo \
Expand Down Expand Up @@ -81,8 +81,8 @@ OPTOBJS=$(OPTUTILS) $(PARSING) $(TYPING) $(COMP) $(ASMCOMP) $(OPTDRIVER)

EXPUNGEOBJS=utils\misc.cmo utils\tbl.cmo \
utils\config.cmo utils\clflags.cmo \
typing\ident.cmo typing\types.cmo typing\btype.cmo typing\predef.cmo \
bytecomp\runtimedef.cmo bytecomp\symtable.cmo \
typing\ident.cmo typing\path.cmo typing\types.cmo typing\btype.cmo \
typing\predef.cmo bytecomp\runtimedef.cmo bytecomp\symtable.cmo \
toplevel\expunge.cmo

PERVASIVES=arg array callback char digest filename format gc hashtbl \
Expand All @@ -100,7 +100,7 @@ all: runtime ocamlc ocamllex ocamlyacc ocamltools library ocaml otherlibraries
world: coldstart all

# Set up the configuration files
configure:
configure: FORCE
cp config\m-nt.h config\m.h
cp config\s-nt.h config\s.h
cp config\Makefile.nt config\Makefile
Expand Down Expand Up @@ -512,3 +512,5 @@ depend: beforedepend
alldepend:: depend

!include .depend

FORCE:
3 changes: 3 additions & 0 deletions config/m-nt.h
Expand Up @@ -16,4 +16,7 @@
#undef ARCH_SIXTYFOUR
#undef ARCH_BIG_ENDIAN
#undef ARCH_ALIGN_DOUBLE
#define SIZEOF_INT 4
#define SIZEOF_LONG 4
#define SIZEOF_SHORT 2

2 changes: 1 addition & 1 deletion config/s-nt.h
Expand Up @@ -16,7 +16,7 @@
#define OCAML_OS_TYPE "Win32"

#define HAS_MEMMOVE
#define BSD_SIGNALS
#undef BSD_SIGNALS
#define HAS_STRERROR
#define HAS_SOCKETS
#define HAS_GETCWD
Expand Down
4 changes: 2 additions & 2 deletions otherlibs/dynlink/Makefile.nt
Expand Up @@ -7,8 +7,8 @@ INCLUDES=-I ..\..\utils -I ..\..\typing -I ..\..\bytecomp
COMPFLAGS=-I ..\..\stdlib $(INCLUDES)

OBJS=dynlink.cmo
COMPILEROBJS=misc.cmo config.cmo tbl.cmo clflags.cmo ident.cmo \
btype.cmo predef.cmo runtimedef.cmo symtable.cmo opcodes.cmo
COMPILEROBJS=misc.cmo config.cmo tbl.cmo clflags.cmo ident.cmo path.cmo \
types.cmo btype.cmo predef.cmo runtimedef.cmo symtable.cmo opcodes.cmo

all: dynlink.cma extract_crc

Expand Down
2 changes: 1 addition & 1 deletion otherlibs/systhreads/Tests/Makefile.nt
@@ -1,6 +1,6 @@
PROGS=test1.byt test2.byt test3.byt test4.byt test5.byt test6.byt \
test7.byt test8.byt test9.byt testA.byt sieve.byt \
testio.byt testsocket.byt testwait.byt testsignal.byt
testio.byt testsocket.byt testwait.byt testsignal.byt testsignal2.byt

!include ../../../config/Makefile.nt

Expand Down
10 changes: 6 additions & 4 deletions otherlibs/systhreads/win32.c
Expand Up @@ -14,6 +14,7 @@
/* Thread interface for Win32 threads */

#include <windows.h>
#include <signal.h>
#include "alloc.h"
#include "callback.h"
#include "fail.h"
Expand Down Expand Up @@ -586,21 +587,22 @@ static void caml_wait_signal_handler(int signo)
SetEvent(wait_signal_event[signo]);
}

typedef void (*sighandler_type)(int);

value caml_wait_signal(value sigs)
{
HANDLE event;
int res, s, retcode;
value l;
void (*)(int) oldsignals[NSIG];
sighandler_type oldsignals[NSIG];

Begin_root(sigs);
event = CreateEvent(NULL, FALSE, 0, NULL);
event = CreateEvent(NULL, FALSE, FALSE, NULL);
if (event == NULL)
caml_wthread_error("Thread.wait_signal (CreateEvent)");
res = 0;
for (l = sigs; l != Val_int(0); l = Field(l, 1)) {
s = convert_signal_number(Int_val(Field(l, 0)));
if (s < 0) s = posix_signals[-s-1];
oldsignals[s] = signal(s, caml_wait_signal_handler);
if (oldsignals[s] == SIG_ERR) {
CloseHandle(event);
Expand All @@ -618,7 +620,7 @@ value caml_wait_signal(value sigs)
}
CloseHandle(event);
End_roots();
if (retcode == WAIT_FAILED || retcode == WAIT_ABANDONED)
if (retcode == WAIT_FAILED)
caml_wthread_error("Thread.wait_signal (WaitForSingleObject)");
return Val_int(res);
}
Expand Down
18 changes: 9 additions & 9 deletions otherlibs/win32unix/unix.ml
Expand Up @@ -238,9 +238,9 @@ type stats =
st_gid : int;
st_rdev : int;
st_size : int;
st_atime : int;
st_mtime : int;
st_ctime : int }
st_atime : float;
st_mtime : float;
st_ctime : float }

external stat : string -> stats = "unix_stat"
let lstat = stat
Expand Down Expand Up @@ -371,17 +371,17 @@ type tm =
tm_yday : int;
tm_isdst : bool }

external time : unit -> int = "unix_time"
external time : unit -> float = "unix_time"
external gettimeofday : unit -> float = "unix_gettimeofday"
external gmtime : int -> tm = "unix_gmtime"
external localtime : int -> tm = "unix_localtime"
external mktime : tm -> int * tm = "unix_mktime"
external gmtime : float -> tm = "unix_gmtime"
external localtime : float -> tm = "unix_localtime"
external mktime : tm -> float * tm = "unix_mktime"
let alarm n = invalid_arg "Unix.alarm not implemented"
external sleep : int -> unit = "unix_sleep"
let times () =
{ tms_utime = Sys.time(); tms_stime = 0.0;
tms_cutime = 0.0; tms_cstime = 0.0 }
external utimes : string -> int -> int -> unit = "unix_utimes"
external utimes : string -> float -> float -> unit = "unix_utimes"

type interval_timer =
ITIMER_REAL
Expand Down Expand Up @@ -644,7 +644,7 @@ let open_connection sockaddr =
let sock =
socket domain SOCK_STREAM 0 in
connect sock sockaddr;
(in_channel_of_descr_bin sock, out_channel_of_descr_bin sock)
(in_channel_of_descr sock, out_channel_of_descr sock)

let shutdown_connection inchan =
shutdown (descr_of_in_channel inchan) SHUTDOWN_SEND
Expand Down
4 changes: 2 additions & 2 deletions stdlib/headernt.c
Expand Up @@ -29,7 +29,7 @@ static unsigned long read_size(char * ptr)
static char * read_runtime_path(HANDLE h)
{
char buffer[TRAILER_SIZE];
char runtime_path[MAX_PATH];
static char runtime_path[MAX_PATH];
DWORD nread;
struct exec_trailer tr;
long size;
Expand All @@ -44,7 +44,7 @@ static char * read_runtime_path(HANDLE h)
tr.symbol_size = read_size(buffer + 16);
tr.debug_size = read_size(buffer + 20);
if (tr.path_size >= MAX_PATH) return NULL;
if (tr.path_size == 0) return default_runtime_path;
if (tr.path_size == 0) return default_runtime_name;
size = tr.path_size + tr.code_size + tr.prim_size +
tr.data_size + tr.symbol_size + tr.debug_size + TRAILER_SIZE;
if (SetFilePointer(h, -size, NULL, FILE_END) == -1) return NULL;
Expand Down

0 comments on commit 059e11a

Please sign in to comment.