summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--tools/.cvsignore2
-rw-r--r--tools/Makefile23
-rw-r--r--tools/ocamlmklib.mlp224
-rw-r--r--tools/ocamlmklib.tpl151
4 files changed, 242 insertions, 158 deletions
diff --git a/tools/.cvsignore b/tools/.cvsignore
index 8dcc03428..b7af4ab46 100644
--- a/tools/.cvsignore
+++ b/tools/.cvsignore
@@ -14,6 +14,8 @@ keywords
lexer299.ml
ocaml299to3
ocamlmklib
+ocamlmklib.ml
lexer301.ml
scrapelabels
addlabels
+
diff --git a/tools/Makefile b/tools/Makefile
index 0b797644a..d537517ba 100644
--- a/tools/Makefile
+++ b/tools/Makefile
@@ -75,20 +75,29 @@ clean::
# To help building mixed-mode libraries (Caml + C)
-ocamlmklib: ocamlmklib.tpl ../config/Makefile
+ocamlmklib: ocamlmklib.cmo
+ $(CAMLC) $(LINKFLAGS) -o ocamlmklib ocamlmklib.cmo
+
+install::
+ cp ocamlmklib $(BINDIR)/ocamlmklib
+
+clean::
+ rm -f ocamlmklib
+
+ocamlmklib.ml: ocamlmklib.mlp ../config/Makefile
sed -e "s|%%BINDIR%%|$(BINDIR)|" \
-e "s|%%SUPPORTS_SHARED_LIBRARIES%%|$(SUPPORTS_SHARED_LIBRARIES)|" \
-e "s|%%MKSHAREDLIB%%|$(MKSHAREDLIB)|" \
- -e "s|%%SHAREDLDTYPE%%|$(SHAREDLDTYPE)|" \
+ -e "s|%%BYTECCRPATH%%|$(BYTECCRPATH)|" \
+ -e "s|%%NATIVECCRPATH%%|$(NATIVECCRPATH)|" \
+ -e "s|%%MKSHAREDLIBRPATH%%|$(MKSHAREDLIBRPATH)|" \
-e "s|%%RANLIB%%|$(RANLIB)|" \
- ocamlmklib.tpl > ocamlmklib
- chmod +x ocamlmklib
+ ocamlmklib.mlp > ocamlmklib.ml
-install::
- cp ocamlmklib $(BINDIR)/ocamlmklib
+beforedepend:: ocamlmklib.ml
clean::
- rm -f ocamlmklib
+ rm -f ocamlmklib.ml
# Converter olabl/ocaml 2.99 to ocaml 3
diff --git a/tools/ocamlmklib.mlp b/tools/ocamlmklib.mlp
new file mode 100644
index 000000000..8eeb6401d
--- /dev/null
+++ b/tools/ocamlmklib.mlp
@@ -0,0 +1,224 @@
+(***********************************************************************)
+(* *)
+(* Objective Caml *)
+(* *)
+(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
+(* *)
+(* Copyright 2001 Institut National de Recherche en Informatique et *)
+(* en Automatique. All rights reserved. This file is distributed *)
+(* under the terms of the Q Public License version 1.0. *)
+(* *)
+(***********************************************************************)
+
+(* $Id$ *)
+
+open Printf
+
+let bindir = "%%BINDIR%%"
+and supports_shared_libraries = %%SUPPORTS_SHARED_LIBRARIES%%
+and mksharedlib = "%%MKSHAREDLIB%%"
+and bytecc_rpath = "%%BYTECCRPATH%%"
+and nativecc_rpath = "%%NATIVECCRPATH%%"
+and mksharedlib_rpath = "%%MKSHAREDLIBRPATH%%"
+and ranlib = "%%RANLIB%%"
+
+let bytecode_objs = ref [] (* .cmo,.cma,.ml,.mli files to pass to ocamlc *)
+and native_objs = ref [] (* .cmx,.cmxa,.ml,.mli files to pass to ocamlopt *)
+and c_objs = ref [] (* .o, .a files to pass to mksharedlib and ar *)
+and caml_libs = ref [] (* -cclib to pass to ocamlc, ocamlopt *)
+and caml_opts = ref [] (* -ccopt to pass to ocamlc, ocamlopt *)
+and dynlink = ref supports_shared_libraries
+and failsafe = ref false (* whether to fall back on static build only *)
+and c_libs = ref [] (* libs to pass to mksharedlib and ocamlc -cclib *)
+and c_opts = ref [] (* options to pass to mksharedlib and ocamlc -ccopt *)
+and ocamlc = ref (Filename.concat bindir "ocamlc")
+and ocamlopt = ref (Filename.concat bindir "ocamlopt")
+and output = ref "a" (* Output name for Caml part of library *)
+and output_c = ref "" (* Output name for C part of library *)
+and rpath = ref [] (* rpath options *)
+and verbose = ref false
+
+let starts_with s pref =
+ String.length s >= String.length pref &&
+ String.sub s 0 (String.length pref) = pref
+let ends_with = Filename.check_suffix
+let chop_prefix s pref =
+ String.sub s (String.length pref) (String.length s - String.length pref)
+let chop_suffix = Filename.chop_suffix
+
+exception Bad_argument of string
+
+let parse_arguments argv =
+ let i = ref 1 in
+ let next_arg () =
+ if !i + 1 >= Array.length argv
+ then raise (Bad_argument("Option " ^ argv.(!i) ^ " expects one argument"));
+ incr i; argv.(!i) in
+ while !i < Array.length argv do
+ let s = argv.(!i) in
+ if ends_with s ".cmo" || ends_with s ".cma" then
+ bytecode_objs := s :: !bytecode_objs
+ else if ends_with s ".cmx" || ends_with s ".cmxa" then
+ native_objs := s :: !native_objs
+ else if ends_with s ".ml" || ends_with s ".mli" then
+ (bytecode_objs := s :: !bytecode_objs;
+ native_objs := s :: !native_objs)
+ else if ends_with s ".o" || ends_with s ".a" then
+ c_objs := s :: !c_objs
+ else if s = "-cclib" then
+ caml_libs := next_arg () :: "-cclib" :: !caml_libs
+ else if s = "-ccopt" then
+ caml_opts := next_arg () :: "-cclib" :: !caml_opts
+ else if s = "-custom" then
+ dynlink := false
+ else if s = "-I" then
+ caml_opts := next_arg () :: "-I" :: !caml_opts
+ else if s = "-failsafe" then
+ failsafe := true
+ else if s = "-linkall" then
+ caml_opts := s :: !caml_opts
+ else if starts_with s "-l" then
+ c_libs := s :: !c_libs
+ else if starts_with s "-L" then
+ (c_opts := s :: !c_opts;
+ let l = chop_prefix s "-L" in
+ if not (Filename.is_relative l) then rpath := l :: !rpath)
+ else if s = "-ocamlc" then
+ ocamlc := next_arg ()
+ else if s = "-ocamlopt" then
+ ocamlopt := next_arg ()
+ else if s = "-o" then
+ output := next_arg()
+ else if s = "-oc" then
+ output_c := next_arg()
+ else if s = "-dllpath" || s = "-R" || s = "-rpath" then
+ rpath := next_arg() :: !rpath
+ else if starts_with s "-R" then
+ rpath := chop_prefix s "-R" :: !rpath
+ else if s = "-Wl,-rpath" then
+ (let a = next_arg() in
+ if starts_with a "-Wl,"
+ then rpath := chop_prefix "-Wl," s :: !rpath
+ else raise (Bad_argument("Option -Wl,-rpath expects a -Wl, argument")))
+ else if starts_with s "-Wl,-rpath," then
+ rpath := chop_prefix "-Wl,-rpath," s :: !rpath
+ else if starts_with s "-Wl,-R" then
+ rpath := chop_prefix "-Wl,-R" s :: !rpath
+ else if s = "-v" || s = "-verbose" then
+ verbose := true
+ else if starts_with s "-" then
+ raise (Bad_argument("Unknown option " ^ s))
+ else
+ raise (Bad_argument("Don't know what to do with " ^ s));
+ incr i
+ done;
+ List.iter
+ (fun r -> r := List.rev !r)
+ [ bytecode_objs; native_objs; c_objs; caml_libs; caml_opts;
+ c_libs; c_objs; rpath ];
+ if !output_c = "" then output_c := !output
+
+let usage = "\
+Usage: ocamlmklib [options] <.cmo|.cma|.cmx|.cmxa|.ml|.mli|.o|.a files>
+Options are:
+ -cclib <lib> C library passed to ocamlc -a or ocamlopt -a only
+ -ccopt <opt> C option passed to ocamlc -a or ocamlopt -a only
+ -custom disable dynamic loading
+ -dllpath <dir> Add <dir> to the run-time search path for DLLs
+ -I <dir> Add <dir> to the path searched for Caml object files
+ -failsafe fall back to static linking if DLL construction failed
+ -linkall Build Caml archive with link-all behavior
+ -l<lib> Specify a dependent C library
+ -L<dir> Add <dir> to the path searched for C libraries
+ -ocamlc <cmd> Use <cmd> in place of \"ocamlc\"
+ -ocamlopt <cmd> Use <cmd> in place of \"ocamlopt\"
+ -o <name> Generated Caml library is named <name>.cma or <name>.cmxa
+ -oc <name> Generated C library is named lib<name>.so or lib<name>.a
+ -rpath <dir> Same as -dllpath <dir>
+ -R<dir> Same as -rpath
+ -verbose Print commands before executing them
+ -Wl,-rpath,<dir> Same as -dllpath <dir>
+ -Wl,-rpath -Wl<dir> Same as -dllpath <dir>
+ -Wl,-R<dir> Same as -dllpath <dir>
+"
+
+let command cmd =
+ if !verbose then (print_string "+ "; print_string cmd; print_newline());
+ Sys.command cmd
+
+let scommand cmd =
+ if command cmd <> 0 then exit 2
+
+let safe_remove s =
+ try Sys.remove s with Sys_error _ -> ()
+
+let make_rpath flag =
+ if !rpath = [] || flag = ""
+ then ""
+ else flag ^ String.concat ":" !rpath
+
+let make_rpath_ccopt flag =
+ if !rpath = [] || flag = ""
+ then ""
+ else "-ccopt " ^ flag ^ String.concat ":" !rpath
+
+let prefix_list pref l =
+ List.map (fun s -> pref ^ s) l
+
+let build_libs () =
+ if !c_objs <> [] then begin
+ if !dynlink then begin
+ let retcode = command
+ (sprintf "%s dll%s.so %s %s %s %s"
+ mksharedlib
+ !output_c
+ (String.concat " " !c_objs)
+ (String.concat " " !c_opts)
+ (make_rpath mksharedlib_rpath)
+ (String.concat " " !c_libs)) in
+ if retcode <> 0 then if !failsafe then dynlink := false else exit 2
+ end;
+ safe_remove ("lib" ^ !output_c ^ ".a");
+ scommand
+ (sprintf "ar rc lib%s.a %s"
+ !output_c
+ (String.concat " " !c_objs));
+ scommand
+ (sprintf "%s lib%s.a"
+ ranlib
+ !output_c)
+ end;
+ if !bytecode_objs <> [] then
+ scommand
+ (sprintf "%s -a %s -o %s.cma %s -dllib -l%s -cclib -l%s %s %s %s"
+ !ocamlc
+ (if !dynlink then "" else "-custom")
+ !output
+ (String.concat " " !bytecode_objs)
+ !output_c
+ !output_c
+ (String.concat " " (prefix_list "-ccopt " !c_opts))
+ (make_rpath_ccopt bytecc_rpath)
+ (String.concat " " (prefix_list "-cclib " !c_libs)));
+ if !native_objs <> [] then
+ scommand
+ (sprintf "%s -a -o %s.cmxa %s -cclib -l%s %s %s %s"
+ !ocamlopt
+ !output
+ (String.concat " " !native_objs)
+ !output_c
+ (String.concat " " (prefix_list "-ccopt " !c_opts))
+ (make_rpath_ccopt nativecc_rpath)
+ (String.concat " " (prefix_list "-cclib " !c_libs)))
+
+let _ =
+ try
+ parse_arguments Sys.argv;
+ build_libs()
+ with
+ | Bad_argument s ->
+ prerr_endline s; prerr_string usage; exit 4
+ | Sys_error s ->
+ prerr_string "System error: "; prerr_endline s; exit 4
+ | x ->
+ raise x
diff --git a/tools/ocamlmklib.tpl b/tools/ocamlmklib.tpl
deleted file mode 100644
index 5275c91b0..000000000
--- a/tools/ocamlmklib.tpl
+++ /dev/null
@@ -1,151 +0,0 @@
-#!/bin/sh
-#########################################################################
-# #
-# Objective Caml #
-# #
-# Xavier Leroy, projet Cristal, INRIA Rocquencourt #
-# #
-# Copyright 2001 Institut National de Recherche en Informatique et #
-# en Automatique. All rights reserved. This file is distributed #
-# under the terms of the Q Public License version 1.0. #
-# #
-#########################################################################
-
-# $Id$
-
-bytecode_objs=''
-native_objs=''
-c_objs=''
-c_libs=''
-c_libs_caml=''
-c_opts=''
-c_opts_caml=''
-caml_opts=''
-caml_libs=''
-ocamlc='%%BINDIR%%/ocamlc'
-ocamlopt='%%BINDIR%%/ocamlopt'
-output='a'
-output_c=''
-sharedldtype='%%SHAREDLDTYPE%%'
-dynlink='%%SUPPORTS_SHARED_LIBRARIES%%'
-custom_opt='-custom'
-failsafe='false'
-
-while :; do
- case "$1" in
- "")
- break;;
- *.cmo|*.cma)
- bytecode_objs="$bytecode_objs $1";;
- *.cmx|*.cmxa)
- native_objs="$native_objs $1";;
- *.ml|*.mli)
- bytecode_objs="$bytecode_objs $1"
- native_objs="$native_objs $1";;
- *.o|*.a)
- c_objs="$c_objs $1";;
- -cclib)
- caml_libs="$caml_libs $1 $2"
- shift;;
- -ccopt)
- caml_opts="$caml_opts $1 $2"
- shift;;
- -custom)
- dynlink=false;;
- -I)
- caml_opts="$caml_opts $1 $2"
- shift;;
- -failsafe)
- failsafe=true;;
- -linkall)
- caml_opts="$caml_opts $1";;
- -l*)
- c_libs="$c_libs $1"
- c_libs_caml="$c_libs_caml -cclib $1";;
- -L*)
- c_opts="$c_opts $1"
- c_opts_caml="$c_opts_caml -ccopt $1";;
- -ocamlc)
- ocamlc="$2"
- shift;;
- -ocamlopt)
- ocamlopt="$2"
- shift;;
- -o)
- output="$2"
- shift;;
- -oc)
- output_c="$2"
- shift;;
- -pthread)
- c_opts_caml="$c_opts_caml -ccopt $1";;
- -R|-rpath)
- c_opts="$c_opts $1 $2"
- c_opts_caml="$c_opts_caml -ccopt $1 -ccopt $2"
- shift;;
- -R*)
- c_opts="$c_opts $1"
- c_opts_caml="$c_opts_caml -ccopt $1";;
- -Wl,-rpath)
- case $2 in
- -Wl,*)
- rpatharg=`echo $2 | sed "s/^-Wl,//"`
- if test "$sharedldtype" = "ld"; then
- c_opts="$c_opts -rpath $rpatharg"
- else
- c_opts="$c_opts $1,$rpatharg"
- fi
- c_opts_caml="$c_opts_caml -ccopt $1,$rpatharg"
- shift;;
- *)
- echo "No argument to '$1', ignored" 1>&2;;
- esac;;
- -Wl,-rpath,*)
- if test "$sharedldtype" = "ld"; then
- rpatharg=`echo $1 | sed "s/^-Wl,-rpath,//"`
- c_opts="$c_opts -rpath $rpatharg"
- else
- c_opts="$c_opts $1"
- fi
- c_opts_caml="$c_opts_caml -ccopt $1";;
- -Wl,-R*)
- if test "$sharedldtype" = "ld"; then
- rpatharg=`echo $1 | sed "s/^-Wl,-R//"`
- c_opts="$c_opts -R$rpatharg"
- else
- c_opts="$c_opts $1"
- fi
- c_opts_caml="$c_opts_caml -ccopt $1";;
- -*)
- echo "Unknown option '$1', ignored" 1>&2;;
- *)
- echo "Don't know what to do with '$1', ignored" 1>&2;;
- esac
- shift
-done
-
-if test "$output_c" = ""; then output_c="$output"; fi
-
-set -e
-
-if test "$c_objs" != ""; then
- if $dynlink; then
- %%MKSHAREDLIB%% lib$output_c.so $c_objs $c_opts $c_libs || $failsafe
- fi
- rm -f lib$output_c.a
- ar rc lib$output_c.a $c_objs
- %%RANLIB%% lib$output_c.a
-fi
-if $dynlink && test "$failsafe" = "false" || test -f lib$output_c.so; then
- c_libs_caml=''
- custom_opt=''
-fi
-if test "$bytecode_objs" != ""; then
- $ocamlc -a $custom_opt -o $output.cma $caml_opts $bytecode_objs \
- -cclib -l$output_c $caml_libs $c_opts_caml $c_libs_caml
-fi
-if test "$native_objs" != ""; then
- $ocamlopt -a -o $output.cmxa $caml_opts $native_objs \
- -cclib -l$output_c $caml_libs $c_opts_caml $c_libs_caml
-fi
-