Debut du portage Windows NT/95
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@636 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
9843ff4081
commit
84ffb16ed7
3
Makefile
3
Makefile
|
@ -237,6 +237,9 @@ utils/config.ml: utils/config.mlp config/Makefile
|
|||
-e 's|%%ARCH%%|$(ARCH)|' \
|
||||
-e 's|%%MODEL%%|$(MODEL)|' \
|
||||
-e 's|%%SYSTEM%%|$(SYSTEM)|' \
|
||||
-e 's|%%EXT_OBJ%%|.o|' \
|
||||
-e 's|%%EXT_ASM%%|.s|' \
|
||||
-e 's|%%EXT_LIB%%|.a|' \
|
||||
utils/config.mlp > utils/config.ml
|
||||
@chmod -w utils/config.ml
|
||||
|
||||
|
|
|
@ -14,6 +14,7 @@
|
|||
(* From lambda to assembly code *)
|
||||
|
||||
open Format
|
||||
open Config
|
||||
open Clflags
|
||||
open Misc
|
||||
open Cmm
|
||||
|
@ -80,8 +81,8 @@ let compile_phrase p =
|
|||
let compile_implementation prefixname lam =
|
||||
let asmfile =
|
||||
if !keep_asm_file
|
||||
then prefixname ^ ".s"
|
||||
else Filename.temp_file "camlasm" ".s" in
|
||||
then prefixname ^ ext_asm
|
||||
else Filename.temp_file "camlasm" ext_asm in
|
||||
let oc = open_out asmfile in
|
||||
begin try
|
||||
Emitaux.output_channel := oc;
|
||||
|
@ -94,7 +95,7 @@ let compile_implementation prefixname lam =
|
|||
if !keep_asm_file then () else remove_file asmfile;
|
||||
raise x
|
||||
end;
|
||||
if Proc.assemble_file asmfile (prefixname ^ ".o") <> 0
|
||||
if Proc.assemble_file asmfile (prefixname ^ ext_obj) <> 0
|
||||
then raise(Error(Assembler_error asmfile));
|
||||
if !keep_asm_file then () else remove_file asmfile
|
||||
|
||||
|
|
|
@ -19,7 +19,7 @@ open Compilenv
|
|||
|
||||
type error =
|
||||
File_not_found of string
|
||||
| Archiver_error
|
||||
| Archiver_error of string
|
||||
|
||||
exception Error of error
|
||||
|
||||
|
@ -35,10 +35,10 @@ let read_info name =
|
|||
The linker, which is the only one that reads .cmxa files, does not
|
||||
need the approximation. *)
|
||||
info.ui_approx <- Clambda.Value_unknown;
|
||||
(Filename.chop_suffix filename ".cmx" ^ ".o", (info, crc))
|
||||
(Filename.chop_suffix filename ".cmx" ^ ext_obj, (info, crc))
|
||||
|
||||
let create_archive file_list lib_name =
|
||||
let archive_name = Filename.chop_suffix lib_name ".cmxa" ^ ".a" in
|
||||
let archive_name = Filename.chop_suffix lib_name ".cmxa" ^ ext_lib in
|
||||
let outchan = open_out_bin lib_name in
|
||||
try
|
||||
output_string outchan cmxa_magic_number;
|
||||
|
@ -46,7 +46,7 @@ let create_archive file_list lib_name =
|
|||
List.split (List.map read_info file_list) in
|
||||
output_value outchan descr_list;
|
||||
if Proc.create_archive archive_name objfile_list <> 0
|
||||
then raise(Error(Archiver_error));
|
||||
then raise(Error(Archiver_error archive_name));
|
||||
close_out outchan
|
||||
with x ->
|
||||
close_out outchan;
|
||||
|
@ -59,6 +59,7 @@ open Format
|
|||
let report_error = function
|
||||
File_not_found name ->
|
||||
print_string "Cannot find file "; print_string name
|
||||
| Archiver_error ->
|
||||
print_string "Error while writing the .a file"
|
||||
| Archiver_error name ->
|
||||
print_string "Error while creating the library ";
|
||||
print_string name
|
||||
|
||||
|
|
|
@ -17,7 +17,7 @@ val create_archive: string list -> string -> unit
|
|||
|
||||
type error =
|
||||
File_not_found of string
|
||||
| Archiver_error
|
||||
| Archiver_error of string
|
||||
|
||||
exception Error of error
|
||||
|
||||
|
|
|
@ -164,25 +164,40 @@ let make_startup_file filename info_list =
|
|||
close_out oc
|
||||
|
||||
let call_linker file_list startup_file =
|
||||
let libname = "libasmrun" ^ ext_lib in
|
||||
let runtime_lib =
|
||||
try
|
||||
find_in_path !load_path "libasmrun.a"
|
||||
find_in_path !load_path libname
|
||||
with Not_found ->
|
||||
raise(Error(File_not_found "libasmrun.a")) in
|
||||
if Sys.command
|
||||
(Printf.sprintf
|
||||
"%s -I%s -o %s %s %s %s -L%s %s %s %s"
|
||||
Config.native_c_compiler
|
||||
Config.standard_library
|
||||
!Clflags.exec_name
|
||||
(String.concat " " (List.rev !Clflags.ccopts))
|
||||
(String.concat " " (List.rev file_list))
|
||||
startup_file
|
||||
Config.standard_library
|
||||
(String.concat " " (List.rev !Clflags.ccobjs))
|
||||
runtime_lib
|
||||
Config.c_libraries) <> 0
|
||||
then raise(Error Linking_error)
|
||||
raise(Error(File_not_found libname)) in
|
||||
let cmd =
|
||||
match Config.system with
|
||||
"win32" ->
|
||||
Printf.sprintf
|
||||
"%s -Fe %s -I%s %s %s %s %s %s %s"
|
||||
Config.native_c_compiler
|
||||
!Clflags.exec_name
|
||||
Config.standard_library
|
||||
(String.concat " " (List.rev !Clflags.ccopts))
|
||||
(String.concat " " (List.rev file_list))
|
||||
startup_file
|
||||
(String.concat " " (List.rev !Clflags.ccobjs))
|
||||
runtime_lib
|
||||
Config.c_libraries
|
||||
| _ ->
|
||||
Printf.sprintf
|
||||
"%s -o %s -I%s %s %s %s -L%s %s %s %s"
|
||||
Config.native_c_compiler
|
||||
!Clflags.exec_name
|
||||
Config.standard_library
|
||||
(String.concat " " (List.rev !Clflags.ccopts))
|
||||
(String.concat " " (List.rev file_list))
|
||||
startup_file
|
||||
Config.standard_library
|
||||
(String.concat " " (List.rev !Clflags.ccobjs))
|
||||
runtime_lib
|
||||
Config.c_libraries in
|
||||
if Sys.command cmd <> 0 then raise(Error Linking_error)
|
||||
|
||||
let object_file_name name =
|
||||
let file_name =
|
||||
|
@ -191,9 +206,9 @@ let object_file_name name =
|
|||
with Not_found ->
|
||||
fatal_error "Asmlink.object_file_name: not found" in
|
||||
if Filename.check_suffix file_name ".cmx" then
|
||||
Filename.chop_suffix file_name ".cmx" ^ ".o"
|
||||
Filename.chop_suffix file_name ".cmx" ^ ext_obj
|
||||
else if Filename.check_suffix file_name ".cmxa" then
|
||||
Filename.chop_suffix file_name ".cmxa" ^ ".a"
|
||||
Filename.chop_suffix file_name ".cmxa" ^ ext_lib
|
||||
else
|
||||
fatal_error "Asmlink.object_file_name: bad ext"
|
||||
|
||||
|
@ -205,9 +220,9 @@ let link objfiles =
|
|||
Array.iter remove_required Runtimedef.builtin_exceptions;
|
||||
if not (StringSet.is_empty !missing_globals) then
|
||||
raise(Error(Missing_implementations(StringSet.elements !missing_globals)));
|
||||
let startup = Filename.temp_file "camlstartup" ".s" in
|
||||
let startup = Filename.temp_file "camlstartup" ext_asm in
|
||||
make_startup_file startup units_tolink;
|
||||
let startup_obj = Filename.temp_file "camlstartup" ".o" in
|
||||
let startup_obj = Filename.temp_file "camlstartup" ext_obj in
|
||||
if Proc.assemble_file startup startup_obj <> 0 then
|
||||
raise(Error(Assembler_error startup));
|
||||
try
|
||||
|
|
|
@ -200,7 +200,7 @@ let link_bytecode objfiles exec_name copy_header =
|
|||
(* The table of global data *)
|
||||
let pos2 = pos_out outchan in
|
||||
output_value outchan (Symtable.initial_global_table());
|
||||
(* The List.map of global identifiers *)
|
||||
(* The map of global identifiers *)
|
||||
let pos3 = pos_out outchan in
|
||||
Symtable.output_global_map outchan;
|
||||
(* The trailer *)
|
||||
|
@ -216,6 +216,35 @@ let link_bytecode objfiles exec_name copy_header =
|
|||
remove_file exec_name;
|
||||
raise x
|
||||
|
||||
(* Build a custom runtime *)
|
||||
|
||||
let build_custom_runtime prim_name exec_name =
|
||||
match Config.system with
|
||||
"win32" ->
|
||||
Sys.command
|
||||
(Printf.sprintf
|
||||
"%s -Fe %s -I%s %s %s %s %s\\libcamlrun.lib %s"
|
||||
Config.bytecomp_c_compiler
|
||||
exec_name
|
||||
Config.standard_library
|
||||
(String.concat " " (List.rev !Clflags.ccopts))
|
||||
prim_name
|
||||
(String.concat " " (List.rev !Clflags.ccobjs))
|
||||
Config.standard_library
|
||||
Config.c_libraries)
|
||||
| _ ->
|
||||
Sys.command
|
||||
(Printf.sprintf
|
||||
"%s -o %s -I%s %s %s -L%s %s -lcamlrun %s"
|
||||
Config.bytecomp_c_compiler
|
||||
exec_name
|
||||
Config.standard_library
|
||||
(String.concat " " (List.rev !Clflags.ccopts))
|
||||
prim_name
|
||||
Config.standard_library
|
||||
(String.concat " " (List.rev !Clflags.ccobjs))
|
||||
Config.c_libraries)
|
||||
|
||||
(* Main entry point (build a custom runtime if needed) *)
|
||||
|
||||
let link objfiles =
|
||||
|
@ -227,18 +256,7 @@ let link objfiles =
|
|||
try
|
||||
link_bytecode objfiles bytecode_name false;
|
||||
Symtable.output_primitives prim_name;
|
||||
if Sys.command
|
||||
(Printf.sprintf
|
||||
"%s -I%s -o %s %s %s -L%s %s -lcamlrun %s"
|
||||
Config.bytecomp_c_compiler
|
||||
Config.standard_library
|
||||
!Clflags.exec_name
|
||||
(String.concat " " (List.rev !Clflags.ccopts))
|
||||
prim_name
|
||||
Config.standard_library
|
||||
(String.concat " " (List.rev !Clflags.ccobjs))
|
||||
Config.c_libraries)
|
||||
<> 0
|
||||
if build_custom_runtime prim_name !Clflags.exec_name <> 0
|
||||
then raise(Error Custom_runtime);
|
||||
let oc =
|
||||
open_out_gen [Open_wronly; Open_append; Open_binary] 0
|
||||
|
|
|
@ -110,17 +110,18 @@ value is_printable(chr) /* ML */
|
|||
value chr;
|
||||
{
|
||||
int c;
|
||||
static int iso_charset = -1;
|
||||
unsigned char * printable_chars;
|
||||
|
||||
#ifdef _WIN32
|
||||
printable_chars = printable_chars_iso;
|
||||
#else
|
||||
static int iso_charset = -1;
|
||||
if (iso_charset == -1) {
|
||||
char * lc_ctype = (char *) getenv("LC_CTYPE");
|
||||
if (lc_ctype != 0 && strcmp(lc_ctype, "iso_8859_1") == 0)
|
||||
iso_charset = 1;
|
||||
else
|
||||
iso_charset = 0;
|
||||
iso_charset = (lc_ctype != 0 && strcmp(lc_ctype, "iso_8859_1") == 0);
|
||||
}
|
||||
printable_chars = iso_charset ? printable_chars_iso : printable_chars_ascii;
|
||||
#endif
|
||||
c = Int_val(chr);
|
||||
return Val_bool(printable_chars[c >> 3] & (1 << (c & 7)));
|
||||
}
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
m.h
|
||||
s.h
|
||||
Makefile.h
|
||||
Makefile
|
||||
|
||||
|
|
|
@ -48,6 +48,14 @@ SHARPBANGSCRIPTS=true
|
|||
# On most platforms:
|
||||
#CCLIBS=-lcurses -ltermcap -lm
|
||||
|
||||
### How to invoke the C preprocessor
|
||||
# On most machines:
|
||||
#CPP=/lib/cpp -P
|
||||
# Under Solaris:
|
||||
#CPP=/usr/ccs/lib/cpp -P
|
||||
# Under FreeBSD:
|
||||
#CPP=cpp -P
|
||||
|
||||
### How to invoke ranlib
|
||||
# BSD-style:
|
||||
#RANLIB=ranlib
|
||||
|
@ -153,14 +161,6 @@ SHARPBANGSCRIPTS=true
|
|||
|
||||
############# Configuration for the contributed libraries
|
||||
|
||||
### How to invoke the C preprocessor
|
||||
# On most machines:
|
||||
#CPP=/lib/cpp -P
|
||||
# Under Solaris:
|
||||
#CPP=/usr/ccs/lib/cpp -P
|
||||
# Under FreeBSD:
|
||||
#CPP=cpp -P
|
||||
|
||||
### Name of the target architecture for the "num" library
|
||||
# Known targets:
|
||||
# 68K vax ns mips alpha pyramid i960
|
||||
|
|
|
@ -95,7 +95,8 @@ fi
|
|||
echo "Checking the sizes of integers and pointers..."
|
||||
set `sh runtest sizes.c`
|
||||
case "$1,$2,$3" in
|
||||
4,4,4) echo "OK, this is a regular 32 bit architecture.";;
|
||||
4,4,4) echo "OK, this is a regular 32 bit architecture."
|
||||
echo "#undef SIXTYFOUR" >> m.h;;
|
||||
4,8,8) echo "Wow! A 64 bit architecture!"
|
||||
echo "#define SIXTYFOUR" >> m.h;;
|
||||
8,*,*) echo "Wow! A 64 bit architecture!"
|
||||
|
@ -136,7 +137,8 @@ esac
|
|||
|
||||
sh runtest dblalign.c
|
||||
case $? in
|
||||
0) echo "Doubles can be word-aligned.";;
|
||||
0) echo "Doubles can be word-aligned."
|
||||
echo "#undef ALIGN_DOUBLE" >> m.h;;
|
||||
1) echo "Doubles must be doubleword-aligned."
|
||||
echo "#define ALIGN_DOUBLE" >> m.h;;
|
||||
*) echo "Something went wrong during alignment determination for doubles."
|
||||
|
@ -246,6 +248,26 @@ else
|
|||
echo " assembler flags........... $asflags"
|
||||
fi
|
||||
|
||||
# Checking how to invoke cpp
|
||||
|
||||
if sh ./searchpath cpp; then
|
||||
cpp="cpp -P"
|
||||
elif test -f /lib/cpp; then
|
||||
cpp="/lib/cpp -P"
|
||||
elif test -f /usr/ccs/lib/cpp; then
|
||||
cpp="/usr/ccs/lib/cpp -P"
|
||||
else
|
||||
cpp="not found"
|
||||
fi
|
||||
|
||||
echo "CPP=$cpp" >> Makefile
|
||||
|
||||
echo "How to invoke the C preprocessor: $cpp"
|
||||
|
||||
if test "$cpp" = "not found"; then
|
||||
echo "(Please edit the generated config/Makefile to set CPP correctly)"
|
||||
fi
|
||||
|
||||
# Where is ranlib?
|
||||
|
||||
if sh ./searchpath ranlib; then
|
||||
|
@ -450,26 +472,6 @@ if sh hasgot gettimeofday; then
|
|||
echo "#define HAS_GETTIMEOFDAY" >> s.h
|
||||
fi
|
||||
|
||||
# Checking how to invoke cpp
|
||||
|
||||
if sh ./searchpath cpp; then
|
||||
cpp="cpp -P"
|
||||
elif test -f /lib/cpp; then
|
||||
cpp="/lib/cpp -P"
|
||||
elif test -f /usr/ccs/lib/cpp; then
|
||||
cpp="/usr/ccs/lib/cpp -P"
|
||||
else
|
||||
cpp="not found"
|
||||
fi
|
||||
|
||||
echo "CPP=$cpp" >> Makefile
|
||||
|
||||
echo "How to invoke the C preprocessor: $cpp"
|
||||
|
||||
if test "$cpp" = "not found"; then
|
||||
echo "(Please edit the generated config/Makefile to set CPP correctly)"
|
||||
fi
|
||||
|
||||
# Determine the target architecture for the "num" library
|
||||
|
||||
case "$host" in
|
||||
|
|
|
@ -11,6 +11,7 @@
|
|||
|
||||
(* $Id$ *)
|
||||
|
||||
open Config
|
||||
open Clflags
|
||||
|
||||
let process_file name =
|
||||
|
@ -24,12 +25,12 @@ let process_file name =
|
|||
else if Filename.check_suffix name ".cmo"
|
||||
or Filename.check_suffix name ".cma" then
|
||||
objfiles := name :: !objfiles
|
||||
else if Filename.check_suffix name ".o"
|
||||
or Filename.check_suffix name ".a" then
|
||||
else if Filename.check_suffix name ext_obj
|
||||
or Filename.check_suffix name ext_lib then
|
||||
ccobjs := name :: !ccobjs
|
||||
else if Filename.check_suffix name ".c" then begin
|
||||
Compile.c_file name;
|
||||
ccobjs := (Filename.chop_suffix (Filename.basename name) ".c" ^ ".o")
|
||||
ccobjs := (Filename.chop_suffix (Filename.basename name) ".c" ^ ext_obj)
|
||||
:: !ccobjs
|
||||
end
|
||||
else
|
||||
|
|
|
@ -11,6 +11,7 @@
|
|||
|
||||
(* $Id$ *)
|
||||
|
||||
open Config
|
||||
open Clflags
|
||||
|
||||
let process_file name =
|
||||
|
@ -24,12 +25,12 @@ let process_file name =
|
|||
else if Filename.check_suffix name ".cmx"
|
||||
or Filename.check_suffix name ".cmxa" then
|
||||
objfiles := name :: !objfiles
|
||||
else if Filename.check_suffix name ".o"
|
||||
or Filename.check_suffix name ".a" then
|
||||
else if Filename.check_suffix name ext_obj
|
||||
or Filename.check_suffix name ext_lib then
|
||||
ccobjs := name :: !ccobjs
|
||||
else if Filename.check_suffix name ".c" then begin
|
||||
Optcompile.c_file name;
|
||||
ccobjs := (Filename.chop_suffix (Filename.basename name) ".c" ^ ".o")
|
||||
ccobjs := (Filename.chop_suffix (Filename.basename name) ".c" ^ ext_obj)
|
||||
:: !ccobjs
|
||||
end
|
||||
else
|
||||
|
|
|
@ -18,7 +18,7 @@ csllex: $(OBJS)
|
|||
|
||||
clean::
|
||||
rm -f csllex
|
||||
rm -f *.cmo *.cmi csllex
|
||||
rm -f *.cmo *.cmi
|
||||
|
||||
parser.ml parser.mli: parser.mly
|
||||
$(CAMLYACC) $(YACCFLAGS) parser.mly
|
||||
|
|
|
@ -1 +1,2 @@
|
|||
cslheader
|
||||
filename.ml
|
||||
|
|
|
@ -36,6 +36,9 @@ cslheader: header.c ../config/Makefile
|
|||
else $(BYTECC) $(BYTECCCOMPOPTS) $(BYTECCLINKOPTS) header.c -o cslheader; \
|
||||
strip cslheader; fi
|
||||
|
||||
clean::
|
||||
rm -f cslheader
|
||||
|
||||
pervasives.cmi: pervasives.mli
|
||||
$(CAMLC) $(COMPFLAGS) -nopervasives -c pervasives.mli
|
||||
|
||||
|
@ -45,6 +48,17 @@ pervasives.cmo: pervasives.ml
|
|||
pervasives.cmx: pervasives.ml
|
||||
$(CAMLOPT) $(COMPFLAGS) -nopervasives -c pervasives.ml
|
||||
|
||||
filename.ml: filename.mlp ../config/Makefile
|
||||
@rm -f filename.ml
|
||||
$(CPP) -DUNIX filename.mlp > filename.ml || \
|
||||
{ rm -f filename.ml; exit 2; }
|
||||
@chmod -w filename.ml
|
||||
|
||||
clean::
|
||||
rm -f filename.ml
|
||||
|
||||
beforedepend:: filename.ml
|
||||
|
||||
.SUFFIXES: .mli .ml .cmi .cmo .cmx
|
||||
|
||||
.mli.cmi:
|
||||
|
@ -63,12 +77,11 @@ $(OBJS) std_exit.cmo: $(COMPILER)
|
|||
$(OBJS:.cmo=.cmi) std_exit.cmi: $(COMPILER)
|
||||
$(OBJS:.cmo=.cmx) std_exit.cmx: $(OPTCOMPILER)
|
||||
|
||||
clean:
|
||||
clean::
|
||||
rm -f *.cm* *.o *.a
|
||||
rm -f cslheader
|
||||
rm -f *~
|
||||
|
||||
include .depend
|
||||
|
||||
depend:
|
||||
depend: beforedepend
|
||||
$(CAMLDEP) *.mli *.ml > .depend
|
||||
|
|
|
@ -1,74 +0,0 @@
|
|||
(***********************************************************************)
|
||||
(* *)
|
||||
(* Caml Special Light *)
|
||||
(* *)
|
||||
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
||||
(* *)
|
||||
(* Copyright 1995 Institut National de Recherche en Informatique et *)
|
||||
(* Automatique. Distributed only by permission. *)
|
||||
(* *)
|
||||
(***********************************************************************)
|
||||
|
||||
(* $Id$ *)
|
||||
|
||||
let current_dir_name = "."
|
||||
|
||||
let concat dirname filename =
|
||||
let l = String.length dirname - 1 in
|
||||
if l < 0 or String.get dirname l = '/'
|
||||
then dirname ^ filename
|
||||
else dirname ^ "/" ^ filename
|
||||
|
||||
let is_absolute n =
|
||||
(String.length n >= 1 & String.sub n 0 1 = "/")
|
||||
or (String.length n >= 2 & String.sub n 0 2 = "./")
|
||||
or (String.length n >= 3 & String.sub n 0 3 = "../")
|
||||
|
||||
let rindex s c =
|
||||
let rec pos i =
|
||||
if i < 0 then raise Not_found
|
||||
else if String.get s i = c then i
|
||||
else pos (i - 1)
|
||||
in pos (String.length s - 1)
|
||||
|
||||
let check_suffix name suff =
|
||||
String.length name >= String.length suff &
|
||||
String.sub name (String.length name - String.length suff) (String.length suff)
|
||||
= suff
|
||||
|
||||
let chop_suffix name suff =
|
||||
let n = String.length name - String.length suff in
|
||||
if n < 0 then invalid_arg "chop_suffix" else String.sub name 0 n
|
||||
|
||||
let chop_extension name =
|
||||
try
|
||||
String.sub name 0 (rindex name '.')
|
||||
with Not_found ->
|
||||
invalid_arg "Filename.chop_extension"
|
||||
|
||||
let basename name =
|
||||
try
|
||||
let p = rindex name '/' + 1 in
|
||||
String.sub name p (String.length name - p)
|
||||
with Not_found ->
|
||||
name
|
||||
|
||||
let dirname name =
|
||||
try
|
||||
match rindex name '/' with
|
||||
0 -> "/"
|
||||
| n -> String.sub name 0 n
|
||||
with Not_found ->
|
||||
"."
|
||||
|
||||
let temp_file prefix suffix =
|
||||
let temp_dir =
|
||||
try
|
||||
Sys.getenv "TMPDIR"
|
||||
with Not_found ->
|
||||
"/tmp" in
|
||||
let rec try_name counter =
|
||||
let name = concat temp_dir (prefix ^ string_of_int counter ^ suffix) in
|
||||
if Sys.file_exists name then try_name (counter + 1) else name
|
||||
in try_name 0
|
||||
|
|
@ -25,6 +25,9 @@ val native_c_compiler: string
|
|||
(* The C compiler to use for the native code compiler *)
|
||||
val c_libraries: string
|
||||
(* The C libraries to link with custom runtimes *)
|
||||
val standard_includes: string
|
||||
(* Options to pass to the C compiler for including the standard
|
||||
library directory. *)
|
||||
|
||||
val load_path: string list ref
|
||||
(* Directories in the search path for .cmi and .cmo files *)
|
||||
|
@ -53,3 +56,10 @@ val model: string
|
|||
(* Name of processor submodel for the native-code compiler *)
|
||||
val system: string
|
||||
(* Name of operating system for the native-code compiler *)
|
||||
|
||||
val ext_obj: string
|
||||
(* Extension for object files, e.g. [.o] under Unix. *)
|
||||
val ext_asm: string
|
||||
(* Extension for assembler files, e.g. [.s] under Unix. *)
|
||||
val ext_lib: string
|
||||
(* Extension for library files, e.g. [.a] under Unix. *)
|
||||
|
|
|
@ -11,7 +11,13 @@
|
|||
|
||||
(* $Id$ *)
|
||||
|
||||
let standard_library = "%%LIBDIR%%"
|
||||
let version = "1.15"
|
||||
|
||||
let standard_library =
|
||||
try
|
||||
Sys.getenv "CAMLLIB"
|
||||
with Not_found ->
|
||||
"%%LIBDIR%%"
|
||||
|
||||
let bytecomp_c_compiler = "%%BYTECC%%"
|
||||
|
||||
|
@ -19,8 +25,6 @@ let native_c_compiler = "%%NATIVECC%%"
|
|||
|
||||
let c_libraries = "%%CCLIBS%%"
|
||||
|
||||
let version = "1.14"
|
||||
|
||||
let exec_magic_number = "Caml1999X001"
|
||||
and cmi_magic_number = "Caml1999I002"
|
||||
and cmo_magic_number = "Caml1999O002"
|
||||
|
@ -34,7 +38,14 @@ let max_tag = 248
|
|||
let max_young_wosize = 256
|
||||
|
||||
let architecture = "%%ARCH%%"
|
||||
|
||||
let model = "%%MODEL%%"
|
||||
|
||||
let system = "%%SYSTEM%%"
|
||||
|
||||
let ext_obj = "%%EXT_OBJ%%"
|
||||
let ext_asm = "%%EXT_ASM%%"
|
||||
let ext_lib = "%%EXT_LIB%%"
|
||||
|
||||
let standard_includes =
|
||||
match system with
|
||||
"win32" -> "-I" ^ standard_library
|
||||
| _ -> "-I" ^ standard_library ^ " -L" ^ standard_library
|
||||
|
|
Loading…
Reference in New Issue