PR#5179: giant steps towards a Mingw64 port.

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@11927 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Xavier Leroy 2011-12-21 16:31:01 +00:00
parent 253e88bc67
commit ac0aa0778d
9 changed files with 340 additions and 79 deletions

View File

@ -23,11 +23,8 @@ open Mach
open Linearize
open Emitaux
let macosx =
match Config.system with
| "macosx" -> true
| _ -> false
let macosx = (Config.system = "macosx")
let mingw64 = (Config.system = "mingw64")
(* Tradeoff between code size and code speed *)
@ -64,17 +61,17 @@ let emit_symbol s =
Emitaux.emit_symbol '$' s
let emit_call s =
if !Clflags.dlcode && not macosx
if !Clflags.dlcode && not macosx && not mingw64
then `call {emit_symbol s}@PLT`
else `call {emit_symbol s}`
let emit_jump s =
if !Clflags.dlcode && not macosx
if !Clflags.dlcode && not macosx && not mingw64
then `jmp {emit_symbol s}@PLT`
else `jmp {emit_symbol s}`
let load_symbol_addr s =
if !Clflags.dlcode
if !Clflags.dlcode && not mingw64
then `movq {emit_symbol s}@GOTPCREL(%rip)`
else if !pic_code
then `leaq {emit_symbol s}(%rip)`
@ -604,9 +601,12 @@ let emit_instr fallthrough i =
` movslq ({emit_reg tmp1}, {emit_reg i.arg.(0)}, 4), {emit_reg tmp2}\n`;
` addq {emit_reg tmp2}, {emit_reg tmp1}\n`;
` jmp *{emit_reg tmp1}\n`;
if macosx
then ` .const\n`
else ` .section .rodata\n`;
if macosx then
` .const\n`
else if mingw64 then
` .section .rdata,\"dr\"\n`
else
` .section .rodata\n`;
emit_align 4;
`{emit_label lbl}:`;
for i = 0 to Array.length jumptbl - 1 do
@ -701,9 +701,12 @@ let fundecl fundecl =
| _ -> ()
end;
if !float_constants <> [] then begin
if macosx
then ` .literal8\n`
else ` .section .rodata.cst8,\"a\",@progbits\n`;
if macosx then
` .literal8\n`
else if mingw64 then
` .section .rdata,\"dr\"\n`
else
` .section .rodata.cst8,\"a\",@progbits\n`;
List.iter emit_float_constant !float_constants
end
@ -749,9 +752,11 @@ let begin_assembly() =
if !Clflags.dlcode then begin
(* from amd64.S; could emit these constants on demand *)
if macosx then
` .literal16\n`
` .literal16\n`
else if mingw64 then
` .section .rdata,\"dr\"\n`
else
` .section .rodata.cst8,\"a\",@progbits\n`;
` .section .rodata.cst8,\"a\",@progbits\n`;
emit_align 16;
`{emit_symbol "caml_negf_mask"}: .quad 0x8000000000000000, 0\n`;
emit_align 16;

View File

@ -54,6 +54,9 @@ amd64nt.obj: amd64nt.asm
i386.o: i386.S
$(CC) -c -DSYS_$(SYSTEM) i386.S
amd64.o: amd64.S
$(CC) -c -DSYS_$(SYSTEM) amd64.S
install:
cp libasmrun.$(A) $(LIBDIR)

View File

@ -18,7 +18,7 @@
/* PIC mode support based on contribution by Paul Stravers (see PR#4795) */
#ifdef SYS_macosx
#if defined(SYS_macosx)
#define LBL(x) L##x
#define G(r) _##r
@ -32,6 +32,20 @@
.align FUNCTION_ALIGN; \
name:
#elif defined(SYS_mingw64)
#define LBL(x) .L##x
#define G(r) r
#undef GREL
#define GCALL(r) r
#define FUNCTION_ALIGN 4
#define EIGHT_ALIGN 8
#define SIXTEEN_ALIGN 16
#define FUNCTION(name) \
.globl name; \
.align FUNCTION_ALIGN; \
name:
#else
#define LBL(x) .L##x
@ -49,7 +63,7 @@
#endif
#ifdef __PIC__
#if defined(__PIC__) && !defined(SYS_mingw64)
/* Position-independent operations on global variables. */
@ -120,6 +134,88 @@
leaq 8+OFFSET(%rsp), %rax ; \
STORE_VAR(%rax,caml_bottom_of_stack)
#endif
/* Save and restore all callee-save registers on stack.
Keep the stack 16-aligned. */
#if defined(SYS_mingw64)
/* Win64 API: callee-save regs are rbx, rbp, rsi, rdi, r12-r15, xmm6-xmm15 */
#define PUSH_CALLEE_SAVE_REGS \
pushq %rbx; \
pushq %rbp; \
pushq %rsi; \
pushq %rdi; \
pushq %r12; \
pushq %r13; \
pushq %r14; \
pushq %r15; \
subq $(8+10*16), %rsp; \
movupd %xmm6, 0*16(%rsp); \
movupd %xmm7, 1*16(%rsp); \
movupd %xmm8, 2*16(%rsp); \
movupd %xmm9, 3*16(%rsp); \
movupd %xmm10, 4*16(%rsp); \
movupd %xmm11, 5*16(%rsp); \
movupd %xmm12, 6*16(%rsp); \
movupd %xmm13, 7*16(%rsp); \
movupd %xmm14, 8*16(%rsp); \
movupd %xmm15, 9*16(%rsp)
#define POP_CALLEE_SAVE_REGS \
movupd 0*16(%rsp), %xmm6; \
movupd 1*16(%rsp), %xmm7; \
movupd 2*16(%rsp), %xmm8; \
movupd 3*16(%rsp), %xmm9; \
movupd 4*16(%rsp), %xmm10; \
movupd 5*16(%rsp), %xmm11; \
movupd 6*16(%rsp), %xmm12; \
movupd 7*16(%rsp), %xmm13; \
movupd 8*16(%rsp), %xmm14; \
movupd 9*16(%rsp), %xmm15; \
addq $(8+10*16), %rsp; \
popq %r15; \
popq %r14; \
popq %r13; \
popq %r12; \
popq %rdi; \
popq %rsi; \
popq %rbp; \
popq %rbx
#else
/* Unix API: callee-save regs are rbx, rbp, r12-r15 */
#define PUSH_CALLEE_SAVE_REGS \
pushq %rbx; \
pushq %rbp; \
pushq %r12; \
pushq %r13; \
pushq %r14; \
pushq %r15; \
subq $8, %rsp
#define POP_CALLEE_SAVE_REGS \
addq $8, %rsp; \
popq %r15; \
popq %r14; \
popq %r13; \
popq %r12; \
popq %rbp; \
popq %rbx
#endif
#ifdef SYS_mingw64
/* Calls from Caml to C must reserve 32 bytes of extra stack space */
# define PREPARE_FOR_C_CALL subq $32, %rsp
# define CLEANUP_AFTER_C_CALL addq $32, %rsp
#else
# define PREPARE_FOR_C_CALL
# define CLEANUP_AFTER_C_CALL
#endif
.text
@ -166,7 +262,9 @@ LBL(caml_call_gc):
movsd %xmm14, 14*8(%rsp)
movsd %xmm15, 15*8(%rsp)
/* Call the garbage collector */
PREPARE_FOR_C_CALL
call GCALL(caml_garbage_collection)
CLEANUP_AFTER_C_CALL
/* Restore caml_young_ptr, caml_exception_pointer */
LOAD_VAR(caml_young_ptr, %r15)
LOAD_VAR(caml_exception_pointer, %r14)
@ -269,7 +367,9 @@ LBL(caml_c_call):
STORE_VAR(%r15, caml_young_ptr)
STORE_VAR(%r14, caml_exception_pointer)
/* Call the function (address in %rax) */
PREPARE_FOR_C_CALL
call *%rax
CLEANUP_AFTER_C_CALL
/* Reload alloc ptr */
LOAD_VAR(caml_young_ptr, %r15)
/* Return to caller */
@ -280,13 +380,7 @@ LBL(caml_c_call):
FUNCTION(G(caml_start_program))
/* Save callee-save registers */
pushq %rbx
pushq %rbp
pushq %r12
pushq %r13
pushq %r14
pushq %r15
subq $8, %rsp /* stack 16-aligned */
PUSH_CALLEE_SAVE_REGS
/* Initial entry point is G(caml_program) */
leaq GCALL(caml_program)(%rip), %r12
/* Common code for caml_start_program and caml_callback* */
@ -320,13 +414,7 @@ LBL(109):
POP_VAR(caml_gc_regs)
addq $8, %rsp
/* Restore callee-save registers. */
addq $8, %rsp
popq %r15
popq %r14
popq %r13
popq %r12
popq %rbp
popq %rbx
POP_CALLEE_SAVE_REGS
/* Return to caller. */
ret
LBL(108):
@ -335,6 +423,20 @@ LBL(108):
orq $2, %rax
jmp LBL(109)
/* Registers holding arguments of C functions. */
#ifdef SYS_mingw64
#define C_ARG_1 %rcx
#define C_ARG_2 %rdx
#define C_ARG_3 %r8
#define C_ARG_4 %r9
#else
#define C_ARG_1 %rdi
#define C_ARG_2 %rsi
#define C_ARG_3 %rdx
#define C_ARG_4 %rcx
#endif
/* Raise an exception from Caml */
FUNCTION(G(caml_raise_exn))
@ -345,10 +447,11 @@ FUNCTION(G(caml_raise_exn))
ret
LBL(110):
movq %rax, %r12 /* Save exception bucket */
movq %rax, %rdi /* arg 1: exception bucket */
movq 0(%rsp), %rsi /* arg 2: pc of raise */
leaq 8(%rsp), %rdx /* arg 3: sp of raise */
movq %r14, %rcx /* arg 4: sp of handler */
movq %rax, C_ARG_1 /* arg 1: exception bucket */
movq 0(%rsp), C_ARG_2 /* arg 2: pc of raise */
leaq 8(%rsp), C_ARG_3 /* arg 3: sp of raise */
movq %r14, C_ARG_4 /* arg 4: sp of handler */
PREPARE_FOR_C_CALL /* no need to cleanup after */
call GCALL(caml_stash_backtrace)
movq %r12, %rax /* Recover exception bucket */
movq %r14, %rsp
@ -360,17 +463,18 @@ LBL(110):
FUNCTION(G(caml_raise_exception))
TESTL_VAR($1, caml_backtrace_active)
jne LBL(111)
movq %rdi, %rax
movq C_ARG_1, %rax
LOAD_VAR(caml_exception_pointer, %rsp) /* Cut stack */
popq %r14 /* Recover previous exception handler */
LOAD_VAR(caml_young_ptr, %r15) /* Reload alloc ptr */
ret
LBL(111):
movq %rdi, %r12 /* Save exception bucket */
movq C_ARG_1, %r12 /* Save exception bucket */
/* arg 1: exception bucket */
LOAD_VAR(caml_last_return_address,%rsi) /* arg 2: pc of raise */
LOAD_VAR(caml_bottom_of_stack,%rdx) /* arg 3: sp of raise */
LOAD_VAR(caml_exception_pointer,%rcx) /* arg 4: sp of handler */
LOAD_VAR(caml_last_return_address,C_ARG_2) /* arg 2: pc of raise */
LOAD_VAR(caml_bottom_of_stack,C_ARG_3) /* arg 3: sp of raise */
LOAD_VAR(caml_exception_pointer,C_ARG_4) /* arg 4: sp of handler */
PREPARE_FOR_C_CALL /* no need to cleanup after */
call GCALL(caml_stash_backtrace)
movq %r12, %rax /* Recover exception bucket */
LOAD_VAR(caml_exception_pointer,%rsp)
@ -382,49 +486,31 @@ LBL(111):
FUNCTION(G(caml_callback_exn))
/* Save callee-save registers */
pushq %rbx
pushq %rbp
pushq %r12
pushq %r13
pushq %r14
pushq %r15
subq $8, %rsp /* stack 16-aligned */
PUSH_CALLEE_SAVE_REGS
/* Initial loading of arguments */
movq %rdi, %rbx /* closure */
movq %rsi, %rax /* argument */
movq 0(%rbx), %r12 /* code pointer */
movq C_ARG_1, %rbx /* closure */
movq C_ARG_2, %rax /* argument */
movq 0(%rbx), %r12 /* code pointer */
jmp LBL(caml_start_program)
FUNCTION(G(caml_callback2_exn))
/* Save callee-save registers */
pushq %rbx
pushq %rbp
pushq %r12
pushq %r13
pushq %r14
pushq %r15
subq $8, %rsp /* stack 16-aligned */
PUSH_CALLEE_SAVE_REGS
/* Initial loading of arguments */
/* closure stays in %rdi */
movq %rsi, %rax /* first argument */
movq %rdx, %rbx /* second argument */
movq C_ARG_1, %rdi /* closure -- no op with Unix conventions */
movq C_ARG_2, %rax /* first argument */
movq C_ARG_3, %rbx /* second argument */
leaq GCALL(caml_apply2)(%rip), %r12 /* code pointer */
jmp LBL(caml_start_program)
FUNCTION(G(caml_callback3_exn))
/* Save callee-save registers */
pushq %rbx
pushq %rbp
pushq %r12
pushq %r13
pushq %r14
pushq %r15
subq $8, %rsp /* stack 16-aligned */
PUSH_CALLEE_SAVE_REGS
/* Initial loading of arguments */
movq %rsi, %rax /* first argument */
movq %rdx, %rbx /* second argument */
movq %rdi, %rsi /* closure */
movq %rcx, %rdi /* third argument */
movq C_ARG_2, %rax /* first argument */
movq C_ARG_3, %rbx /* second argument */
movq C_ARG_1, %rsi /* closure */
movq C_ARG_4, %rdi /* third argument */
leaq GCALL(caml_apply3)(%rip), %r12 /* code pointer */
jmp LBL(caml_start_program)
@ -442,8 +528,10 @@ G(caml_system__frametable):
.value 0 /* no roots here */
.align EIGHT_ALIGN
#ifdef SYS_macosx
#if defined(SYS_macosx)
.literal16
#elif defined(SYS_mingw64)
.section .rdata,"dr"
#else
.section .rodata.cst8,"a",@progbits
#endif

View File

@ -513,7 +513,11 @@ let link objfiles output_name =
extern \"C\" {\n\
#endif\n\
#ifdef _WIN64\n\
#ifdef __MINGW32__\n\
typedef long long value;\n\
#else\n\
typedef __int64 value;\n\
#endif\n\
#else\n\
typedef long value;\n\
#endif\n";

View File

@ -125,7 +125,7 @@ static void print_token(struct parser_tables *tables, int state, value tok)
state, token_name(tables->names_block, Tag_val(tok)));
v = Field(tok, 0);
if (Is_long(v))
fprintf(stderr, "%ld", Long_val(v));
fprintf(stderr, "%" ARCH_INTNAT_PRINTF_FORMAT "d", Long_val(v));
else if (Tag_val(v) == String_tag)
fprintf(stderr, "%s", String_val(v));
else if (Tag_val(v) == Double_tag)

View File

@ -73,7 +73,7 @@ CAMLexport char * caml_format_exception(value exn)
if (i > start) add_string(&buf, ", ");
v = Field(bucket, i);
if (Is_long(v)) {
sprintf(intbuf, "%ld", Long_val(v));
sprintf(intbuf, "%" ARCH_INTNAT_PRINTF_FORMAT "d", Long_val(v));
add_string(&buf, intbuf);
} else if (Tag_val(v) == String_tag) {
add_char(&buf, '"');

161
config/Makefile.mingw64 Normal file
View File

@ -0,0 +1,161 @@
#########################################################################
# #
# OCaml #
# #
# Xavier Leroy, projet Cristal, INRIA Rocquencourt #
# #
# Copyright 1999 Institut National de Recherche en Informatique et #
# en Automatique. All rights reserved. This file is distributed #
# under the terms of the GNU Library General Public License, with #
# the special exception on linking described in file ../LICENSE. #
# #
#########################################################################
# $Id: Makefile.mingw 11319 2011-12-16 17:02:48Z xleroy $
# Configuration for Windows, Mingw compiler
######### General configuration
PREFIX=C:/ocamlmgw64
### Where to install the binaries
BINDIR=$(PREFIX)/bin
### Where to install the standard library
LIBDIR=$(PREFIX)/lib
### Where to install the stub DLLs
STUBLIBDIR=$(LIBDIR)/stublibs
### Where to install the info files
DISTRIB=$(PREFIX)
### Where to install the man pages
MANDIR=$(PREFIX)/man
########## Toolchain and OS dependencies
TOOLCHAIN=mingw
### Toolchain prefix
TOOLPREF=x86_64-w64-mingw32-
CCOMPTYPE=cc
O=o
A=a
S=s
SO=s.o
DO=d.o
EXE=.exe
EXT_DLL=.dll
EXT_OBJ=.$(O)
EXT_LIB=.$(A)
EXT_ASM=.$(S)
MANEXT=1
SHARPBANGSCRIPTS=false
PTHREAD_LINK=
X11_INCLUDES=
X11_LINK=
DBM_INCLUDES=
DBM_LINK=
BYTECCRPATH=
SUPPORTS_SHARED_LIBRARIES=true
SHAREDCCCOMPOPTS=
MKSHAREDLIBRPATH=
NATIVECCPROFOPTS=
NATIVECCRPATH=
ASM=$(TOOLPREF)as
ASPP=gcc
ASPPPROFFLAGS=
PROFILING=noprof
RUNTIMED=noruntimed
DYNLINKOPTS=
DEBUGGER=ocamldebugger
CC_PROFILE=
SYSTHREAD_SUPPORT=true
EXTRALIBS=
NATDYNLINK=true
CMXS=cmxs
RUNTIMED=noruntimed
########## Configuration for the bytecode compiler
### Which C compiler to use for the bytecode interpreter.
BYTECC=$(TOOLPREF)gcc
### Additional compile-time options for $(BYTECC). (For static linking.)
BYTECCCOMPOPTS=-O -mms-bitfields -Wall -Wno-unused
### Additional link-time options for $(BYTECC). (For static linking.)
BYTECCLINKOPTS=
### Additional compile-time options for $(BYTECC). (For building a DLL.)
DLLCCCOMPOPTS=-O -mms-bitfields -Wall -Wno-unused -DCAML_DLL
### Libraries needed
BYTECCLIBS=-lws2_32
NATIVECCLIBS=-lws2_32
### How to invoke the C preprocessor
CPP=$(BYTECC) -E
### Flexlink
FLEXLINK=flexlink -chain mingw64
FLEXDIR=$(shell $(FLEXLINK) -where)
IFLEXDIR=-I"$(FLEXDIR)"
MKDLL=$(FLEXLINK)
MKEXE=$(FLEXLINK) -exe
MKMAINDLL=$(FLEXLINK) -maindll
### How to build a static library
MKLIB=rm -f $(1); $(TOOLPREF)ar rc $(1) $(2); $(RANLIB) $(1)
#ml let mklib out files opts = Printf.sprintf "rm -f %s && %sar rcs %s %s %s" out toolpref opts out files;;
### Canonicalize the name of a system library
SYSLIB=-l$(1)
#ml let syslib x = "-l"^x;;
### The ranlib command
RANLIB=$(TOOLPREF)ranlib
RANLIBCMD=$(TOOLPREF)ranlib
############# Configuration for the native-code compiler
### Name of architecture for the native-code compiler
ARCH=amd64
### Name of architecture model for the native-code compiler.
MODEL=default
### Name of operating system family for the native-code compiler.
SYSTEM=mingw64
### Which C compiler to use for the native-code compiler.
NATIVECC=$(BYTECC)
### Additional compile-time options for $(NATIVECC).
NATIVECCCOMPOPTS=-O -mms-bitfields -Wall -Wno-unused
### Additional link-time options for $(NATIVECC)
NATIVECCLINKOPTS=
### Build partially-linked object file
PACKLD=$(TOOLPREF)ld -r $(NATIVECCLINKOPTS) -o #there must be a space after this '-o'
############# Configuration for the contributed libraries
OTHERLIBRARIES=win32unix str num win32graph dynlink bigarray systhreads
### Name of the target architecture for the "num" library
BNG_ARCH=amd64
BNG_ASM_LEVEL=1
### Configuration for LablTk (not supported)
TK_DEFS=
TK_LINK=
############# Aliases for common commands
MAKEREC=$(MAKE) -f Makefile.nt
MAKECMD=$(MAKE)

View File

@ -28,7 +28,7 @@ clean::
rm -f *~
bng.$(O): bng.h bng_digit.c \
bng_alpha.c bng_amd64.c bng_ia32.c bng_mips.c bng_ppc.c bng_sparc.c
bng_amd64.c bng_ia32.c bng_ppc.c bng_sparc.c
depend:
sed -e 's/\.o/.$(O)/g' .depend > .depend.nt

View File

@ -20,15 +20,15 @@
#include "unixsupport.h"
#include <fcntl.h>
extern long _get_osfhandle(int);
extern int _open_osfhandle(long, int);
extern intptr_t _get_osfhandle(int);
extern int _open_osfhandle(intptr_t, int);
int win_CRT_fd_of_filedescr(value handle)
{
if (CRT_fd_val(handle) != NO_CRT_FD) {
return CRT_fd_val(handle);
} else {
int fd = _open_osfhandle((long) Handle_val(handle), O_BINARY);
int fd = _open_osfhandle((intptr_t) Handle_val(handle), O_BINARY);
if (fd == -1) uerror("channel_of_descr", Nothing);
CRT_fd_val(handle) = fd;
return fd;