diff options
-rw-r--r-- | Makefile.nt | 453 | ||||
-rw-r--r-- | asmcomp/asmlink.ml | 2 | ||||
-rw-r--r-- | asmrun/Makefile.nt | 70 | ||||
-rw-r--r-- | asmrun/fail.c | 2 | ||||
-rw-r--r-- | asmrun/i386nt.asm | 289 | ||||
-rw-r--r-- | bytecomp/bytelink.ml | 2 | ||||
-rw-r--r-- | byterun/Makefile.nt | 66 | ||||
-rw-r--r-- | byterun/io.c | 3 | ||||
-rw-r--r-- | byterun/main.c | 3 | ||||
-rw-r--r-- | byterun/sys.c | 4 | ||||
-rw-r--r-- | config/Makefile.nt | 62 | ||||
-rw-r--r-- | config/m-nt.h | 19 | ||||
-rw-r--r-- | config/s-nt.h | 22 | ||||
-rw-r--r-- | config/s-templ.h | 4 | ||||
-rwxr-xr-x | configure | 14 | ||||
-rw-r--r-- | lex/Makefile.nt | 51 | ||||
-rw-r--r-- | stdlib/Makefile.nt | 4 | ||||
-rw-r--r-- | test/Makefile.nt | 175 | ||||
-rw-r--r-- | testasmcomp/Makefile.nt | 134 | ||||
-rw-r--r-- | testasmcomp/i386nt.asm | 66 | ||||
-rw-r--r-- | testasmcomp/mainarith.c | 6 | ||||
-rw-r--r-- | tools/Makefile.nt | 111 | ||||
-rw-r--r-- | yacc/Makefile.nt | 32 |
23 files changed, 1582 insertions, 12 deletions
diff --git a/Makefile.nt b/Makefile.nt new file mode 100644 index 000000000..f280c5efd --- /dev/null +++ b/Makefile.nt @@ -0,0 +1,453 @@ +# The main Makefile + +!include config\Makefile.nt + +### Which libraries to compile and install +OTHERLIBRARIES=str num dynlink + +CAMLC=boot\cslrun boot\cslc -I boot +CAMLOPT=boot\cslrun .\cslopt -I stdlib +COMPFLAGS=$(INCLUDES) +LINKFLAGS= +CAMLYACC=boot\cslyacc +YACCFLAGS= +CAMLLEX=boot\cslrun boot\csllex +CAMLDEP=boot\cslrun tools\csldep +DEPFLAGS=$(INCLUDES) +CAMLRUN=byterun\cslrun + +INCLUDES=-I utils -I parsing -I typing -I bytecomp -I asmcomp -I driver -I toplevel + +UTILS=utils\misc.cmo utils\tbl.cmo utils\config.cmo \ + utils\clflags.cmo utils\terminfo.cmo + +PARSING=parsing\location.cmo parsing\longident.cmo \ + parsing\pstream.cmo parsing\parser.cmo parsing\lexer.cmo parsing\parse.cmo + +TYPING=typing\ident.cmo typing\path.cmo \ + typing\primitive.cmo typing\typedtree.cmo \ + typing\subst.cmo typing\printtyp.cmo \ + typing\predef.cmo typing\datarepr.cmo typing\env.cmo \ + typing\ctype.cmo typing\mtype.cmo \ + typing\includecore.cmo typing\includemod.cmo typing\parmatch.cmo \ + typing\typetexp.cmo typing\typecore.cmo \ + typing\typedecl.cmo typing\typemod.cmo + +COMP=bytecomp\lambda.cmo bytecomp\printlambda.cmo \ + bytecomp\dectree.cmo bytecomp\matching.cmo \ + bytecomp\translcore.cmo bytecomp\translmod.cmo \ + bytecomp\simplif.cmo bytecomp\runtimedef.cmo + +BYTECOMP=bytecomp\meta.cmo bytecomp\instruct.cmo bytecomp\bytegen.cmo \ + bytecomp\printinstr.cmo bytecomp\opcodes.cmo bytecomp\emitcode.cmo \ + bytecomp\symtable.cmo bytecomp\bytelibrarian.cmo bytecomp\bytelink.cmo + +ASMCOMP=asmcomp\arch.cmo asmcomp\cmm.cmo asmcomp\printcmm.cmo \ + asmcomp\reg.cmo asmcomp\mach.cmo asmcomp\proc.cmo \ + asmcomp\clambda.cmo asmcomp\compilenv.cmo \ + asmcomp\closure.cmo asmcomp\cmmgen.cmo \ + asmcomp\printmach.cmo asmcomp\selection.cmo asmcomp\liveness.cmo \ + asmcomp\spill.cmo asmcomp\split.cmo \ + asmcomp\interf.cmo asmcomp\coloring.cmo asmcomp\reload.cmo \ + asmcomp\printlinear.cmo asmcomp\linearize.cmo asmcomp\scheduling.cmo \ + asmcomp\emitaux.cmo asmcomp\emit.cmo asmcomp\asmgen.cmo \ + asmcomp\asmlink.cmo asmcomp\asmlibrarian.cmo + +DRIVER=driver\errors.cmo driver\compile.cmo driver\main.cmo + +OPTDRIVER=driver\opterrors.cmo driver\optcompile.cmo driver\optmain.cmo + +TOPLEVEL=driver\errors.cmo driver\compile.cmo \ + toplevel\printval.cmo toplevel\toploop.cmo \ + toplevel\trace.cmo toplevel\topdirs.cmo + +TOPLEVELMAIN=toplevel\topmain.cmo + +COMPOBJS=$(UTILS) $(PARSING) $(TYPING) $(COMP) $(BYTECOMP) $(DRIVER) + +TOPLIB=$(UTILS) $(PARSING) $(TYPING) $(COMP) $(BYTECOMP) $(TOPLEVEL) + +TOPOBJS=$(TOPLIB) $(TOPLEVELMAIN) + +OPTOBJS=$(UTILS) $(PARSING) $(TYPING) $(COMP) $(ASMCOMP) $(OPTDRIVER) + +EXPUNGEOBJS=utils\misc.cmo utils\tbl.cmo \ + utils\config.cmo utils\clflags.cmo \ + typing\ident.cmo typing\predef.cmo \ + bytecomp\runtimedef.cmo bytecomp\symtable.cmo \ + toplevel\expunge.cmo + +PERVASIVES=arg array char digest filename format gc hashtbl lexing list map \ + obj parsing pervasives printexc printf queue random set sort \ + stack string stream sys + +# Recompile the system using the bootstrap compiler +all: runtime cslc csllex cslyacc csltools library csltop otherlibraries + +# The compilation of csltop will fail if the runtime has changed. +# Never mind, just do make bootstrap to reach fixpoint again. + +# Compile everything the first time +world: coldstart clean all + +# Set up the configuration files +configure: + cp config\m-nt.h config\m.h + cp config\s-nt.h config\s.h + +# Complete bootstrapping cycle +bootstrap: +# Save the original bootstrap compiler + $(MAKEREC) backup +# Promote the new compiler but keep the old runtime +# This compiler runs on boot\cslrun and produces bytecode for byterun\cslrun + $(MAKEREC) promote-cross +# Rebuild cslc and csllex (run on byterun\cslrun) + $(MAKEREC) clean + $(MAKEREC) cslc csllex +# Rebuild the library (using byterun\cslrun .\cslc) + $(MAKEREC) library-cross +# Promote the new compiler and the new runtime + $(MAKEREC) promote +# Rebuild everything, including csltop and the tools + $(MAKEREC) clean + $(MAKEREC) all +# Check if fixpoint reached + $(MAKEREC) compare + +LIBFILES=stdlib.cma std_exit.cmo *.cmi cslheader + +# Start up the system from the distribution compiler +coldstart: + cd byterun & $(MAKEREC) all + cp byterun\cslrun.exe boot\cslrun.exe + cd yacc & $(MAKEREC) all + cp yacc\cslyacc.exe boot\cslyacc.exe + cd stdlib & $(MAKEREC) COMPILER=..\boot\cslc all + cd stdlib & cp $(LIBFILES) ..\boot + +# Save the current bootstrap compiler +backup: + if not exist boot\Saved mkdir boot\Saved + mv boot\Saved boot\Saved.prev + mkdir boot\Saved + mv boot\Saved.prev boot\Saved\Saved.prev + cp boot\cslrun.exe boot\Saved + mv boot\cslc boot\csllex boot\cslyacc.exe boot\Saved + cd boot & cp $(LIBFILES) Saved + +# Promote the newly compiled system to the rank of cross compiler +# (Runs on the old runtime, produces code for the new runtime) +promote-cross: + cp cslc boot\cslc + cp lex\csllex boot\csllex + cp yacc\cslyacc boot\cslyacc + cd stdlib & cp $(LIBFILES) ..\boot + +# Promote the newly compiled system to the rank of bootstrap compiler +# (Runs on the new runtime, produces code for the new runtime) +promote: promote-cross + cp byterun\cslrun.exe boot\cslrun.exe + +# Restore the saved bootstrap compiler if a problem arises +restore: + mv boot\Saved\* boot + rmdir boot\Saved + mv boot\Saved.prev boot\Saved + +# Check if fixpoint reached +compare: + fc /b boot\cslc cslc + fc /b boot\csllex lex\csllex + echo "Fixpoint reached, bootstrap succeeded." + +# Remove old bootstrap compilers +cleanboot: + rm -rf boot\Saved\Saved.prev\* + +# Compile the native-code compiler +opt: runtimeopt cslopt libraryopt otherlibrariesopt + +# Installation +install: + if not exist $(BINDIR) mkdir $(BINDIR) + if not exist $(LIBDIR) mkdir $(LIBDIR) + if not exist $(MANDIR) mkdir $(MANDIR) + cd byterun & $(MAKEREC) install + cp cslc $(BINDIR)\cslc.exe + cp csltop $(BINDIR)\csltop.exe + cd stdlib & $(MAKEREC) install + cp lex\csllex $(BINDIR)\csllex.exe + cp yacc\cslyacc.exe $(BINDIR)\cslyacc.exe + $(CAMLC) -a -o $(LIBDIR)\toplevellib.cma $(TOPLIB) + cp toplevel\topmain.cmo $(LIBDIR) + cp toplevel\toploop.cmi toplevel\topdirs.cmi $(LIBDIR) + cd tools & $(MAKEREC) install + for %i in ($(OTHERLIBRARIES)) do (cd otherlibs\%i & $(MAKEREC) install) + +# Installation of the native-code compiler +installopt: + cd asmrun & $(MAKEREC) install + cp cslopt $(BINDIR)\cslopt + cd stdlib & $(MAKEREC) installopt + for %i in ($(OTHERLIBRARIES)) do (cd otherlibs\%i & $(MAKEREC) installopt) + +realclean:: clean + +# The compiler + +cslc: $(COMPOBJS) + $(CAMLC) $(LINKFLAGS) -o cslc $(COMPOBJS) + +clean:: + rm -f cslc + +# The native-code compiler + +cslopt: $(OPTOBJS) + $(CAMLC) $(LINKFLAGS) -o cslopt $(OPTOBJS) + +clean:: + rm -f cslopt + +# The toplevel + +csltop: $(TOPOBJS) expunge + $(CAMLC) $(LINKFLAGS) -linkall -o csltop.tmp $(TOPOBJS) + - $(CAMLRUN) .\expunge csltop.tmp csltop $(PERVASIVES) + rm -f csltop.tmp + +clean:: + rm -f csltop + +# The configuration file + +utils\config.ml: utils\config.mlp config\Makefile.nt + @rm -f utils\config.ml + sed -e "s|%%%%LIBDIR%%%%|$(LIBDIR:\=/)|" \ + -e "s|%%%%BYTECC%%%%|$(BYTECC) $(BYTECCLINKOPTS)|" \ + -e "s|%%%%NATIVECC%%%%|$(NATIVECC) $(NATIVECCLINKOPTS)|" \ + -e "s|%%%%CCLIBS%%%%|$(CCLIBS)|" \ + -e "s|%%%%ARCH%%%%|$(ARCH)|" \ + -e "s|%%%%MODEL%%%%|$(MODEL)|" \ + -e "s|%%%%SYSTEM%%%%|$(SYSTEM)|" \ + -e "s|%%%%EXT_OBJ%%%%|.obj|" \ + -e "s|%%%%EXT_ASM%%%%|.asm|" \ + -e "s|%%%%EXT_LIB%%%%|.lib|" \ + utils\config.mlp > utils\config.ml + @attrib +r utils\config.ml + +clean:: + rm -f utils\config.ml + +beforedepend:: utils\config.ml + +# The parser generator + +parsing\parser.mli parsing\parser.ml: parsing\parser.mly + $(CAMLYACC) $(YACCFLAGS) parsing\parser.mly + +clean:: + rm -f parsing\parser.mli parsing\parser.ml parsing\parser.output + +beforedepend:: parsing\parser.mli parsing\parser.ml + +# The lexer generator + +parsing\lexer.ml: parsing\lexer.mll + $(CAMLLEX) parsing\lexer.mll + +clean:: + rm -f parsing\lexer.ml + +beforedepend:: parsing\lexer.ml + +# The compiler compiled with the native-code compiler +# Currently not working because it requires C primitives from byterun\meta.c +# which are not provided by asmrun\libasmrun.lib + +# cslc.opt: $(COMPOBJS:.cmo=.cmx) +# $(CAMLOPT) $(LINKFLAGS) -o cslc.opt $(COMPOBJS:.cmo=.cmx) + +clean:: + rm -f cslc.opt + +# The native-code compiler compiled with itself + +cslopt.opt: $(OPTOBJS:.cmo=.cmx) + $(CAMLOPT) $(LINKFLAGS) -o cslopt.opt $(OPTOBJS:.cmo=.cmx) + +clean:: + rm -f cslopt.opt + +$(OPTOBJS:.cmo=.cmx): cslopt + +# The numeric opcodes + +bytecomp\opcodes.ml: byterun\instruct.h + sed -n -e "/^enum/p" -e "s|,||g" -e "/^ /p" byterun\instruct.h | \ + gawk -f tools\make-opcodes > bytecomp\opcodes.ml + +clean:: + rm -f bytecomp\opcodes.ml + +beforedepend:: bytecomp\opcodes.ml + +# The predefined exceptions and primitives + +runtime\primitives: + cd runtime & $(MAKEREC) primitives + +bytecomp\runtimedef.ml: byterun\primitives byterun\fail.h + echo let builtin_exceptions = ^[^| > bytecomp\runtimedef.ml + sed -n -e "s|.*/\* \(\"[A-Za-z_]*\"\) \*/$$| \1;|p" byterun\fail.h | \ + sed -e "$$s|;$$||" >> bytecomp\runtimedef.ml + echo ^|^] >> bytecomp\runtimedef.ml + echo let builtin_primitives = ^[^| >> bytecomp\runtimedef.ml + sed -e "s|.*| \"^&\";|" -e "$$s|;$$||" byterun\primitives \ + >> bytecomp\runtimedef.ml + echo ^|^] >> bytecomp\runtimedef.ml + +clean:: + rm -f bytecomp\runtimedef.ml + +beforedepend:: bytecomp\runtimedef.ml + +# Choose the right arch, emit and proc files + +asmcomp\arch.ml: asmcomp\arch_$(ARCH).ml + cp asmcomp\arch_$(ARCH).ml asmcomp\arch.ml + +clean:: + rm -f asmcomp\arch.ml + +beforedepend:: asmcomp\arch.ml + +asmcomp\proc.ml: asmcomp\proc_$(ARCH).ml + cp asmcomp\proc_$(ARCH)nt.ml asmcomp\proc.ml + +clean:: + rm -f asmcomp\proc.ml + +beforedepend:: asmcomp\proc.ml + +# Preprocess the code emitters + +asmcomp\emit.ml: asmcomp\emit_$(ARCH)nt.mlp tools\cvt_emit + perl tools\cvt_emit asmcomp\emit_$(ARCH)nt.mlp > asmcomp\emit.ml + +clean:: + rm -f asmcomp\emit.ml + +beforedepend:: asmcomp\emit.ml + +# The "expunge" utility + +expunge: $(EXPUNGEOBJS) + $(CAMLC) $(LINKFLAGS) -o expunge $(EXPUNGEOBJS) + +clean:: + rm -f expunge + +# The runtime system for the bytecode compiler + +runtime: + cd byterun & $(MAKEREC) all +realclean:: + cd byterun & $(MAKEREC) clean +alldepend:: + cd byterun & $(MAKEREC) depend + +# The runtime system for the native-code compiler + +runtimeopt: makeruntimeopt stdlib\libasmrun.lib + +makeruntimeopt: + cd asmrun & $(MAKEREC) all +stdlib\libasmrun.lib: asmrun\libasmrun.lib + cp asmrun\libasmrun.lib stdlib\libasmrun.lib +realclean:: + cd asmrun & $(MAKEREC) clean +alldepend:: + cd asmrun & $(MAKEREC) depend + +# The library + +library: + cd stdlib & $(MAKEREC) all +library-cross: + cd stdlib & $(MAKEREC) RUNTIME=..\byterun\cslrun all +libraryopt: + cd stdlib & $(MAKEREC) allopt +clean:: + cd stdlib & $(MAKEREC) clean +alldepend:: + cd stdlib & $(MAKEREC) depend + +# The lexer and parser generators + +csllex: + cd lex & $(MAKEREC) all +clean:: + cd lex & $(MAKEREC) clean +alldepend:: + cd lex & $(MAKEREC) depend + +cslyacc: + cd yacc & $(MAKEREC) all +realclean:: + cd yacc & $(MAKEREC) clean + +# Tools + +csltools: + cd tools & $(MAKEREC) all +realclean:: + cd tools & $(MAKEREC) clean +alldepend:: + cd tools & $(MAKEREC) depend + +# The extra libraries + +otherlibraries: + -for %i in ($(OTHERLIBRARIES)) do (cd otherlibs\%i & $(MAKEREC) all) +otherlibrariesopt: + -for %i in ($(OTHERLIBRARIES)) do (cd otherlibs\%i & $(MAKEREC) allopt) +clean:: + -for %i in ($(OTHERLIBRARIES)) do (cd otherlibs\%i & $(MAKEREC) clean) +realclean:: + -for %i in ($(OTHERLIBRARIES)) do (cd otherlibs\%i & $(MAKEREC) realclean) +alldepend:: + -for %i in ($(OTHERLIBRARIES)) do (cd otherlibs\%i & $(MAKEREC) depend) + +# Default rules + +.SUFFIXES: .ml .mli .cmo .cmi .cmx + +.ml.cmo: + $(CAMLC) $(COMPFLAGS) -c $< + +.mli.cmi: + $(CAMLC) $(COMPFLAGS) -c $< + +.ml.cmx: + $(CAMLOPT) $(COMPFLAGS) -c $< + +clean:: + rm -f utils\*.cm[iox] utils\*.[so] utils\*~ + rm -f parsing\*.cm[iox] parsing\*.[so] parsing\*~ + rm -f typing\*.cm[iox] typing\*.[so] typing\*~ + rm -f bytecomp\*.cm[iox] bytecomp\*.[so] bytecomp\*~ + rm -f asmcomp\*.cm[iox] asmcomp\*.[so] asmcomp\*~ + rm -f driver\*.cm[iox] driver\*.[so] driver\*~ + rm -f toplevel\*.cm[iox] toplevel\*.[so] toplevel\*~ + rm -f tools\*.cm[iox] tools\*.[so] tools\*~ + rm -f *~ + +depend: beforedepend + echo > .depend + for %d in (utils parsing typing bytecomp asmcomp driver toplevel) do $(CAMLDEP) $(DEPFLAGS) %d\*.mli %d\*.ml >> .depend + +alldepend:: depend + +!include .depend diff --git a/asmcomp/asmlink.ml b/asmcomp/asmlink.ml index eeb8fbdc3..1a2efae10 100644 --- a/asmcomp/asmlink.ml +++ b/asmcomp/asmlink.ml @@ -175,7 +175,7 @@ let call_linker file_list startup_file = match Config.system with "win32" -> Printf.sprintf - "%s -Fe %s -I%s %s %s %s %s %s %s" + "%s /Fe%s -I%s %s %s %s %s %s %s" Config.native_c_compiler !Clflags.exec_name Config.standard_library diff --git a/asmrun/Makefile.nt b/asmrun/Makefile.nt new file mode 100644 index 000000000..e6a4c9fcc --- /dev/null +++ b/asmrun/Makefile.nt @@ -0,0 +1,70 @@ +!include ..\config\Makefile.nt + +CC=$(NATIVECC) +CFLAGS=-I..\byterun -DNATIVE_CODE -DTARGET_$(ARCH) -DSYS_$(SYSTEM) $(NATIVECCCOMPOPTS) + +COBJS=main.obj fail.obj roots.obj signals.obj \ + misc.obj freelist.obj major_gc.obj minor_gc.obj memory.obj alloc.obj compare.obj ints.obj \ + floats.obj str.obj array.obj io.obj extern.obj intern.obj hash.obj sys.obj parsing.obj \ + gc_ctrl.obj terminfo.obj md5.obj obj.obj +ASMOBJS=$(ARCH)nt.obj + +OBJS=$(COBJS) $(ASMOBJS) + +all: libasmrun.lib + +libasmrun.lib: $(OBJS) + rm -f libasmrun.lib + $(MKLIB)libasmrun.lib $(OBJS) + +install: + cp libasmrun.lib $(LIBDIR) + +misc.c: ..\byterun\misc.c + cp ..\byterun\misc.c misc.c +freelist.c: ..\byterun\freelist.c + cp ..\byterun\freelist.c freelist.c +major_gc.c: ..\byterun\major_gc.c + cp ..\byterun\major_gc.c major_gc.c +minor_gc.c: ..\byterun\minor_gc.c + cp ..\byterun\minor_gc.c minor_gc.c +memory.c: ..\byterun\memory.c + cp ..\byterun\memory.c memory.c +alloc.c: ..\byterun\alloc.c + cp ..\byterun\alloc.c alloc.c +compare.c: ..\byterun\compare.c + cp ..\byterun\compare.c compare.c +ints.c: ..\byterun\ints.c + cp ..\byterun\ints.c ints.c +floats.c: ..\byterun\floats.c + cp ..\byterun\floats.c floats.c +str.c: ..\byterun\str.c + cp ..\byterun\str.c str.c +io.c: ..\byterun\io.c + cp ..\byterun\io.c io.c +extern.c: ..\byterun\extern.c + cp ..\byterun\extern.c extern.c +intern.c: ..\byterun\intern.c + cp ..\byterun\intern.c intern.c +hash.c: ..\byterun\hash.c + cp ..\byterun\hash.c hash.c +sys.c: ..\byterun\sys.c + cp ..\byterun\sys.c sys.c +parsing.c: ..\byterun\parsing.c + cp ..\byterun\parsing.c parsing.c +gc_ctrl.c: ..\byterun\gc_ctrl.c + cp ..\byterun\gc_ctrl.c gc_ctrl.c +terminfo.c: ..\byterun\terminfo.c + cp ..\byterun\terminfo.c terminfo.c +md5.c: ..\byterun\md5.c + cp ..\byterun\md5.c md5.c +obj.c: ..\byterun\obj.c + cp ..\byterun\obj.c obj.c + +clean:: + rm -f *.obj *.lib *~ + +depend: + sed -e "s/\.o/.obj/g" .depend > .depend.nt + +!include .depend.nt diff --git a/asmrun/fail.c b/asmrun/fail.c index 8b014fbc3..b796ecf68 100644 --- a/asmrun/fail.c +++ b/asmrun/fail.c @@ -46,8 +46,10 @@ void mlraise(v) sigemptyset(&mask); sigprocmask(SIG_SETMASK, &mask, NULL); #else +#ifdef HAS_SIGSETMASK sigsetmask(0); #endif +#endif leave_blocking_section(); #ifndef Stack_grows_upwards while (local_roots != NULL && diff --git a/asmrun/i386nt.asm b/asmrun/i386nt.asm new file mode 100644 index 000000000..264a96e02 --- /dev/null +++ b/asmrun/i386nt.asm @@ -0,0 +1,289 @@ +;********************************************************************* +; +; Caml Special Light +; +; Xavier Leroy, projet Cristal, INRIA Rocquencourt +; +; Copyright 1995 Institut National de Recherche en Informatique et +; Automatique. Distributed only by permission. +; +;********************************************************************* + +; $Id$ + +; Asm part of the runtime system, Intel 386 processor, Intel syntax + + .386 + .MODEL FLAT + + EXTERN _garbage_collection: PROC + EXTERN _mlraise: PROC + EXTERN _caml_apply2: PROC + EXTERN _caml_apply3: PROC + EXTERN _caml_program: PROC + EXTERN _young_limit: DWORD + EXTERN _young_ptr: DWORD + + PUBLIC _gc_entry_regs + PUBLIC _caml_bottom_of_stack + PUBLIC _caml_top_of_stack + PUBLIC _caml_last_return_address + PUBLIC _caml_exception_pointer + + .DATA + ALIGN 4 + +_gc_entry_regs DWORD 7 DUP(?) +_caml_bottom_of_stack DWORD 0 +_caml_top_of_stack DWORD 0 +_caml_last_return_address DWORD 0 +_caml_exception_pointer DWORD 0 + +; Allocation + + .CODE + PUBLIC _caml_alloc1 + PUBLIC _caml_alloc2 + PUBLIC _caml_alloc3 + PUBLIC _caml_alloc + PUBLIC _caml_call_gc + + ALIGN 4 +_caml_alloc1: + mov eax, _young_ptr + sub eax, 8 + mov _young_ptr, eax + cmp eax, _young_limit + jb L100 + ret +L100: mov eax, 8 + jmp L105 + + ALIGN 4 +_caml_alloc2: + mov eax, _young_ptr + sub eax, 12 + mov _young_ptr, eax + cmp eax, _young_limit + jb L101 + ret +L101: mov eax, 12 + jmp L105 + + ALIGN 4 +_caml_alloc3: + mov eax, _young_ptr + sub eax, 16 + mov _young_ptr, eax + cmp eax, _young_limit + jb L102 + ret +L102: mov eax, 16 + jmp L105 + + ALIGN 4 +_caml_alloc: + push eax + mov eax, _young_ptr + sub eax, [esp] + mov _young_ptr, eax + cmp eax, _young_limit + jb L103 + add esp, 4 + ret +L103: pop eax + jmp L105 + +_caml_call_gc: + ; Adjust return address and recover desired size in eax + pop eax + add eax, 2 + push eax + movzx eax, WORD PTR [eax-2] +L105: + ; Record lowest stack address and return address + pop _caml_last_return_address + mov _caml_bottom_of_stack, esp + ; Save all regs used by the code generator + mov _gc_entry_regs + 4, ebx + mov _gc_entry_regs + 8, ecx + mov _gc_entry_regs + 12, edx + mov _gc_entry_regs + 16, esi + mov _gc_entry_regs + 20, edi + mov _gc_entry_regs + 24, ebp + ; Save desired size + push eax + ; Call the garbage collector + call _garbage_collection + ; Restore all regs used by the code generator + mov ebx, _gc_entry_regs + 4 + mov ecx, _gc_entry_regs + 8 + mov edx, _gc_entry_regs + 12 + mov esi, _gc_entry_regs + 16 + mov edi, _gc_entry_regs + 20 + mov ebp, _gc_entry_regs + 24 + ; Recover desired size + pop eax + ; Decrement young_ptr by desired size + sub _young_ptr, eax + ; Reload result of allocation in %eax + mov eax, _young_ptr + ; Return to caller + push _caml_last_return_address + ret + +; Call a C function from Caml + + PUBLIC _caml_c_call + ALIGN 4 +_caml_c_call: + ; Record lowest stack address and return address + ; In parallel, free the floating point registers + ; (Pairing is expected on the Pentium.) + mov edx, [esp] + ffree st(0) + mov _caml_last_return_address, edx + ffree st(1) + lea edx, [esp+4] + ffree st(2) + mov _caml_bottom_of_stack, edx + ffree st(3) + ; Call the function (address in %eax) + jmp eax + +; Start the Caml program + + PUBLIC _caml_start_program + ALIGN 4 +_caml_start_program: + ; Save callee-save registers + push ebx + push esi + push edi + push ebp + ; Build an exception handler + push L104 + push 0 + mov _caml_exception_pointer, esp + ; Record highest stack address + mov _caml_top_of_stack, esp + ; Go for it + call _caml_program + ; Pop handler + add esp, 8 + ; Zero return code + xor eax, eax +L104: + ; Restore registers and return + pop ebp + pop edi + pop esi + pop ebx + ret + +; Raise an exception from C + + PUBLIC _raise_caml_exception + ALIGN 4 +_raise_caml_exception: + mov eax, [esp+4] + mov esp, _caml_exception_pointer + pop _caml_exception_pointer + ret + +; Callback from C to Caml + + PUBLIC _callback + ALIGN 4 +_callback: + ; Save callee-save registers + push ebx + push esi + push edi + push ebp + ; Initial loading of arguments + mov ebx, [esp+20] ; closure + mov eax, [esp+24] ; argument + mov esi, [ebx] ; code pointer +L106: + ; Build a callback link + push _caml_last_return_address + push _caml_bottom_of_stack + ; Build an exception handler + push L108 + push _caml_exception_pointer + mov _caml_exception_pointer, esp + ; Call the Caml code + call esi +L107: + ; Pop the exception handler + pop _caml_exception_pointer + pop esi ; dummy register + ; Pop the callback link, restoring the global variables + ; used by caml_c_call + pop _caml_bottom_of_stack + pop _caml_last_return_address + ; Restore callee-save registers. + ; In parallel, free the floating-point registers + ; that may have been used by Caml. + pop ebp + ffree st(0) + pop edi + ffree st(1) + pop esi + ffree st(2) + pop ebx + ffree st(3) + ; Return to caller. + ret +L108: + ; Exception handler + ; Pop the callback link, restoring the global variables + ; used by caml_c_call + pop _caml_bottom_of_stack + pop _caml_last_return_address + ; Re-raise the exception through mlraise, + ; so that local C roots are cleaned up correctly. + push eax ; exn bucket is the argument + call _mlraise ; never returns + + PUBLIC _callback2 + ALIGN 4 +_callback2: + ; Save callee-save registers + push ebx + push esi + push edi + push ebp + ; Initial loading of arguments + mov ecx, [esp+20] ; closure + mov eax, [esp+24] ; first argument + mov ebx, [esp+28] ; second argument + mov esi, offset _caml_apply2 ; code pointer + jmp L106 + + PUBLIC _callback3 + ALIGN 4 +_callback3: + ; Save callee-save registers + push ebx + push esi + push edi + push ebp + ; Initial loading of arguments + mov edx, [esp+20] ; closure + mov eax, [esp+24] ; first argument + mov ebx, [esp+28] ; second argument + mov ecx, [esp+32] ; third argument + mov esi, offset _caml_apply3 ; code pointer + jmp L106 + + .DATA + PUBLIC _system_frametable +_system_frametable LABEL DWORD + DWORD 1 ; one descriptor + DWORD L107 ; return address into callback + WORD -1 ; negative frame size => use callback link + WORD 0 ; no roots here + + END diff --git a/bytecomp/bytelink.ml b/bytecomp/bytelink.ml index d3f8dfa06..dfec31d9f 100644 --- a/bytecomp/bytelink.ml +++ b/bytecomp/bytelink.ml @@ -223,7 +223,7 @@ let build_custom_runtime prim_name exec_name = "win32" -> Sys.command (Printf.sprintf - "%s -Fe %s -I%s %s %s %s %s\\libcamlrun.lib %s" + "%s /Fe%s -I%s %s %s %s %s\\libcamlrun.lib %s" Config.bytecomp_c_compiler exec_name Config.standard_library diff --git a/byterun/Makefile.nt b/byterun/Makefile.nt new file mode 100644 index 000000000..73f6c38d2 --- /dev/null +++ b/byterun/Makefile.nt @@ -0,0 +1,66 @@ +!include ..\config\Makefile.nt + +CC=$(BYTECC) +CFLAGS=$(BYTECCCOMPOPTS) + +OBJS=interp.obj misc.obj stacks.obj fix_code.obj main.obj fail.obj signals.obj \ + freelist.obj major_gc.obj minor_gc.obj memory.obj alloc.obj roots.obj \ + compare.obj ints.obj floats.obj str.obj array.obj io.obj extern.obj intern.obj \ + hash.obj sys.obj meta.obj parsing.obj gc_ctrl.obj terminfo.obj md5.obj obj.obj + +PRIMS=array.c compare.c extern.c floats.c gc_ctrl.c hash.c \ + intern.c interp.c ints.c io.c md5.c meta.c obj.c parsing.c \ + signals.c str.c sys.c terminfo.c + +all: cslrun.exe + +cslrun.exe: $(OBJS) prims.obj + $(BYTECC) $(BYTECCCOMPOPTS) $(BYTECCLINKOPTS) /Fecslrun.exe prims.obj $(OBJS) $(CCLIBS) + +install: + cp cslrun.exe $(BINDIR)\cslrun.exe + rm -f $(LIBDIR)\libcamlrun.lib + $(MKLIB)$(LIBDIR)\libcamlrun.lib $(OBJS) + if not exist $(LIBDIR)\caml mkdir $(LIBDIR)\caml + cp mlvalues.h alloc.h misc.h $(LIBDIR)\caml + sed -e "/#include .*\/m.h\r ..\config\m.h" \ + -e "/#include .*\/s.h\r ..\config\s.h" \ + -e "/#include /d" config.h > $(LIBDIR)\caml\config.h + sed -e "/#include .*gc\.h"/d" \ + -e "/#define Alloc_small/,/^}/d" \ + -e "/Modify/,/^}/d" memory.h > $(LIBDIR)\caml\memory.h + +clean: + rm -f cslrun.exe *.obj *.lib + rm -f primitives prims.c opnames.h jumptbl.h + +primitives : $(PRIMS) + sed -n -e "/\/\* ML \*\//s/.* \([a-z0-9_]*\)(.*/\1/p" \ + $(PRIMS) > primitives + +prims.c : primitives + echo #include "mlvalues.h" > prims.c + echo #include "prims.h" >> prims.c + sed -e "s/.*/extern value &();/" primitives >> prims.c + echo c_primitive cprim[] = { >> prims.c + sed -e "s/.*/ &,/" primitives >> prims.c + echo 0 }; >> prims.c + echo char * names_of_cprim[] = { >> prims.c + sed -e "s/.*/ \"^&\",/" primitives >> prims.c + echo 0 }; >> prims.c + +opnames.h : instruct.h + sed -e "/\/\*/d" \ + -e "s\enum /char * names_of_/" \ + -e "s/{$$/[] = {/" \ + -e "s/\([A-Z][A-Z_0-9]*\)/"\1"/g" instruct.h > opnames.h + +# jumptbl.h is required only if you have GCC 2.0 or later +jumptbl.h : instruct.h + sed -n -e "/^ /s/ \([A-Z]\)/ \&\&lbl_\1/gp" \ + -e "/^}/q" instruct.h > jumptbl.h + +depend: + sed -e "s/\.o/.obj/g" .depend > .depend.nt + +!include .depend.nt diff --git a/byterun/io.c b/byterun/io.c index 69a192ba5..342dd6896 100644 --- a/byterun/io.c +++ b/byterun/io.c @@ -16,7 +16,10 @@ #include <errno.h> #include <fcntl.h> #include <string.h> +#include "config.h" +#ifdef HAS_UNISTD #include <unistd.h> +#endif #ifdef __STDC__ #include <limits.h> #endif diff --git a/byterun/main.c b/byterun/main.c index 6cd9d8ab7..5ffd899fb 100644 --- a/byterun/main.c +++ b/byterun/main.c @@ -17,7 +17,10 @@ #include <stdlib.h> #include <string.h> #include <fcntl.h> +#include "config.h" +#ifdef HAS_UNISTD #include <unistd.h> +#endif #include "alloc.h" #include "exec.h" #include "fail.h" diff --git a/byterun/sys.c b/byterun/sys.c index d56b00a2f..957885fad 100644 --- a/byterun/sys.c +++ b/byterun/sys.c @@ -20,8 +20,10 @@ #include <string.h> #include <sys/types.h> #include <sys/stat.h> -#include <unistd.h> #include "config.h" +#ifdef HAS_UNISTD +#include <unistd.h> +#endif #include "alloc.h" #include "fail.h" #include "instruct.h" diff --git a/config/Makefile.nt b/config/Makefile.nt new file mode 100644 index 000000000..9d79f94d6 --- /dev/null +++ b/config/Makefile.nt @@ -0,0 +1,62 @@ +# Configuration for Windows NT/95, Visual C++ 4.0 + +######### General configuration + +### Where to install the binaries +BINDIR=c:\camlsl\bin + +### Where to install the standard library +LIBDIR=c:\camlsl\lib + +########## Configuration for the bytecode compiler + +### Which C compiler to use for the bytecode interpreter. +BYTECC=cl /nologo + +### Additional compile-time options for $(BYTECC). +BYTECCCOMPOPTS=/Ox + +### Additional link-time options for $(BYTECC) +BYTECCLINKOPTS= + +### Libraries needed +CCLIBS= + +### How to invoke the C preprocessor +CPP=cl /nologo /EP + +### How to invoke the librarian +MKLIB=lib /nologo /debugtype:CV /out: + +############# Configuration for the native-code compiler + +### Name of architecture for the native-code compiler +ARCH=i386 + +### Name of architecture model for the native-code compiler. +MODEL=default + +### Name of operating system family for the native-code compiler. +SYSTEM=win32 + +### Which C compiler to use for the native-code compiler. +NATIVECC=cl /nologo + +### Additional compile-time options for $(NATIVECC). +NATIVECCCOMPOPTS=/Ox + +### Additional link-time options for $(NATIVECC) +NATIVECCLINKOPTS= + +### Flags for the assembler +AS=ml /nologo +ASFLAGS=/coff /Cp + +############# Configuration for the contributed libraries + +### Name of the target architecture for the "num" library +BIGNUM_ARCH=C + +############# Aliases for common commands + +MAKEREC=$(MAKE) -nologo -f Makefile.nt diff --git a/config/m-nt.h b/config/m-nt.h new file mode 100644 index 000000000..3bf7c7739 --- /dev/null +++ b/config/m-nt.h @@ -0,0 +1,19 @@ +/***********************************************************************/ +/* */ +/* Caml Special Light */ +/* */ +/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */ +/* */ +/* Copyright 1995 Institut National de Recherche en Informatique et */ +/* Automatique. Distributed only by permission. */ +/* */ +/***********************************************************************/ + +/* $Id$ */ + +/* Machine configuration, Intel x86 processors, Windows NT */ + +#undef SIXTYFOUR +#undef BIG_ENDIAN +#undef ALIGN_DOUBLE + diff --git a/config/s-nt.h b/config/s-nt.h new file mode 100644 index 000000000..90dcc158b --- /dev/null +++ b/config/s-nt.h @@ -0,0 +1,22 @@ +/***********************************************************************/ +/* */ +/* Caml Special Light */ +/* */ +/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */ +/* */ +/* Copyright 1995 Institut National de Recherche en Informatique et */ +/* Automatique. Distributed only by permission. */ +/* */ +/***********************************************************************/ + +/* $Id$ */ + +/* Operating system dependencies, Intel x86 processors, Windows NT */ + +#define HAS_MEMMOVE +#define BSD_SIGNALS +#define HAS_STRERROR +#define HAS_GETCWD +#define HAS_DUP2 +#define HAS_SELECT +#define HAS_GETHOSTNAME diff --git a/config/s-templ.h b/config/s-templ.h index 3cfb458f6..bfb6d2a5d 100644 --- a/config/s-templ.h +++ b/config/s-templ.h @@ -44,6 +44,10 @@ undefined if signal handlers have the System V semantics: the signal resets the behavior to default. */ +#define HAS_SIGSETMASK + +/* Define HAS_SIGSETMASK if you have sigsetmask(), as in BSD. */ + #define HAS_TERMCAP /* Define HAS_TERMCAP if you have the termcap functions to read the @@ -311,11 +311,17 @@ fi if sh hasgot sigaction sigprocmask; then echo "POSIX signal handling found." echo "#define POSIX_SIGNALS" >> s.h -elif sh runtest signals.c; then - echo "Signals have the BSD semantics." - echo "#define BSD_SIGNALS" >> s.h else - echo "Signals have the System V semantics." + if sh runtest signals.c; then + echo "Signals have the BSD semantics." + echo "#define BSD_SIGNALS" >> s.h + else + echo "Signals have the System V semantics." + fi + if sh hasgot sigsetmask; then + echo "sigsetmask() found" + echo "#define HAS_SIGSETMASK" >> s.h + fi fi # For the sys module diff --git a/lex/Makefile.nt b/lex/Makefile.nt new file mode 100644 index 000000000..a6fc15aa7 --- /dev/null +++ b/lex/Makefile.nt @@ -0,0 +1,51 @@ +# The lexer generator + +CAMLC=..\boot\cslrun ..\boot\cslc -I ..\boot +COMPFLAGS= +LINKFLAGS= +CAMLYACC=..\boot\cslyacc +YACCFLAGS= +CAMLLEX=..\boot\cslrun ..\boot\csllex +CAMLDEP=..\boot\cslrun ..\tools\csldep +DEPFLAGS= + +OBJS=syntax.cmo parser.cmo lexer.cmo lexgen.cmo output.cmo main.cmo + +all: csllex + +csllex: $(OBJS) + $(CAMLC) $(LINKFLAGS) -o csllex $(OBJS) + +clean:: + rm -f csllex + rm -f *.cmo *.cmi + +parser.ml parser.mli: parser.mly + $(CAMLYACC) $(YACCFLAGS) parser.mly + +clean:: + rm -f parser.ml parser.mli + +beforedepend:: parser.ml parser.mli + +lexer.ml: lexer.mll + $(CAMLLEX) lexer.mll + +clean:: + rm -f lexer.ml + +beforedepend:: lexer.ml + +.SUFFIXES: +.SUFFIXES: .ml .cmo .mli .cmi + +.ml.cmo: + $(CAMLC) -c $(COMPFLAGS) $< + +.mli.cmi: + $(CAMLC) -c $(COMPFLAGS) $< + +depend: beforedepend + $(CAMLDEP) *.mli *.ml > .depend + +!include .depend diff --git a/stdlib/Makefile.nt b/stdlib/Makefile.nt index 6c8bf324f..7c5868898 100644 --- a/stdlib/Makefile.nt +++ b/stdlib/Makefile.nt @@ -31,7 +31,7 @@ stdlib.cmxa: $(OBJS:.cmo=.cmx) $(CAMLOPT) -a -o stdlib.cmxa $(OBJS:.cmo=.cmx) cslheader: header.c ..\config\Makefile.nt - $(BYTECC) $(BYTECCCOMPOPTS) $(BYTECCLINKOPTS) header.c -Fe cslheader. + $(BYTECC) $(BYTECCCOMPOPTS) $(BYTECCLINKOPTS) -Fecslheader. header.c clean:: rm -f cslheader @@ -47,7 +47,7 @@ pervasives.cmx: pervasives.ml filename.ml: filename.mlp ..\config\Makefile.nt @rm -f filename.ml - $(CPP) -DUNIX filename.mlp > filename.ml + $(CPP) -DWIN32 filename.mlp > filename.ml @attrib +r filename.ml clean:: diff --git a/test/Makefile.nt b/test/Makefile.nt new file mode 100644 index 000000000..3b2d8474c --- /dev/null +++ b/test/Makefile.nt @@ -0,0 +1,175 @@ +!include ..\config\Makefile.nt + +CAMLC=..\boot\cslrun ..\cslc -I ..\stdlib -I KB -I Lex +CAMLOPT=..\boot\cslrun ..\cslopt -I ..\stdlib -I KB -I Lex +OPTFLAGS=-S +CAMLYACC=..\yacc\cslyacc +CAMLLEX=..\boot\cslrun ..\lex\csllex +CAMLDEP=..\boot\cslrun ..\tools\csldep +CAMLRUN=..\byterun\cslrun +CODERUNPARAMS=CAMLRUNPARAM='o=100' + +BYTE_EXE=fib.byt takc.byt taku.byt sieve.byt quicksort.byt quicksort.fast.byt \ + fft.byt fft.fast.byt soli.byt soli.fast.byt boyer.byt kb.byt \ + nucleic.byt genlex.byt + +CODE_EXE=$(BYTE_EXE:.byt=.exe) + +all: $(BYTE_EXE) $(CODE_EXE) + +# Nucleic + +nucleic.exe: nucleic.ml +!if "$(ARCH)" == "i386" + sed -e "/<HAND_CSE>/,/<\/HAND_CSE>/d" -e "/NO_CSE>/d" nucleic.ml > nucleic.mlt + $(CAMLOPT) $(OPTFLAGS) -o nucleic.exe nucleic.mlt + rm -f nucleic.mlt +!else + $(CAMLOPT) $(OPTFLAGS) -o nucleic.exe nucleic.ml +!endif + +# KB + +BYTE_KB=KB\terms.cmo KB\equations.cmo KB\kb.cmo KB\orderings.cmo KB\kbmain.cmo +CODE_KB=$(BYTE_KB:.cmo=.cmx) + +kb.byt: $(BYTE_KB) + $(CAMLC) -I KB $(BYTE_KB) -o kb.byt +kb.exe: $(CODE_KB) + $(CAMLOPT) $(OPTFLAGS) -I KB $(CODE_KB) -o kb.exe + +clean:: + rm -f KB\*.cm* KB\*.obj KB\*.asm + +# Genlex + +BYTE_GENLEX=Lex\syntax.cmo Lex\scan_aux.cmo Lex\scanner.cmo Lex\gram_aux.cmo \ + Lex\grammar.cmo Lex\lexgen.cmo Lex\output.cmo Lex\main.cmo +CODE_GENLEX=$(BYTE_GENLEX:.cmo=.cmx) + +genlex.byt: $(BYTE_GENLEX) + $(CAMLC) -I Lex $(BYTE_GENLEX) -o genlex.byt +genlex.exe: $(CODE_GENLEX) + $(CAMLOPT) $(OPTFLAGS) -I Lex $(CODE_GENLEX) -o genlex.exe + +clean:: + rm -f Lex\*.cm* Lex\*.obj Lex\*.asm + +Lex\grammar.ml Lex\grammar.mli: Lex\grammar.mly + $(CAMLYACC) $(YACCFLAGS) Lex\grammar.mly + +clean:: + rm -f Lex\grammar.ml Lex\grammar.mli +beforedepend:: Lex\grammar.ml Lex\grammar.mli + +Lex\scanner.ml: Lex\scanner.mll + $(CAMLLEX) Lex\scanner.mll + +clean:: + rm -f Lex\scanner.ml +beforedepend:: Lex\scanner.ml + +# "Fast" stuff + +quicksort.fast.byt: quicksort.ml + cp quicksort.ml quicksort.fast.ml + $(CAMLC) -unsafe -o quicksort.fast.byt quicksort.fast.ml + rm -f quicksort.fast.ml + +soli.fast.byt: soli.ml + cp soli.ml soli.fast.ml + $(CAMLC) -unsafe -o soli.fast.byt soli.fast.ml + rm -f soli.fast.ml + +fft.fast.byt: fft.ml + cp fft.ml fft.fast.ml + $(CAMLC) -unsafe -o fft.fast.byt fft.fast.ml + rm -f fft.fast.ml + +quicksort.fast.exe: quicksort.ml + cp quicksort.ml quicksort.fast.ml + $(CAMLOPT) $(OPTFLAGS) -unsafe -o quicksort.fast.exe quicksort.fast.ml + rm -f quicksort.fast.ml + +soli.fast.exe: soli.ml + cp soli.ml soli.fast.ml + $(CAMLOPT) $(OPTFLAGS) -unsafe -o soli.fast.exe soli.fast.ml + rm -f soli.fast.ml + +fft.fast.exe: fft.ml + cp fft.ml fft.fast.ml + $(CAMLOPT) $(OPTFLAGS) -unsafe -o fft.fast.exe fft.fast.ml + rm -f fft.fast.ml + +# Common rules + +.SUFFIXES: +.SUFFIXES: .mli .ml .cmi .cmo .cmx .byt .exe + +.ml.byt: + $(CAMLC) -o $*.byt $< + +.ml.exe: + $(CAMLOPT) $(OPTFLAGS) -o $*.exe $< + +.mli.cmi: + $(CAMLC) -c $< + +.ml.cmo: + $(CAMLC) -c $< + +.ml.cmx: + $(CAMLOPT) $(OPTFLAGS) -c $< + +$(BYTE_EXE) $(BYTE_KB) $(BYTE_GENLEX): ..\cslc +$(BYTE_EXE): ..\stdlib\stdlib.cma +$(CODE_EXE) $(CODE_KB) $(CODE_GENLEX): ..\cslopt +$(CODE_EXE): ..\stdlib\stdlib.cmxa ..\stdlib\libasmrun.lib + +clean:: + rm -f *.byt *.exe + rm -f *.cm* *.obj *.asm + +# Regression test + +.SUFFIXES: .btst .etst + +.byt.btst: + $(CAMLRUN) $*.byt > %temp%\test.out + fc /l %temp%\test.out Results\$*.out +.exe.etst: + $*.exe > %temp%\test.out + fc /l %temp%\test.out Results\$*.out + +clean:: + rm -f %temp%\test.out + +genlex.btst: + $(CAMLRUN) genlex.byt Lex/testscanner.mll +genlex.etst: + genlex.exe Lex/testscanner.mll + +FFT_TEST=gawk "$$2 >= 1e-9 { exit 2; }" +fft.btst: + $(CAMLRUN) fft.byt | $(FFT_TEST) +fft.fast.btst: + $(CAMLRUN) fft.fast.byt | $(FFT_TEST) +fft.etst: + fft.exe | $(FFT_TEST) +fft.fast.etst: + fft.fast.exe | $(FFT_TEST) + +test: codetest +bytetest: $(BYTE_EXE:.byt=.btst) +codetest: $(CODE_EXE:.exe=.etst) + +clean:: + rm -f Lex\testscanner.ml + +# Dependencies + +depend: beforedepend + $(CAMLDEP) -I KB -I Lex *.mli *.ml KB\*.mli KB\*.ml Lex\*.mli Lex\*.ml > .depend + +!include .depend + diff --git a/testasmcomp/Makefile.nt b/testasmcomp/Makefile.nt new file mode 100644 index 000000000..7bea9ca90 --- /dev/null +++ b/testasmcomp/Makefile.nt @@ -0,0 +1,134 @@ +!include ..\config\Makefile.nt + +CAMLC=..\boot\cslrun ..\boot\cslc -I ..\boot +COMPFLAGS=$(INCLUDES) +LINKFLAGS= +CAMLYACC=..\boot\cslyacc +YACCFLAGS= +CAMLLEX=..\boot\cslrun ..\boot\csllex +CAMLDEP=..\boot\cslrun ..\tools\csldep +DEPFLAGS=$(INCLUDES) +CAMLRUN=..\boot\cslrun + +CODEGEN=.\codegen +CC=$(NATIVECC) +CFLAGS= + +PROGS=fib.exe tak.exe quicksort.exe quicksort2.exe soli.exe integr.exe \ + arith.exe checkbound.exe + +all: codegen $(PROGS) + +INCLUDES=-I ..\utils -I ..\typing -I ..\asmcomp + +OTHEROBJS=..\utils\misc.cmo ..\utils\tbl.cmo \ + ..\utils\clflags.cmo ..\utils\config.cmo \ + ..\parsing\location.cmo \ + ..\typing\ident.cmo ..\typing\path.cmo ..\typing\subst.cmo \ + ..\typing\primitive.cmo ..\typing\predef.cmo ..\typing\printtyp.cmo \ + ..\typing\datarepr.cmo ..\typing\env.cmo \ + ..\bytecomp\lambda.cmo \ + ..\asmcomp\arch.cmo ..\asmcomp\cmm.cmo ..\asmcomp\printcmm.cmo \ + ..\asmcomp\clambda.cmo ..\asmcomp\compilenv.cmo \ + ..\asmcomp\reg.cmo ..\asmcomp\mach.cmo ..\asmcomp\proc.cmo \ + ..\asmcomp\closure.cmo ..\asmcomp\cmmgen.cmo \ + ..\asmcomp\printmach.cmo ..\asmcomp\selection.cmo ..\asmcomp\liveness.cmo \ + ..\asmcomp\spill.cmo ..\asmcomp\split.cmo \ + ..\asmcomp\interf.cmo ..\asmcomp\coloring.cmo ..\asmcomp\reload.cmo \ + ..\asmcomp\linearize.cmo ..\asmcomp\scheduling.cmo \ + ..\asmcomp\printlinear.cmo ..\asmcomp\emitaux.cmo \ + ..\asmcomp\emit.cmo ..\asmcomp\asmgen.cmo + +OBJS=parsecmmaux.cmo parsecmm.cmo lexcmm.cmo main.cmo + +codegen: $(OTHEROBJS) $(OBJS) + $(CAMLC) $(LINKFLAGS) -o codegen $(OTHEROBJS) $(OBJS) +clean:: + rm -f codegen + +# The parser + +parsecmm.mli parsecmm.ml: parsecmm.mly + $(CAMLYACC) $(YACCFLAGS) parsecmm.mly + +clean:: + rm -f parsecmm.mli parsecmm.ml parsecmm.output + +beforedepend:: parsecmm.mli parsecmm.ml + +# The lexer + +lexcmm.ml: lexcmm.mll + $(CAMLLEX) lexcmm.mll + +clean:: + rm -f lexcmm.ml + +beforedepend:: lexcmm.ml + +# The test programs + +$(PROGS:.exe=.obj): codegen + +fib.exe: main.c fib.obj $(ARCH).obj + $(CC) $(CFLAGS) -o fib.exe -DINT_INT -DFUN=fib main.c fib.obj $(ARCH).obj + +tak.exe: main.c tak.obj $(ARCH).obj + $(CC) $(CFLAGS) -o tak.exe -DUNIT_INT -DFUN=takmain main.c tak.obj $(ARCH).obj + +quicksort.exe: main.c quicksort.obj $(ARCH).obj + $(CC) $(CFLAGS) -o quicksort.exe -DSORT -DFUN=quicksort main.c quicksort.obj $(ARCH).obj + +quicksort2.exe: main.c quicksort2.obj $(ARCH).obj + $(CC) $(CFLAGS) -o quicksort2.exe -DSORT -DFUN=quicksort main.c quicksort2.obj $(ARCH).obj + +soli.exe: main.c soli.obj $(ARCH).obj + $(CC) $(CFLAGS) -o soli.exe -DUNIT_INT -DFUN=solitaire main.c soli.obj $(ARCH).obj + +integr.exe: main.c integr.obj $(ARCH).obj + $(CC) $(CFLAGS) -o integr.exe -DINT_FLOAT -DFUN=test main.c integr.obj $(ARCH).obj + +tagged-fib.exe: main.c tagged-fib.obj $(ARCH).obj + $(CC) $(CFLAGS) -o tagged-fib.exe -DINT_INT -DFUN=fib main.c tagged-fib.obj $(ARCH).obj + +tagged-tak.exe: main.c tagged-tak.obj $(ARCH).obj + $(CC) $(CFLAGS) -o tagged-tak.exe -DUNIT_INT -DFUN=takmain main.c tagged-tak.obj $(ARCH).obj + +tagged-quicksort.exe: main.c tagged-quicksort.obj $(ARCH).obj + $(CC) $(CFLAGS) -o tagged-quicksort.exe -DSORT -DFUN=quicksort main.c tagged-quicksort.obj $(ARCH).obj + +tagged-integr.exe: main.c tagged-integr.obj $(ARCH).obj + $(CC) $(CFLAGS) -o tagged-integr.exe -DINT_FLOAT -DFUN=test main.c tagged-integr.obj $(ARCH).obj + +arith.exe: mainarith.c arith.obj $(ARCH).obj + $(CC) $(CFLAGS) -o arith.exe mainarith.c arith.obj $(ARCH).obj + +checkbound.exe: main.c checkbound.obj $(ARCH).obj + $(CC) $(CFLAGS) -o checkbound.exe -DCHECKBOUND main.c checkbound.obj $(ARCH).obj + +$(ARCH).obj: $(ARCH)nt.asm + $(AS) $(ASFLAGS) /c /Fo$(ARCH).obj $(ARCH)nt.asm + +.SUFFIXES: +.SUFFIXES: .cmm .obj .ml .mli .cmo .cmi + +.ml.cmo: + $(CAMLC) $(COMPFLAGS) -c $< + +.mli.cmi: + $(CAMLC) $(COMPFLAGS) -c $< + +.cmm.obj: + $(CAMLRUN) $(CODEGEN) $*.cmm > $*.asm + $(AS) $(ASFLAGS) /c $*.asm + +clean:: + rm -f *.exe *.cm* *.obj *~ + rm -f $(PROGS:.exe=.asm) + +$(PROGS:.exe=.obj): $(CODEGEN) + +depend: beforedepend + $(CAMLDEP) $(DEPFLAGS) *.mli *.ml > .depend + +!include .depend diff --git a/testasmcomp/i386nt.asm b/testasmcomp/i386nt.asm new file mode 100644 index 000000000..1bcbf84f8 --- /dev/null +++ b/testasmcomp/i386nt.asm @@ -0,0 +1,66 @@ +;********************************************************************* +; +; Caml Special Light +; +; Xavier Leroy, projet Cristal, INRIA Rocquencourt +; +; Copyright 1995 Institut National de Recherche en Informatique et +; Automatique. Distributed only by permission. +; +;********************************************************************* + +; $Id$ + + .386 + .MODEL FLAT + + .CODE + PUBLIC _call_gen_code + ALIGN 4 +_call_gen_code: + push ebp + mov ebp, esp + push ebx + push esi + push edi + mov eax, [ebp+12] + mov ebx, [ebp+16] + mov ecx, [ebp+20] + mov edx, [ebp+24] + call DWORD PTR [ebp+8] + pop edi + pop esi + pop ebx + pop ebp + ret + + PUBLIC _caml_c_call + ALIGN 4 +_caml_c_call: + ffree st(0) + ffree st(1) + ffree st(2) + ffree st(3) + jmp eax + + PUBLIC _caml_call_gc + PUBLIC _caml_alloc + PUBLIC _caml_alloc1 + PUBLIC _caml_alloc2 + PUBLIC _caml_alloc3 +_caml_call_gc: +_caml_alloc: +_caml_alloc1: +_caml_alloc2: +_caml_alloc3: + int 3 + + .DATA + PUBLIC _caml_exception_pointer +_caml_exception_pointer dword 0 + PUBLIC _young_ptr +_young_ptr dword 0 + PUBLIC _young_limit +_young_limit dword 0 + + END diff --git a/testasmcomp/mainarith.c b/testasmcomp/mainarith.c index 5290c35a5..af233c889 100644 --- a/testasmcomp/mainarith.c +++ b/testasmcomp/mainarith.c @@ -284,9 +284,9 @@ int main(argc, argv) } } weird[0] = 0.0; - weird[1] = 1.0 / 0.0; /* +infty */ - weird[2] = -1.0 / 0.0; /* -infty */ - weird[3] = 0.0 / 0.0; /* NaN */ + weird[1] = 1.0 / weird[0]; /* +infty */ + weird[2] = -1.0 / weird[0]; /* -infty */ + weird[3] = 0.0 / weird[0]; /* NaN */ for (x = 0; x < 4; x++) { for (y = 0; y < 4; y++) { f = weird[x]; g = weird[y]; do_test(); diff --git a/tools/Makefile.nt b/tools/Makefile.nt new file mode 100644 index 000000000..87cada26c --- /dev/null +++ b/tools/Makefile.nt @@ -0,0 +1,111 @@ +!include ..\config\Makefile.nt + +CAMLRUN=..\boot\cslrun +CAMLC=$(CAMLRUN) ..\boot\cslc -I ..\boot +CAMLLEX=$(CAMLRUN) ..\boot\csllex +INCLUDES=-I ..\utils -I ..\parsing -I ..\typing -I ..\bytecomp -I ..\asmcomp +COMPFLAGS=$(INCLUDES) +LINKFLAGS=$(INCLUDES) + +all: csldep cslprof + +# The dependency generator + +CAMLDEP=csldep.cmo + +csldep: $(CAMLDEP) + $(CAMLC) $(LINKFLAGS) -o csldep misc.cmo $(CAMLDEP) + +clean:: + rm -f csldep + +csldep.ml: csldep.mll + $(CAMLLEX) csldep.mll + +clean:: + rm -f csldep.ml + +install:: + cp csldep $(BINDIR)\csldep.exe + +beforedepend:: csldep + +# The profiler + +CSLPROF=cslprof.cmo +CSLPROF_IMPORTS=misc.cmo config.cmo clflags.cmo terminfo.cmo \ + location.cmo longident.cmo pstream.cmo parser.cmo lexer.cmo parse.cmo + +cslprof: $(CSLPROF) profiling.cmo + $(CAMLC) $(LINKFLAGS) -o cslprof $(CSLPROF_IMPORTS) $(CSLPROF) + +install:: + cp cslprof $(BINDIR)\cslprof.exe + cp cslcp $(BINDIR)\cslcp + cp profiling.cmi profiling.cmo $(LIBDIR) + +clean:: + rm -f cslprof + +# To make custom toplevels + +install:: + cp cslmktop $(BINDIR)\cslmktop + +# The bytecode disassembler + +DUMPOBJ=opnames.cmo dumpobj.cmo + +dumpobj: $(DUMPOBJ) + $(CAMLC) $(LINKFLAGS) -o dumpobj misc.cmo tbl.cmo config.cmo ident.cmo opcodes.cmo runtimedef.cmo $(DUMPOBJ) + +clean:: + rm -f dumpobj + +opnames.ml: ..\byterun\instruct.h + sed -e '/\/\*/d' \ + -e 's\enum \(.*\) {/let names_of_\1 = [|/' \ + -e 's/};$$/ |]/' \ + -e 's/\([A-Z][A-Z_0-9a-z]*\)/"\1"/g' \ + -e 's/,/;/g' \ + ..\byterun\instruct.h > opnames.ml + +clean:: + rm -f opnames.ml + +beforedepend:: opnames.ml + +# Dump .cmx files + +dumpapprox: dumpapprox.cmo + $(CAMLC) $(LINKFLAGS) -o dumpapprox config.cmo dumpapprox.cmo + +clean:: + rm -f dumpapprox + +# Print imported interfaces for .cmo files + +objinfo: objinfo.cmo + $(CAMLC) $(LINKFLAGS) -o objinfo config.cmo objinfo.cmo + +clean:: + rm -f objinfo + +# Common stuff + +.SUFFIXES: +.SUFFIXES: .ml .cmo .mli .cmi + +.ml.cmo: + $(CAMLC) -c $(COMPFLAGS) $< + +.mli.cmi: + $(CAMLC) -c $(COMPFLAGS) $< + +clean:: + rm -f *.cmo *.cmi + +depend: beforedepend + $(CAMLRUN) .\csldep $(INCLUDES) *.mli *.ml > .depend + +!include .depend diff --git a/yacc/Makefile.nt b/yacc/Makefile.nt new file mode 100644 index 000000000..86231f37e --- /dev/null +++ b/yacc/Makefile.nt @@ -0,0 +1,32 @@ +# Makefile for the parser generator. + +!include ..\config\Makefile.nt + +CC=$(BYTECC) +CFLAGS=-DNDEBUG -DNO_UNIX $(BYTECCCOMPOPTS) + +OBJS= closure.obj error.obj lalr.obj lr0.obj main.obj mkpar.obj output.obj reader.obj \ + skeleton.obj symtab.obj verbose.obj warshall.obj + +all: cslyacc.exe + +cslyacc.exe: $(OBJS) + $(CC) $(CFLAGS) $(CCLINKFLAGS) -o cslyacc.exe $(OBJS) + +clean: + rm -f *.obj cslyacc.exe *~ + +depend: + +closure.obj: defs.h +error.obj: defs.h +lalr.obj: defs.h +lr0.obj: defs.h +main.obj: defs.h +mkpar.obj: defs.h +output.obj: defs.h +reader.obj: defs.h +skeleton.obj: defs.h +symtab.obj: defs.h +verbose.obj: defs.h +warshall.obj: defs.h |