summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--_tags82
-rwxr-xr-xboot/myocamlbuild.bootbin441686 -> 0 bytes
-rw-r--r--build/.ignore1
-rwxr-xr-xbuild/boot-c-parts.sh50
-rwxr-xr-xbuild/boot.sh39
-rwxr-xr-xbuild/buildbot119
-rw-r--r--build/camlp4-bootstrap-recipe.txt180
-rwxr-xr-xbuild/camlp4-bootstrap.sh51
-rwxr-xr-xbuild/camlp4-byte-only.sh23
-rwxr-xr-xbuild/camlp4-mkCamlp4Ast.sh36
-rwxr-xr-xbuild/camlp4-native-only.sh23
-rw-r--r--build/camlp4-targets.sh46
-rwxr-xr-xbuild/distclean.sh37
-rwxr-xr-xbuild/fastworld.sh48
-rwxr-xr-xbuild/install.sh475
-rwxr-xr-xbuild/mixed-boot.sh22
-rwxr-xr-xbuild/mkconfig.sh27
-rwxr-xr-xbuild/mkmyocamlbuild_config.sh40
-rwxr-xr-xbuild/mkruntimedef.sh21
-rwxr-xr-xbuild/myocamlbuild.sh31
-rw-r--r--build/new-build-system47
-rwxr-xr-xbuild/ocamlbuild-byte-only.sh19
-rwxr-xr-xbuild/ocamlbuild-native-only.sh19
-rwxr-xr-xbuild/ocamlbuildlib-native-only.sh19
-rw-r--r--build/otherlibs-targets.sh103
-rwxr-xr-xbuild/partial-install.sh157
-rw-r--r--build/targets.sh63
-rw-r--r--build/tolower.sed23
-rwxr-xr-xbuild/world.all.sh24
-rwxr-xr-xbuild/world.byte.sh21
-rwxr-xr-xbuild/world.native.sh22
-rwxr-xr-xbuild/world.sh35
-rw-r--r--myocamlbuild.ml607
-rw-r--r--myocamlbuild_config.mli72
-rw-r--r--tools/.depend44
-rw-r--r--tools/Makefile.shared39
-rw-r--r--tools/eqparsetree.ml2
-rw-r--r--tools/ocamlmklib.ml (renamed from tools/ocamlmklib.mlp)2
38 files changed, 33 insertions, 2636 deletions
diff --git a/_tags b/_tags
deleted file mode 100644
index 558a81f86..000000000
--- a/_tags
+++ /dev/null
@@ -1,82 +0,0 @@
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-# Ocamlbuild tags file
-
-true: -traverse
-
-# Traverse only these directories
-<{bytecomp,driver,stdlib,tools,asmcomp,ocamlbuild,toplevel,ocamldoc,typing,otherlibs,utils,debugger,lex,parsing,byterun,asmrun}/**>: traverse
-
-"ocamlbuild/test" or "ocamlbuild/testsuite": -traverse
-
-"boot" or "byterun" or "asmrun" or "compilerlibs": not_hygienic
-
-# These should not be required but it fails on *BSD and Windows...
-"yacc" or "win32caml": not_hygienic
-
-# We want -g everywhere it's possible
-true: debug
-
-# By default everything we link needs the stdlib
-true: use_stdlib
-
-# The stdlib neither requires the stdlib nor debug information
-<stdlib/**>: -use_stdlib, -debug
-
-<**/*.ml*>: warn_error_A
-
-<{bytecomp,driver,stdlib,tools,asmcomp,toplevel,typing,utils,lex,parsing}/**>: strict_sequence
-
-"toplevel/topstart.byte": linkall
-
-<ocamldoc/**>: -debug
-<ocamldoc/*.ml>: ocamldoc_sources
-<ocamldoc/*.ml*>: include_unix, include_str, include_dynlink
-<ocamldoc/odoc.{byte,native}>: use_unix, use_str, use_dynlink
-
-<ocamlbuild/*>: include_unix
-
-<**/pervasives.ml> or <**/pervasives.mli> or <**/camlinternalOO.mli>: nopervasives
-<**/camlinternalOO*.cmx>: inline(0)
-<**/scanf*.cmx>: inline(9)
-<**/*Labels.ml*>: nolabels
-
-"tools/addlabels.ml": warn_s
-
-<debugger/main.byte> or <debugger/main.native>: use_unix, linkall
-<debugger/*.ml*>: include_unix
-
-<otherlibs/{,win32}unix/unix.cm{,x}a> or <otherlibs/str/str.cm{,x}a>: ocamlmklib
-<otherlibs/num/nums.cm{,x}a> or <otherlibs/dbm/dbm.cm{,x}a>: ocamlmklib
-<otherlibs/{,win32}graph/graphics.cm{,x}a>: ocamlmklib
-<otherlibs/threads/threads.cm{,x}a>: ocamlmklib
-"otherlibs/threads/unix.cma": ocamlmklib
-<otherlibs/bigarray/bigarray.cm{,x}a>: ocamlmklib
-
-<otherlibs/{bigarray,systhreads}/**.ml*>: include_unix
-
-# See the remark about static linking of threads.cmxa in myocamlbuild.ml
-<otherlibs/systhreads/threads.cma>: ocamlmklib
-
-"otherlibs/threads/pervasives.ml": include_unix
-
-<otherlibs/**>: otherlibs
-<otherlibs/{,win32}unix/**>: otherlibs_unix
-<otherlibs/win32unix/**>: otherlibs_win32unix
-<otherlibs/bigarray/**>: otherlibs_bigarray
-<otherlibs/num/**>: otherlibs_num
-<otherlibs/threads/**>: otherlibs_threads
-"otherlibs/threads/unix.cma": -otherlibs_threads
-<otherlibs/systhreads/**>: otherlibs_systhreads
-<otherlibs/graph/**>: otherlibs_graph
-<otherlibs/win32graph/**>: otherlibs_win32graph
diff --git a/boot/myocamlbuild.boot b/boot/myocamlbuild.boot
deleted file mode 100755
index 3437423b9..000000000
--- a/boot/myocamlbuild.boot
+++ /dev/null
Binary files differ
diff --git a/build/.ignore b/build/.ignore
deleted file mode 100644
index 274c6e555..000000000
--- a/build/.ignore
+++ /dev/null
@@ -1 +0,0 @@
-ocamlbuild_mixed_mode
diff --git a/build/boot-c-parts.sh b/build/boot-c-parts.sh
deleted file mode 100755
index fd5a35c72..000000000
--- a/build/boot-c-parts.sh
+++ /dev/null
@@ -1,50 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-cd `dirname $0`/..
-set -ex
-
-. config/config.sh
-
-if "$WINDOWS"; then
- MAKEOPTS='-f Makefile.nt'
- LINK='cp -f'
-else
- MAKEOPTS=''
- LINK='ln -s -f'
-fi
-
-(cd byterun && make $MAKEOPTS)
-(cd asmrun && make $MAKEOPTS all meta."$O" dynlink."$O")
-(cd yacc && make $MAKEOPTS)
-
-if "$WINDOWS"; then
- (cd win32caml && make)
-fi
-
-mkdir -p _build/boot
-
-# Create a bunch of symlinks (or copies) to _build/boot
-(cd _build/boot &&
-$LINK ../../byterun/ocamlrun$EXE \
- ../../byterun/libcamlrun.$A \
- ../../asmrun/libasmrun.$A \
- ../../yacc/ocamlyacc$EXE \
- ../../boot/ocamlc \
- ../../boot/ocamllex \
- ../../boot/ocamldep \
- . )
-
-(cd boot &&
-[ -f boot/ocamlrun$EXE ] || $LINK ../byterun/ocamlrun$EXE . )
diff --git a/build/boot.sh b/build/boot.sh
deleted file mode 100755
index ca6eaabac..000000000
--- a/build/boot.sh
+++ /dev/null
@@ -1,39 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-cd `dirname $0`/..
-set -ex
-TAG_LINE='true: -use_stdlib'
-
-STDLIB_MODULES='Pervasives,Arg,Array,Buffer,Char,Digest,Filename,Format,Hashtbl,Lazy,Lexing,List,Map,Printexc,Printf,Scanf,Set,String,Sys,Parsing,Int32,Int64,Nativeint,Obj,Queue,Sort,Stream,Stack'
-
-./boot/ocamlrun boot/myocamlbuild.boot -ignore "$STDLIB_MODULES" \
- -tag-line "$TAG_LINE" -no-ocamlfind \
- boot/stdlib.cma boot/std_exit.cmo
-
-boot/ocamlrun boot/myocamlbuild.boot \
- -tag-line "$TAG_LINE" -no-ocamlfind -log _boot_log1 \
- ocamlbuild/ocamlbuildlightlib.cma ocamlbuild/ocamlbuildlight.byte
-
-rm -f _build/myocamlbuild
-
-boot/ocamlrun boot/myocamlbuild.boot \
- -just-plugin -install-lib-dir _build/ocamlbuild -byte-plugin \
- -no-ocamlfind || exit 1
-
-cp _build/myocamlbuild boot/myocamlbuild
-
-./boot/ocamlrun boot/myocamlbuild -no-ocamlfind \
- -tag-line "$TAG_LINE" \
- $@ -log _boot_log2 boot/camlheader ocamlc
diff --git a/build/buildbot b/build/buildbot
deleted file mode 100755
index d7e010365..000000000
--- a/build/buildbot
+++ /dev/null
@@ -1,119 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-# If you want to help me by participating to the build/test effort:
-# http://gallium.inria.fr/~pouillar/ocaml-testing.html
-# -- Nicolas Pouillard
-
-usage() {
- echo "Usage: $0 (make|ocb|ocamlbuild) (win (mingw|msvc|msvc64) | <configure-arg>*)"
- exit 1
-}
-
-logfile="buildbot.log"
-
-finish() {
- curl -s -0 -F "log=@$logfile" \
- -F "host=`hostname`" \
- -F "mode=$mode-$opt_win-$opt_win2" \
- http://buildbot.feydakins.org/dropbox || :
-}
-
-rm -f buildbot.failed
-rm -f $logfile
-
-bad() {
- touch buildbot.failed
-}
-
-finish_if_bad() {
- if [ -f buildbot.failed ]; then
- finish
- exit 2
- fi
-}
-
-if figlet "test" > /dev/null 2> /dev/null; then
- draw="figlet"
-else
- draw="echo ----------- "
-fi
-
-if echo | tee -a tee.log > /dev/null 2> /dev/null; then
- tee="tee -a $logfile"
-else
- tee=:
-fi
-
-rm -f tee.log
-
-log() {
- $draw $@
- $tee
-}
-
-mode=$1
-shift 1
-
-case "$mode" in
- make|ocb|ocamlbuild) : ;;
- *) usage;;
-esac
-
-case "$1" in
- win)
- opt_win=win
- opt_win2=$2
- shift 2
- Makefile=Makefile.nt;;
- *) Makefile=Makefile;;
-esac
-
-( [ -f config/Makefile ] && make -f $Makefile clean || : ) 2>&1 | log clean
-
-( ./build/distclean.sh || : ) 2>&1 | log distclean
-
-(cvs -q up -dP -r release311 || bad) 2>&1 | log cvs up
-finish_if_bad
-
-case "$opt_win" in
-win)
- cp config/m-nt.h config/m.h || bad
- finish_if_bad
- cp config/s-nt.h config/s.h || bad
- finish_if_bad
- ;;
-
-*)
- (./configure --prefix `pwd`/_install $@ || bad) 2>&1 | log configure
- finish_if_bad
- ;;
-esac
-
-case "$mode" in
- make)
- (make -f $Makefile world opt opt.opt install || bad) 2>&1 | log build install
- finish_if_bad
- ;;
- ocb|ocamlbuild)
- (./build/fastworld.sh || bad) 2>&1 | log build
- finish_if_bad
- (./build/install.sh || bad) 2>&1 | log install
- finish_if_bad
- ;;
-esac
-
-(cat _build/not_installed || bad) 2>&1 | log not_installed
-
-finish
diff --git a/build/camlp4-bootstrap-recipe.txt b/build/camlp4-bootstrap-recipe.txt
deleted file mode 100644
index 8a3a7b122..000000000
--- a/build/camlp4-bootstrap-recipe.txt
+++ /dev/null
@@ -1,180 +0,0 @@
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2010 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. #
-# #
-#########################################################################
-
-=== Initial setup ===
- make clean
- ./build/distclean.sh
- ./configure -prefix `pwd`/_install
- ./build/fastworld.sh
- # Go to "Bootstrap camlp4"
-
-=== Install the bootstrapping camlp4 processor ===
- ./build/install.sh
-
-=== Build camlp4 ===
- # This step is not needed right after a "./build/world.sh byte"
- ./build/camlp4-byte-only.sh
-
-=== Bootstrap camlp4 ===
- # First "Build camlp4"
- # Then "Install the bootstrapping camlp4 processor"
- # Indeed the following bootstrapping script
- # does use the installed version!
- ./build/camlp4-bootstrap.sh
- # If the fixpoint not is reached yet
- # Go to "Bootstrap camlp4"
- # Otherwise
- # Have a look at the changes in
- # camlp4/boot it may be a good idea to commit them
-
-=== Generate Camlp4Ast.ml ===
- # First "Install the bootstrapping camlp4 processor"
- # Indeed the following bootstrapping script
- # does use the installed version!
- ./build/camlp4-mkCamlp4Ast.sh
-
-=== Case study "let open M in e" ===
-
- Open the revised parser
- Camlp4Parsers/Camlp4OCamlRevisedParser.ml
-
- Look for similar constructs, indeed rules
- that start by the same prefix should in
- the same entry. It is simpler to stick
- them close to each other.
-
- [ "let"; r = opt_rec; ...
- | "let"; "module"; m = a_UIDENT; ...
-
- So we naturally add something like
-
- | "let"; "open"; ...
-
- Then have a look to the "open" construct:
-
- | "open"; i = module_longident ->
-
- So we need a module_longident, it becomes:
-
- | "let"; "open"; i = module_longident; "in"; e = SELF ->
-
- Then we leave a dummy action but very close to what we want
- in the end:
-
- | "let"; "open"; i = module_longident; "in"; e = SELF ->
- <:expr< open_in $id:i$ $e$ >>
-
- Here it is just calling a (non-existing) function called open_in.
-
- Check that there is no other place where we have to duplicate this
- rule (yuk!). In our case it is! The sequence entry have the "let"
- rules again.
-
- Then go into Camlp4Parsers/Camlp4OCamlParser.ml and look for other
- occurences.
-
- When copy/pasting the rule take care of SELF occurences, you may
- have to replace it by expr and expr LEVEL ";" in our case.
-
- The return type of the production might be different from expr in
- our case an action become <:str_item<...>> instead of <:expr<...>
-
- Watch the DELETE_RULE as well, in our case I'm searching for the
- literal string "let" in the source:
-
- DELETE_RULE Gram expr: "let"; "open"; module_longident; "in"; SELF END;
-
- Then build and bootstrap.
-
- Then you can at last extend the AST, go in:
-
- Camlp4/Camlp4Ast.partial.ml
-
- And add the "open in" constructor (at the end).
-
- (* let open i in e *)
- | ExOpI of loc and ident and expr
-
- Then "Generate Camlp4Ast.ml" and build.
-
- We get a single warning in Camlp4/Struct/Camlp4Ast2OCamlAst.ml but
- don't fix it now. Notice that you may need to disable '-warn-error'
- in order to be able to successfully compile, despite of the warning.
-
- Then I hacked the camlp4/boot/camlp4boot.ml to generate:
- Ast.ExOpI(_loc, i, e)
- instead of
- Ast.ExApp(_loc .... "open_in" ... i ... e ...)
-
- Build. Bootstrap once and build again.
-
- Then change the parsers again and replace the
- open_in $id:i$ $e$
- by
- let open $i$ in $e$
-
- Then change the Parsetree generation in
- Camlp4/Struct/Camlp4Ast2OCamlAst.ml
-
- | <:expr@loc< let open $i$ in $e$ >> ->
- mkexp loc (Pexp_open (long_uident i) (expr e))
-
- Change the pretty-printers as well (drawing inspiration in
- "let module" in this case):
-
- In Camlp4/Printers/OCaml.ml:
- | <:expr< let open $i$ in $e$ >> ->
- pp f "@[<2>let open %a@]@ @[<2>in@ %a@]"
- o#ident i o#reset_semi#expr e
- And at the end of #simple_expr:
- <:expr< let open $_$ in $_$ >>
-
- Have a look in Camlp4/Printers/OCamlr.ml as well.
-
-=== Second case study "with t := ..." ===
-
-1/ Change the revised parser first.
-Add new parsing rules for := but keep the old actions for now.
-
-2/ Change Camlp4Ast.partial.ml, add:
- (* type t := t *)
- | WcTyS of loc and ctyp and ctyp
- (* module i := i *)
- | WcMoS of loc and ident and ident
-
-3/ "Generate Camlp4Ast.ml" and build.
-
-4/ Change the generated camlp4/boot/camlp4boot.ml:
- Look for ":=" and change occurences of
- WcMod by WcMoS and WcTyp by WcTyS
-
-5/ Build (DO NOT bootstrap)
- "Install the bootstrapping camlp4 processor"
-
-6/ Change the required files:
- Camlp4/Printers/OCaml.ml:
- just copy/paste&adapt what is done for
- "... with type t = u" and
- "... with module M = N"
- Camlp4/Struct/Camlp4Ast2OCamlAst.ml:
- I've factored out a common part under
- another function and then copy/pasted.
- Camlp4Parsers/Camlp4OCamlRevisedParser.ml:
- Change the <:with_constr< type $...$ = $...$ >>
- we've introduced earlier by replacing the '='
- by ':='.
- Camlp4Parsers/Camlp4OCamlParser.ml:
- Copy paste what we have done in Camlp4OCamlRevisedParser
- and but we need to call opt_private_ctyp instead of
- ctyp (just like the "type =" construct).
-
-7/ Build & Bootstrap
diff --git a/build/camlp4-bootstrap.sh b/build/camlp4-bootstrap.sh
deleted file mode 100755
index 70600c09b..000000000
--- a/build/camlp4-bootstrap.sh
+++ /dev/null
@@ -1,51 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-# README: to bootstrap camlp4 have a look at build/camlp4-bootstrap-recipe.txt
-
-set -e
-cd `dirname $0`/..
-
-. config/config.sh
-export PATH=$BINDIR:$PATH
-
-TMPTARGETS="\
- camlp4/boot/Lexer.ml"
-
-TARGETS="\
- camlp4/Camlp4/Struct/Camlp4Ast.ml \
- camlp4/boot/Camlp4.ml \
- camlp4/boot/camlp4boot.ml"
-
-for target in $TARGETS camlp4/boot/Camlp4Ast.ml; do
- [ -f "$target" ] && mv "$target" "$target.old"
- rm -f "_build/$target"
-done
-
-if [ -x ./boot/myocamlbuild.native ]; then
- OCAMLBUILD=./boot/myocamlbuild.native -no-ocamlfind
-else
- OCAMLBUILD="./boot/ocamlrun boot/myocamlbuild -no-ocamlfind"
-fi
-$OCAMLBUILD $TMPTARGETS $TARGETS
-
-for t in $TARGETS; do
- echo promote $t
- cp _build/$t camlp4/boot/`basename $t`
- if cmp _build/$t camlp4/boot/`basename $t`.old; then
- echo fixpoint for $t
- else
- echo $t is different, you should rebootstrap it by cleaning, building and call this script
- fi
-done
diff --git a/build/camlp4-byte-only.sh b/build/camlp4-byte-only.sh
deleted file mode 100755
index 8f4ed4e20..000000000
--- a/build/camlp4-byte-only.sh
+++ /dev/null
@@ -1,23 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2008 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. #
-# #
-#########################################################################
-
-set -e
-cd `dirname $0`/..
-. build/targets.sh
-set -x
-
-# If you modify this list, modify it also in boot.sh
-STDLIB_MODULES='Pervasives,Arg,Array,Buffer,Char,Digest,Filename,Format,Hashtbl,Lazy,Lexing,List,Map,Printexc,Printf,Scanf,Set,String,Sys,Parsing,Int32,Int64,Nativeint,Obj,Queue,Sort,Stream,Stack'
-
-$OCAMLBUILD -ignore "$STDLIB_MODULES" $@ byte_stdlib_mixed_mode $OCAMLC_BYTE $OCAMLLEX_BYTE $CAMLP4_BYTE
diff --git a/build/camlp4-mkCamlp4Ast.sh b/build/camlp4-mkCamlp4Ast.sh
deleted file mode 100755
index 0ff20e8b2..000000000
--- a/build/camlp4-mkCamlp4Ast.sh
+++ /dev/null
@@ -1,36 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2010 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. #
-# #
-#########################################################################
-
-set -e
-cd `dirname $0`/..
-
-. config/config.sh
-export PATH=$BINDIR:$PATH
-
-CAMLP4AST=camlp4/Camlp4/Struct/Camlp4Ast.ml
-BOOTP4AST=camlp4/boot/Camlp4Ast.ml
-
-[ -f "$BOOTP4AST" ] && mv "$BOOTP4AST" "$BOOTP4AST.old"
-rm -f "_build/$BOOTP4AST"
-rm -f "_build/$CAMLP4AST"
-
-if [ -x ./boot/myocamlbuild.native ]; then
- OCAMLBUILD=./boot/myocamlbuild.native
-else
- OCAMLBUILD="./boot/ocamlrun boot/myocamlbuild"
-fi
-$OCAMLBUILD $CAMLP4AST
-
-echo promote $CAMLP4AST
-cp _build/$CAMLP4AST camlp4/boot/`basename $CAMLP4AST`
diff --git a/build/camlp4-native-only.sh b/build/camlp4-native-only.sh
deleted file mode 100755
index d53395c23..000000000
--- a/build/camlp4-native-only.sh
+++ /dev/null
@@ -1,23 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2008 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. #
-# #
-#########################################################################
-
-set -e
-cd `dirname $0`/..
-. build/targets.sh
-set -x
-
-# If you modify this list, modify it also in boot.sh
-STDLIB_MODULES='Pervasives,Arg,Array,Buffer,Char,Digest,Filename,Format,Hashtbl,Lazy,Lexing,List,Map,Printexc,Printf,Scanf,Set,String,Sys,Parsing,Int32,Int64,Nativeint,Obj,Queue,Sort,Stream,Stack'
-
-$OCAMLBUILD -ignore "$STDLIB_MODULES" $@ native_stdlib_mixed_mode $OCAMLOPT_BYTE $OCAMLLEX_BYTE $CAMLP4_NATIVE
diff --git a/build/camlp4-targets.sh b/build/camlp4-targets.sh
deleted file mode 100644
index 8fbaafb59..000000000
--- a/build/camlp4-targets.sh
+++ /dev/null
@@ -1,46 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-CAMLP4_COMMON="\
- camlp4/Camlp4/Camlp4Ast.partial.ml \
- camlp4/boot/camlp4boot.byte"
-CAMLP4_BYTE="$CAMLP4_COMMON \
- camlp4/Camlp4.cmo \
- camlp4/Camlp4Top.cmo \
- camlp4/camlp4prof.byte$EXE \
- camlp4/mkcamlp4.byte$EXE \
- camlp4/camlp4.byte$EXE \
- camlp4/camlp4fulllib.cma"
-CAMLP4_NATIVE="$CAMLP4_COMMON \
- camlp4/Camlp4.cmx \
- camlp4/Camlp4Top.cmx \
- camlp4/camlp4prof.native$EXE \
- camlp4/mkcamlp4.native$EXE \
- camlp4/camlp4.native$EXE \
- camlp4/camlp4fulllib.cmxa"
-
-for i in camlp4boot camlp4r camlp4rf camlp4o camlp4of camlp4oof camlp4orf; do
- CAMLP4_BYTE="$CAMLP4_BYTE camlp4/$i.byte$EXE camlp4/$i.cma"
- CAMLP4_NATIVE="$CAMLP4_NATIVE camlp4/$i.native$EXE"
-done
-
-cd camlp4
-for dir in Camlp4Parsers Camlp4Printers Camlp4Filters; do
- for file in $dir/*.ml; do
- base=camlp4/$dir/`basename $file .ml`
- CAMLP4_BYTE="$CAMLP4_BYTE $base.cmo"
- CAMLP4_NATIVE="$CAMLP4_NATIVE $base.cmx $base.$O"
- done
-done
-cd ..
diff --git a/build/distclean.sh b/build/distclean.sh
deleted file mode 100755
index 6e978eecc..000000000
--- a/build/distclean.sh
+++ /dev/null
@@ -1,37 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-cd `dirname $0`/..
-set -ex
-(cd byterun && make clean) || :
-(cd asmrun && make clean) || :
-(cd yacc && make clean) || :
-rm -f build/ocamlbuild_mixed_mode
-rm -rf _build
-rm -f boot/ocamlrun boot/ocamlrun.exe boot/camlheader \
- boot/myocamlbuild boot/myocamlbuild.native boot/myocamlbuild.native.exe \
- myocamlbuild_config.ml config/config.sh config/Makefile \
- boot/ocamlyacc tools/cvt_emit.bak tools/*.bak \
- config/s.h config/m.h boot/*.cm* _log _*_log*
-
-# from partial boot
-rm -f driver/main.byte driver/optmain.byte lex/main.byte \
- tools/ocamlmklib.byte \
- tools/myocamlbuild_config.ml
-
-# from ocamlbuild bootstrap
-rm -f ocamlbuild/_log ocamlbuild/,ocamlbuild.byte.start \
- ocamlbuild/boot/ocamlbuild ocamlbuild/myocamlbuild_config.ml \
- ocamlbuild/myocamlbuild_config.mli
-rm -rf ocamlbuild/_build ocamlbuild/_start
diff --git a/build/fastworld.sh b/build/fastworld.sh
deleted file mode 100755
index 389a8a8d9..000000000
--- a/build/fastworld.sh
+++ /dev/null
@@ -1,48 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2008 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. #
-# #
-#########################################################################
-
-cd `dirname $0`
-set -e
-if [ -e ocamlbuild_mixed_mode ]; then
- echo ocamlbuild mixed mode detected
- echo 'please cleanup and re-launch (make clean ; ./build/distclean.sh)'
- exit 1
-fi
-./mkconfig.sh
-./mkmyocamlbuild_config.sh
-./boot-c-parts.sh
-./boot.sh $@
-
-cd ..
-. build/targets.sh
-OCAMLMKLIB_BYTE="tools/ocamlmklib.byte"
-set -x
-$OCAMLBUILD $@ -log _boot_fast_log \
- $STDLIB_BYTE $OCAMLOPT_BYTE $STDLIB_NATIVE \
- $OCAMLOPT_NATIVE $OCAMLMKLIB_BYTE $OTHERLIBS_UNIX_NATIVE $OCAMLBUILD_NATIVE
-
-rm -f _build/myocamlbuild
-boot/ocamlrun boot/myocamlbuild \
- -just-plugin -install-lib-dir _build/ocamlbuild \
- -ocamlopt "../_build/ocamlopt.opt -nostdlib -I boot -I stdlib -I $UNIXDIR"
-cp _build/myocamlbuild boot/myocamlbuild.native
-
-./boot/myocamlbuild.native $@ \
- $OCAMLC_NATIVE $TOPLEVEL $OTHERLIBS_BYTE $OTHERLIBS_NATIVE $OCAMLLEX_BYTE \
- $OCAMLLEX_NATIVE $TOOLS_BYTE $TOOLS_NATIVE $DEBUGGER \
- $OCAMLDOC_BYTE $OCAMLDOC_NATIVE $OCAMLBUILD_BYTE
-
-cd tools
-make objinfo_helper
-cd ..
diff --git a/build/install.sh b/build/install.sh
deleted file mode 100755
index de2802e70..000000000
--- a/build/install.sh
+++ /dev/null
@@ -1,475 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-set -e
-
-cd `dirname $0`/..
-
-. config/config.sh
-
-not_installed=$PWD/_build/not_installed
-
-rm -f "$not_installed"
-touch "$not_installed"
-
-wontinstall() {
- echo "$1" >> "$not_installed"
- echo " don't install $1"
-}
-
-installbin() {
- if [ -f "$1" ]; then
- echo " install binary $2"
- cp -f "$1" "$2"
- [ -x "$2" ] || chmod +x "$2"
- else
- wontinstall "$1"
- fi
-}
-
-installbestbin() {
- if [ -f "$1" ]; then
- echo " install binary $3 (with `basename $1`)"
- cp -f "$1" "$3"
- else
- if [ -f "$2" ]; then
- echo " install binary $3 (with `basename $2`)"
- cp -f "$2" "$3"
- else
- echo "None of $1, $2 exists"
- exit 3
- fi
- fi
- [ -x "$3" ] || chmod +x "$3"
-}
-
-installlib() {
- if [ -f "$1" ]; then
- dest="$2/`basename $1`"
- echo " install library $dest"
- cp -f "$1" "$2"
- if [ "$RANLIB" != "" ]; then
- "$RANLIB" "$dest"
- fi
- else
- wontinstall "$1"
- fi
-}
-
-installdir() {
- args=""
- while [ $# -gt 1 ]; do
- if [ -f "$1" ]; then
- args="$args $1"
- else
- wontinstall "$1"
- fi
- shift
- done
- last="$1"
- for file in $args; do
- echo " install $last/`basename $file`"
- cp -f "$file" "$last"
- done
-}
-
-installlibdir() {
- args=""
- while [ $# -gt 1 ]; do
- args="$args $1"
- shift
- done
- last="$1"
- for file in $args; do
- installlib "$file" "$last"
- done
-}
-
-mkdir -p $BINDIR
-mkdir -p $LIBDIR
-mkdir -p $LIBDIR/caml
-mkdir -p $LIBDIR/vmthreads
-mkdir -p $LIBDIR/threads
-mkdir -p $LIBDIR/ocamlbuild
-mkdir -p $LIBDIR/ocamldoc
-mkdir -p $LIBDIR/ocamldoc/custom
-mkdir -p $STUBLIBDIR
-mkdir -p $MANDIR/man1
-mkdir -p $MANDIR/man3
-mkdir -p $MANDIR/man$MANEXT
-
-echo "Installing core libraries..."
-installlibdir byterun/libcamlrun.$A asmrun/libasmrun.$A asmrun/libasmrunp.$A \
- $LIBDIR
-installdir byterun/libcamlrun_shared$EXT_DLL $LIBDIR
-
-PUBLIC_INCLUDES="\
- alloc.h callback.h config.h custom.h fail.h intext.h \
- memory.h misc.h mlvalues.h printexc.h signals.h compatibility.h"
-
-cd byterun
-for i in $PUBLIC_INCLUDES; do
- echo " install caml/$i"
- sed -f ../tools/cleanup-header $i > $LIBDIR/caml/$i
-done
-cd ..
-
-WIN32=""
-if [ "x$EXE" = "x.exe" ]; then
- installbin win32caml/ocamlwin.exe $PREFIX/OCamlWin.exe
- WIN32=win32
-fi
-
-installdir otherlibs/"$WIN32"unix/unixsupport.h \
- otherlibs/bigarray/bigarray.h \
- $LIBDIR/caml
-
-installdir yacc/ocamlyacc$EXE byterun/ocamlrun$EXE $BINDIR
-
-installdir config/Makefile $LIBDIR/Makefile.config
-installdir byterun/ld.conf $LIBDIR
-
-cd _build
-
-echo "Installing the toplevel and compilers..."
-installbin ocaml$EXE $BINDIR/ocaml$EXE
-installbin ocamlc$EXE $BINDIR/ocamlc$EXE
-installbin ocamlopt$EXE $BINDIR/ocamlopt$EXE
-installbin ocamlc.opt$EXE $BINDIR/ocamlc.opt$EXE
-installbin ocamlopt.opt$EXE $BINDIR/ocamlopt.opt$EXE
-
-set=set # coloration workaround
-
-echo "Installing the standard library..."
-installdir \
- stdlib/stdlib.cma \
- stdlib/stdlib.cmxa stdlib/stdlib.p.cmxa \
- stdlib/camlheader \
- stdlib/camlheader_ur \
- stdlib/std_exit.cm[io] stdlib/std_exit.ml \
- stdlib/arg.cmi stdlib/arg.ml stdlib/arg.mli \
- stdlib/array.cmi stdlib/array.ml stdlib/array.mli \
- stdlib/arrayLabels.cmi stdlib/arrayLabels.ml stdlib/arrayLabels.mli \
- stdlib/buffer.cmi stdlib/buffer.ml stdlib/buffer.mli \
- stdlib/callback.cmi stdlib/callback.ml stdlib/callback.mli \
- stdlib/camlinternalLazy.cmi stdlib/camlinternalLazy.ml stdlib/camlinternalLazy.mli \
- stdlib/camlinternalMod.cmi stdlib/camlinternalMod.ml stdlib/camlinternalMod.mli \
- stdlib/camlinternalOO.cmi stdlib/camlinternalOO.ml stdlib/camlinternalOO.mli \
- stdlib/char.cmi stdlib/char.ml stdlib/char.mli \
- stdlib/complex.cmi stdlib/complex.ml stdlib/complex.mli \
- stdlib/digest.cmi stdlib/digest.ml stdlib/digest.mli \
- stdlib/filename.cmi stdlib/filename.ml stdlib/filename.mli \
- stdlib/format.cmi stdlib/format.ml stdlib/format.mli \
- stdlib/gc.cmi stdlib/gc.ml stdlib/gc.mli \
- stdlib/genlex.cmi stdlib/genlex.ml stdlib/genlex.mli \
- stdlib/hashtbl.cmi stdlib/hashtbl.ml stdlib/hashtbl.mli \
- stdlib/int32.cmi stdlib/int32.ml stdlib/int32.mli \
- stdlib/int64.cmi stdlib/int64.ml stdlib/int64.mli \
- stdlib/lazy.cmi stdlib/lazy.ml stdlib/lazy.mli \
- stdlib/lexing.cmi stdlib/lexing.ml stdlib/lexing.mli \
- stdlib/list.cmi stdlib/list.ml stdlib/list.mli \
- stdlib/listLabels.cmi stdlib/listLabels.ml stdlib/listLabels.mli \
- stdlib/map.cmi stdlib/map.ml stdlib/map.mli \
- stdlib/marshal.cmi stdlib/marshal.ml stdlib/marshal.mli \
- stdlib/moreLabels.cmi stdlib/moreLabels.ml stdlib/moreLabels.mli \
- stdlib/nativeint.cmi stdlib/nativeint.ml stdlib/nativeint.mli \
- stdlib/obj.cmi stdlib/obj.ml stdlib/obj.mli \
- stdlib/oo.cmi stdlib/oo.ml stdlib/oo.mli \
- stdlib/parsing.cmi stdlib/parsing.ml stdlib/parsing.mli \
- stdlib/pervasives.cmi stdlib/pervasives.ml stdlib/pervasives.mli \
- stdlib/printexc.cmi stdlib/printexc.ml stdlib/printexc.mli \
- stdlib/printf.cmi stdlib/printf.ml stdlib/printf.mli \
- stdlib/queue.cmi stdlib/queue.ml stdlib/queue.mli \
- stdlib/random.cmi stdlib/random.ml stdlib/random.mli \
- stdlib/scanf.cmi stdlib/scanf.ml stdlib/scanf.mli \
- stdlib/sort.cmi stdlib/sort.ml stdlib/sort.mli \
- stdlib/stack.cmi stdlib/stack.ml stdlib/stack.mli \
- stdlib/stdLabels.cmi stdlib/stdLabels.ml stdlib/stdLabels.mli \
- stdlib/stream.cmi stdlib/stream.ml stdlib/stream.mli \
- stdlib/string.cmi stdlib/string.ml stdlib/string.mli \
- stdlib/stringLabels.cmi stdlib/stringLabels.ml stdlib/stringLabels.mli \
- stdlib/sys.cmi stdlib/sys.ml stdlib/sys.mli \
- stdlib/weak.cmi stdlib/weak.ml stdlib/weak.mli \
- stdlib/$set.cmi stdlib/$set.ml stdlib/$set.mli \
- stdlib/arg.cmx stdlib/arg.p.cmx \
- stdlib/array.cmx stdlib/array.p.cmx \
- stdlib/arrayLabels.cmx stdlib/arrayLabels.p.cmx \
- stdlib/buffer.cmx stdlib/buffer.p.cmx \
- stdlib/callback.cmx stdlib/callback.p.cmx \
- stdlib/camlinternalLazy.cmx stdlib/camlinternalLazy.p.cmx \
- stdlib/camlinternalMod.cmx stdlib/camlinternalMod.p.cmx \
- stdlib/camlinternalOO.cmx stdlib/camlinternalOO.p.cmx \
- stdlib/char.cmx stdlib/char.p.cmx \
- stdlib/complex.cmx stdlib/complex.p.cmx \
- stdlib/digest.cmx stdlib/digest.p.cmx \
- stdlib/filename.cmx stdlib/filename.p.cmx \
- stdlib/format.cmx stdlib/format.p.cmx \
- stdlib/gc.cmx stdlib/gc.p.cmx \
- stdlib/genlex.cmx stdlib/genlex.p.cmx \
- stdlib/hashtbl.cmx stdlib/hashtbl.p.cmx \
- stdlib/int32.cmx stdlib/int32.p.cmx \
- stdlib/int64.cmx stdlib/int64.p.cmx \
- stdlib/lazy.cmx stdlib/lazy.p.cmx \
- stdlib/lexing.cmx stdlib/lexing.p.cmx \
- stdlib/list.cmx stdlib/list.p.cmx \
- stdlib/listLabels.cmx stdlib/listLabels.p.cmx \
- stdlib/map.cmx stdlib/map.p.cmx \
- stdlib/marshal.cmx stdlib/marshal.p.cmx \
- stdlib/moreLabels.cmx stdlib/moreLabels.p.cmx \
- stdlib/nativeint.cmx stdlib/nativeint.p.cmx \
- stdlib/obj.cmx stdlib/obj.p.cmx \
- stdlib/oo.cmx stdlib/oo.p.cmx \
- stdlib/parsing.cmx stdlib/parsing.p.cmx \
- stdlib/pervasives.cmx stdlib/pervasives.p.cmx \
- stdlib/printexc.cmx stdlib/printexc.p.cmx \
- stdlib/printf.cmx stdlib/printf.p.cmx \
- stdlib/queue.cmx stdlib/queue.p.cmx \
- stdlib/random.cmx stdlib/random.p.cmx \
- stdlib/scanf.cmx stdlib/scanf.p.cmx \
- stdlib/sort.cmx stdlib/sort.p.cmx \
- stdlib/stack.cmx stdlib/stack.p.cmx \
- stdlib/stdLabels.cmx stdlib/stdLabels.p.cmx \
- stdlib/std_exit.cmx stdlib/std_exit.p.cmx stdlib/std_exit.$O stdlib/std_exit.p.$O \
- stdlib/stream.cmx stdlib/stream.p.cmx \
- stdlib/string.cmx stdlib/string.p.cmx \
- stdlib/stringLabels.cmx stdlib/stringLabels.p.cmx \
- stdlib/sys.cmx stdlib/sys.p.cmx \
- stdlib/weak.cmx stdlib/weak.p.cmx \
- stdlib/$set.cmx stdlib/$set.p.cmx \
- $LIBDIR
-
-installlibdir \
- stdlib/stdlib.$A stdlib/stdlib.p.$A \
- $LIBDIR
-
-echo "Installing ocamllex, ocamldebug..."
-installbin lex/ocamllex$EXE $BINDIR/ocamllex$EXE
-installbin debugger/ocamldebug$EXE $BINDIR/ocamldebug$EXE
-installbin lex/ocamllex.opt$EXE $BINDIR/ocamllex.opt$EXE
-installbin tools/ocamldep.native$EXE $BINDIR/ocamldep.opt$EXE
-
-echo "Installing some tools..."
-installbin tools/objinfo.byte$EXE $BINDIR/ocamlobjinfo$EXE
-installbin ../tools/objinfo_helper$EXE $LIBDIR/objinfo_helper$EXE
-installbin tools/ocamlcp.byte$EXE $BINDIR/ocamlcp$EXE
-installbin tools/ocamldep.byte$EXE $BINDIR/ocamldep$EXE
-installbin tools/ocamlmklib.byte$EXE $BINDIR/ocamlmklib$EXE
-installbin tools/ocamlmktop.byte$EXE $BINDIR/ocamlmktop$EXE
-installbin tools/ocamlprof.byte$EXE $BINDIR/ocamlprof$EXE
-installbin toplevel/expunge.byte$EXE $LIBDIR/expunge$EXE
-installbin tools/addlabels.byte $LIBDIR/addlabels
-installbin tools/scrapelabels.byte $LIBDIR/scrapelabels
-installbin otherlibs/dynlink/extract_crc.byte $LIBDIR/extract_crc
-
-echo "Installing libraries..."
-installdir \
- otherlibs/bigarray/bigarray.cma \
- otherlibs/dbm/dbm.cma \
- otherlibs/dynlink/dynlink.cma \
- otherlibs/"$WIN32"graph/graphics.cma \
- otherlibs/num/nums.cma \
- otherlibs/str/str.cma \
- otherlibs/"$WIN32"unix/unix.cma \
- otherlibs/bigarray/bigarray.cmxa \
- otherlibs/dbm/dbm.cmxa \
- otherlibs/dynlink/dynlink.cmxa \
- otherlibs/"$WIN32"graph/graphics.cmxa \
- otherlibs/num/nums.cmxa \
- otherlibs/str/str.cmxa \
- otherlibs/"$WIN32"unix/unix.cmxa \
- toplevel/toplevellib.cma \
- otherlibs/systhreads/thread.mli \
- otherlibs/systhreads/mutex.mli \
- otherlibs/systhreads/condition.mli \
- otherlibs/systhreads/event.mli \
- otherlibs/systhreads/threadUnix.mli \
- $LIBDIR
-
-installdir \
- otherlibs/systhreads/threads.cma \
- otherlibs/systhreads/threads.cmxa \
- otherlibs/systhreads/thread.cmi \
- otherlibs/systhreads/thread.cmx \
- otherlibs/systhreads/mutex.cmi \
- otherlibs/systhreads/mutex.cmx \
- otherlibs/systhreads/condition.cmi \
- otherlibs/systhreads/condition.cmx \
- otherlibs/systhreads/event.cmi \
- otherlibs/systhreads/event.cmx \
- otherlibs/systhreads/threadUnix.cmi \
- otherlibs/systhreads/threadUnix.cmx \
- $LIBDIR/threads
-
-installdir \
- otherlibs/bigarray/dllbigarray$EXT_DLL \
- otherlibs/dbm/dllmldbm$EXT_DLL \
- otherlibs/"$WIN32"graph/dllgraphics$EXT_DLL \
- otherlibs/num/dllnums$EXT_DLL \
- otherlibs/str/dllstr$EXT_DLL \
- otherlibs/systhreads/dllthreads$EXT_DLL \
- otherlibs/"$WIN32"unix/dllunix$EXT_DLL \
- otherlibs/threads/dllvmthreads$EXT_DLL \
- $STUBLIBDIR
-
-installlibdir \
- otherlibs/threads/libvmthreads.$A \
- $LIBDIR/vmthreads
-
-installdir \
- otherlibs/threads/thread.cmi \
- otherlibs/threads/thread.mli \
- otherlibs/threads/mutex.cmi \
- otherlibs/threads/mutex.mli \
- otherlibs/threads/condition.cmi \
- otherlibs/threads/condition.mli \
- otherlibs/threads/event.cmi \
- otherlibs/threads/event.mli \
- otherlibs/threads/threadUnix.cmi \
- otherlibs/threads/threadUnix.mli \
- otherlibs/threads/threads.cma \
- otherlibs/threads/stdlib.cma \
- otherlibs/threads/unix.cma \
- $LIBDIR/vmthreads
-
-installlibdir \
- otherlibs/bigarray/libbigarray.$A \
- otherlibs/dbm/libmldbm.$A \
- otherlibs/"$WIN32"graph/libgraphics.$A \
- otherlibs/num/libnums.$A \
- otherlibs/str/libstr.$A \
- otherlibs/systhreads/libthreads.$A \
- otherlibs/systhreads/libthreadsnat.$A \
- otherlibs/"$WIN32"unix/libunix.$A \
- $LIBDIR
-
-echo "Installing object files and interfaces..."
-installdir \
- tools/profiling.cm[oi] \
- toplevel/topstart.cmo \
- toplevel/toploop.cmi \
- toplevel/topdirs.cmi \
- toplevel/topmain.cmi \
- typing/outcometree.cmi \
- typing/outcometree.mli \
- otherlibs/graph/graphicsX11.cmi \
- otherlibs/graph/graphicsX11.mli \
- otherlibs/dynlink/dynlink.cmi \
- otherlibs/dynlink/dynlink.mli \
- otherlibs/num/arith_status.cmi \
- otherlibs/num/arith_status.mli \
- otherlibs/num/big_int.cmi \
- otherlibs/num/big_int.mli \
- otherlibs/num/nat.cmi \
- otherlibs/num/nat.mli \
- otherlibs/num/num.cmi \
- otherlibs/num/num.mli \
- otherlibs/num/ratio.cmi \
- otherlibs/num/ratio.mli \
- otherlibs/bigarray/bigarray.cmi \
- otherlibs/bigarray/bigarray.mli \
- otherlibs/dbm/dbm.cmi \
- otherlibs/dbm/dbm.mli \
- otherlibs/dynlink/dynlink.cmx \
- otherlibs/"$WIN32"graph/graphics.cmi \
- otherlibs/"$WIN32"graph/graphics.mli \
- otherlibs/str/str.cmi \
- otherlibs/str/str.mli \
- otherlibs/"$WIN32"unix/unix.cmi \
- otherlibs/"$WIN32"unix/unix.mli \
- otherlibs/"$WIN32"unix/unixLabels.cmi \
- otherlibs/"$WIN32"unix/unixLabels.mli \
- otherlibs/num/arith_flags.cmx \
- otherlibs/num/int_misc.cmx \
- otherlibs/num/arith_status.cmx \
- otherlibs/num/big_int.cmx \
- otherlibs/num/nat.cmx \
- otherlibs/num/num.cmx \
- otherlibs/num/ratio.cmx \
- otherlibs/bigarray/bigarray.cmx \
- otherlibs/dbm/dbm.cmx \
- otherlibs/"$WIN32"graph/graphics.cmx \
- otherlibs/graph/graphicsX11.cmx \
- otherlibs/str/str.cmx \
- otherlibs/"$WIN32"unix/unix.cmx \
- otherlibs/"$WIN32"unix/unixLabels.cmx \
- $LIBDIR
-
-installlibdir \
- otherlibs/bigarray/bigarray.$A \
- otherlibs/dbm/dbm.$A \
- otherlibs/dynlink/dynlink.$A \
- otherlibs/"$WIN32"graph/graphics.$A \
- otherlibs/num/nums.$A \
- otherlibs/str/str.$A \
- otherlibs/"$WIN32"unix/unix.$A \
- stdlib/stdlib.$A \
- $LIBDIR
-
-installlibdir \
- otherlibs/systhreads/threads.$A \
- $LIBDIR/threads
-
-echo "Installing manuals..."
-(cd ../man && make install)
-
-echo "Installing ocamldoc..."
-installbin ocamldoc/ocamldoc $BINDIR/ocamldoc$EXE
-installbin ocamldoc/ocamldoc.opt $BINDIR/ocamldoc.opt$EXE
-
-installdir \
- ../ocamldoc/ocamldoc.hva \
- ocamldoc/*.cmi \
- ocamldoc/odoc_info.mli ocamldoc/odoc_info.cm[ia] ocamldoc/odoc_info.cmxa \
- ocamldoc/odoc_info.$A \
- $LIBDIR/ocamldoc
-
-installdir \
- ocamldoc/stdlib_man/* \
- $MANDIR/man3
-
-echo "Installing ocamlbuild..."
-
-cd ocamlbuild
-installbin ocamlbuild.byte$EXE $BINDIR/ocamlbuild.byte$EXE
-installbin ocamlbuild.native$EXE $BINDIR/ocamlbuild.native$EXE
-installbestbin ocamlbuild.native$EXE ocamlbuild.byte$EXE $BINDIR/ocamlbuild$EXE
-
-installlibdir \
- ocamlbuildlib.$A \
- $LIBDIR/ocamlbuild
-
-installdir \
- ocamlbuildlib.cmxa \
- ocamlbuildlib.cma \
- ocamlbuild_plugin.cmi \
- ocamlbuild_plugin.cmo \
- ocamlbuild_plugin.cmx \
- ocamlbuild_pack.cmi \
- ocamlbuild_unix_plugin.cmi \
- ocamlbuild_unix_plugin.cmo \
- ocamlbuild_unix_plugin.cmx \
- ocamlbuild_unix_plugin.$O \
- ocamlbuild_executor.cmi \
- ocamlbuild_executor.cmo \
- ocamlbuild_executor.cmx \
- ocamlbuild_executor.$O \
- ocamlbuild.cmo \
- ocamlbuild.cmx \
- ocamlbuild.$O \
- $LIBDIR/ocamlbuild
-cd ..
-
-installdir \
- ../ocamlbuild/man/ocamlbuild.1 \
- $MANDIR/man1
diff --git a/build/mixed-boot.sh b/build/mixed-boot.sh
deleted file mode 100755
index 133f8cff8..000000000
--- a/build/mixed-boot.sh
+++ /dev/null
@@ -1,22 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-set -ex
-cd `dirname $0`/..
-touch build/ocamlbuild_mixed_mode
-mkdir -p _build
-cp -rf boot _build/
-./build/mkconfig.sh
-./build/mkmyocamlbuild_config.sh
-./build/boot.sh
diff --git a/build/mkconfig.sh b/build/mkconfig.sh
deleted file mode 100755
index 8cf1773dd..000000000
--- a/build/mkconfig.sh
+++ /dev/null
@@ -1,27 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-cd `dirname $0`/..
-
-sed -e 's/^\(.*\$([0-9]).*\)$/# \1/' \
- -e 's/\$(\([^)]*\))/${\1}/g' \
- -e 's/^FLEX.*$//g' \
- -e 's/^\([^#=]*\)=\([^"]*\)$/if [ "x$\1" = "x" ]; then \1="\2"; fi/' \
- config/Makefile > config/config.sh
-
-if [ "x$EXE" = "x.exe" -a "x$SYSTEM" != "xcygwin" ]; then
- echo "WINDOWS=true" >> config/config.sh
-else
- echo "WINDOWS=false" >> config/config.sh
-fi
diff --git a/build/mkmyocamlbuild_config.sh b/build/mkmyocamlbuild_config.sh
deleted file mode 100755
index 75d6e9ca6..000000000
--- a/build/mkmyocamlbuild_config.sh
+++ /dev/null
@@ -1,40 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-cd `dirname $0`/..
-
-sed \
- -e 's/^.*FLEXDIR.*$//g' \
- -e '/^SET_LD_PATH/d' \
- -e 's/^#ml \(.*\)/\1/' \
- -e 's/^\([^"][^"]*\("[^"]*"[^"]*\)*\)#.*$/\1/' \
- -e 's/^\(#.*\)$/(* \1 *)/' \
- -e 's/^\(.*\$([0-9]).*\)$/(* \1 *)/' \
- -e 's/^\([^(=]*\)=\([^"]*\)$/let <:lower<\1>> = "\2";;/' \
- -e 's/\$(AS)/as/g' \
- -e 's/\$(\([^)]*\))/"\^<:lower<\1>>\^"/g' \
- -e 's/""\^//g' \
- -e 's/\^""//g' \
- -e 's/^let <:lower<MAKE.*$//g' \
- -e 's/^let <:lower<DO.*$//g' \
- -e 's/"true"/true/g' \
- -e 's/"false"/false/g' \
- config/Makefile \
- | sed -f build/tolower.sed \
- | sed -f build/tolower.sed \
- | sed -f build/tolower.sed \
- | sed -f build/tolower.sed \
- | sed -f build/tolower.sed \
- | sed -f build/tolower.sed \
- > myocamlbuild_config.ml
diff --git a/build/mkruntimedef.sh b/build/mkruntimedef.sh
deleted file mode 100755
index a1bf141ed..000000000
--- a/build/mkruntimedef.sh
+++ /dev/null
@@ -1,21 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-echo 'let builtin_exceptions = [|'; \
-sed -n -e 's|.*/\* \("[A-Za-z_]*"\) \*/$| \1;|p' byterun/fail.h | \
-sed -e '$s/;$//'; \
-echo '|]'; \
-echo 'let builtin_primitives = [|'; \
-sed -e 's/.*/ "&";/' -e '$s/;$//' byterun/primitives; \
-echo '|]'
diff --git a/build/myocamlbuild.sh b/build/myocamlbuild.sh
deleted file mode 100755
index 34ad894f9..000000000
--- a/build/myocamlbuild.sh
+++ /dev/null
@@ -1,31 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, Berke Durak, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-cd `dirname $0`/..
-set -xe
-if [ ! -x _build/ocamlbuild/ocamlbuildlight.byte ]; then
- if [ ! -x ocamlbuild/_build/ocamlbuildlight.byte ]; then
- (cd ocamlbuild && ${GNUMAKE:-make})
- fi
- mkdir -p _build/ocamlbuild
- for i in "light.cmo" "light.byte" "lightlib.cma" "_plugin.cmi" "_pack.cmi"
- do
- cp ocamlbuild/_build/ocamlbuild$i _build/ocamlbuild
- done
-fi
-rm -f ocamlbuild/myocamlbuild_config.ml ocamlbuild/myocamlbuild_config.mli
-rm -rf _build/myocamlbuild boot/myocamlbuild boot/myocamlbuild.native
-./boot/ocamlrun _build/ocamlbuild/ocamlbuildlight.byte -no-hygiene \
- -tag debug -install-lib-dir _build/ocamlbuild -byte-plugin -just-plugin
-cp _build/myocamlbuild boot/myocamlbuild.boot
diff --git a/build/new-build-system b/build/new-build-system
deleted file mode 100644
index 60018e40e..000000000
--- a/build/new-build-system
+++ /dev/null
@@ -1,47 +0,0 @@
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-_tags # Defines tags to setup exceptions
-myocamlbuild.ml # Contains all needed rules that are differents
-boot/ocamldep
-myocamlbuild_config.mli
-utils/config.mlbuild # Should be renamed as utils/config.ml
-
-# Files that just contain module names of object files.
-**/*.mllib # Files that describe the contents of an OCaml library
-**/*.mlpack # Files that describe the contents of an OCaml package
-**/*.cilb # Files that describe the contents of an C static library
-**/*.dilb # Files that describe the contents of an C dynamic library
-
-build/
- world.sh # Build all the OCaml world
- world.byte.sh # Build the bytecode world
- world.native.sh # Build the native world
- world.all.sh # Build all the world the don't bootstrap
- fastworld.sh # Same as above but faster
- boot-c-parts.sh # Compile byterun, ocamlyacc and asmrun with the Makefiles
- boot.sh # Compile the stdlib and ocamlc
- otherlibs-targets.sh # Setup otherlibs targets
- targets.sh # All targets of the OCaml distribution
-
-
- install.sh # Install all needed files
- distclean.sh # Clean all generated files
-
- myocamlbuild.sh # Regenerate the boot/myocamlbuild program
- mkconfig.sh # Generate config/config.sh
- mkmyocamlbuild_config.sh # Generate myocamlbuild_config.ml
-
- # Partial stuffs
- mixed-boot.sh
- ocamlbuild-byte-only.sh
- ocamlbuild-native-only.sh
diff --git a/build/ocamlbuild-byte-only.sh b/build/ocamlbuild-byte-only.sh
deleted file mode 100755
index aeb5bcba9..000000000
--- a/build/ocamlbuild-byte-only.sh
+++ /dev/null
@@ -1,19 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2008 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. #
-# #
-#########################################################################
-
-set -e
-cd `dirname $0`/..
-. build/targets.sh
-set -x
-$OCAMLBUILD $@ byte_stdlib_mixed_mode $OCAMLC_BYTE $OCAMLLEX_BYTE $OCAMLBUILD_BYTE
diff --git a/build/ocamlbuild-native-only.sh b/build/ocamlbuild-native-only.sh
deleted file mode 100755
index 4d7decfc0..000000000
--- a/build/ocamlbuild-native-only.sh
+++ /dev/null
@@ -1,19 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2008 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. #
-# #
-#########################################################################
-
-set -e
-cd `dirname $0`/..
-. build/targets.sh
-set -x
-$OCAMLBUILD $@ native_stdlib_mixed_mode $OCAMLOPT_BYTE $OCAMLLEX_BYTE $OCAMLBUILD_NATIVE
diff --git a/build/ocamlbuildlib-native-only.sh b/build/ocamlbuildlib-native-only.sh
deleted file mode 100755
index 285c561a0..000000000
--- a/build/ocamlbuildlib-native-only.sh
+++ /dev/null
@@ -1,19 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2008 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. #
-# #
-#########################################################################
-
-set -e
-cd `dirname $0`/..
-. build/targets.sh
-set -x
-$OCAMLBUILD $@ native_stdlib_mixed_mode $OCAMLOPT_BYTE $OCAMLLEX_BYTE $OCAMLBUILDLIB_NATIVE
diff --git a/build/otherlibs-targets.sh b/build/otherlibs-targets.sh
deleted file mode 100644
index 9b470c843..000000000
--- a/build/otherlibs-targets.sh
+++ /dev/null
@@ -1,103 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2008 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. #
-# #
-#########################################################################
-
-OTHERLIBS_BYTE=""
-OTHERLIBS_NATIVE=""
-OTHERLIBS_UNIX_NATIVE=""
-UNIXDIR="otherlibs/unix"
-
-add_native() {
- for native_file in $@; do
- OTHERLIBS_NATIVE="$OTHERLIBS_NATIVE otherlibs/$lib/$native_file"
- case $lib in
- unix|win32unix)
- OTHERLIBS_UNIX_NATIVE="$OTHERLIBS_UNIX_NATIVE otherlibs/$lib/$native_file";;
- esac
- done
-}
-
-add_byte() {
- for byte_file in $@; do
- OTHERLIBS_BYTE="$OTHERLIBS_BYTE otherlibs/$lib/$byte_file"
- done
-}
-
-add_file() {
- add_byte $@
- add_native $@
-}
-
-add_bin() {
- for bin_file in $@; do
- add_byte $bin_file.byte$EXE
- add_native $bin_file.native$EXE
- done
-}
-
-add_c_lib() {
- add_file "lib$1.$A"
-}
-
-add_ocaml_lib() {
- add_native "$1.cmxa"
- add_native "$1.$A"
- add_byte "$1.cma"
-}
-
-add_dll() {
- add_file "dll$1$EXT_DLL"
-}
-
-add() {
- add_c_lib $1
- add_ocaml_lib $1
- add_dll $1
-}
-
-THREADS_CMIS="thread.cmi mutex.cmi condition.cmi event.cmi threadUnix.cmi"
-
-for lib in $OTHERLIBRARIES; do
- case $lib in
- num)
- add nums;;
- systhreads)
- add_ocaml_lib threads
- add_dll threads
- add_file $THREADS_CMIS
- add_byte libthreads.$A
- add_native libthreadsnat.$A;;
- graph|win32graph)
- add graphics;;
- threads)
- add_byte pervasives.cmi pervasives.mli \
- $THREADS_CMIS marshal.cmi marshal.mli \
- stdlib.cma unix.cma threads.cma libvmthreads.$A;;
- dbm)
- add_ocaml_lib dbm
- add_c_lib mldbm;;
- dynlink)
- add_ocaml_lib dynlink
- add_native dynlink.cmx dynlink.$O
- add_file $lib.cmi extract_crc;;
- win32unix)
- UNIXDIR="otherlibs/win32unix"
- add_file unixsupport.h cst2constr.h socketaddr.h
- add unix;;
- unix)
- add_file unixsupport.h
- add unix;;
- *)
- add $lib
- esac
-done
diff --git a/build/partial-install.sh b/build/partial-install.sh
deleted file mode 100755
index 4a8ff502c..000000000
--- a/build/partial-install.sh
+++ /dev/null
@@ -1,157 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-######################################
-######### Copied from build/install.sh
-######################################
-
-set -e
-
-cd `dirname $0`/..
-
-. config/config.sh
-
-not_installed=$PWD/_build/not_installed
-
-rm -f "$not_installed"
-mkdir -p "$PWD/_build"
-touch "$not_installed"
-
-wontinstall() {
- echo "$1" >> "$not_installed"
- echo " don't install $1"
-}
-
-installbin() {
- if [ -f "$1" ]; then
- echo " install binary $2"
- cp -f "$1" "$2"
- [ -x "$2" ] || chmod +x "$2"
- else
- wontinstall "$1"
- fi
-}
-
-installbestbin() {
- if [ -f "$1" ]; then
- echo " install binary $3 (with `basename $1`)"
- cp -f "$1" "$3"
- else
- if [ -f "$2" ]; then
- echo " install binary $3 (with `basename $2`)"
- cp -f "$2" "$3"
- else
- echo "None of $1, $2 exists"
- exit 3
- fi
- fi
- [ -x "$3" ] || chmod +x "$3"
-}
-
-installlib() {
- if [ -f "$1" ]; then
- dest="$2/`basename $1`"
- echo " install library $dest"
- cp -f "$1" "$2"
- if [ "$RANLIB" != "" ]; then
- "$RANLIB" "$dest"
- fi
- else
- wontinstall "$1"
- fi
-}
-
-installdir() {
- args=""
- while [ $# -gt 1 ]; do
- if [ -f "$1" ]; then
- args="$args $1"
- else
- wontinstall "$1"
- fi
- shift
- done
- last="$1"
- for file in $args; do
- echo " install $last/`basename $file`"
- cp -f "$file" "$last"
- done
-}
-
-installlibdir() {
- args=""
- while [ $# -gt 1 ]; do
- args="$args $1"
- shift
- done
- last="$1"
- for file in $args; do
- installlib "$file" "$last"
- done
-}
-
-mkdir -p $BINDIR
-mkdir -p $LIBDIR
-mkdir -p $LIBDIR/ocamlbuild
-mkdir -p $STUBLIBDIR
-mkdir -p $MANDIR/man1
-mkdir -p $MANDIR/man3
-mkdir -p $MANDIR/man$MANEXT
-
-cd _build
-
-# I would have liked to test the value of ${WITH_OCAMLBUILD} instead of using
-# "test -d". However, the config.sh script that gets sourced near the top of
-# the file does: WITH_CAMLP4=${WITH_CAMLP4:-camlp4}, effectly destroying the
-# information that camlp4, ocamlbuild and others might have been disabled.
-# Of course, I tried to fix that. The config.sh file is created by mkconfig.sh
-# through an awful set of sed expressions which I don't feel confident to
-# change. -- Adrien Nader
-if test -d ocamlbuild; then
- echo "Installing ocamlbuild..."
- cd ocamlbuild
- installbin ocamlbuild.byte$EXE $BINDIR/ocamlbuild.byte$EXE
- installbin ocamlbuild.native$EXE $BINDIR/ocamlbuild.native$EXE
- installbestbin ocamlbuild.native$EXE ocamlbuild.byte$EXE \
- $BINDIR/ocamlbuild$EXE
-
- installlibdir \
- ocamlbuildlib.$A \
- $LIBDIR/ocamlbuild
-
- installdir \
- ocamlbuildlib.cmxa \
- ocamlbuildlib.cma \
- ocamlbuild_plugin.cmi \
- ocamlbuild_plugin.cmo \
- ocamlbuild_plugin.cmx \
- ocamlbuild_pack.cmi \
- ocamlbuild_unix_plugin.cmi \
- ocamlbuild_unix_plugin.cmo \
- ocamlbuild_unix_plugin.cmx \
- ocamlbuild_unix_plugin.$O \
- ocamlbuild_executor.cmi \
- ocamlbuild_executor.cmo \
- ocamlbuild_executor.cmx \
- ocamlbuild_executor.$O \
- ocamlbuild.cmo \
- ocamlbuild.cmx \
- ocamlbuild.$O \
- $LIBDIR/ocamlbuild
- cd ..
-
- installdir \
- ../ocamlbuild/man/ocamlbuild.1 \
- $MANDIR/man1
-fi
diff --git a/build/targets.sh b/build/targets.sh
deleted file mode 100644
index edc6c66bc..000000000
--- a/build/targets.sh
+++ /dev/null
@@ -1,63 +0,0 @@
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-. config/config.sh
-. build/otherlibs-targets.sh
-
-INSTALL_BIN="$BINDIR"
-export INSTALL_BIN
-
-STDLIB_BYTE="stdlib/libcamlrun.$A stdlib/stdlib.cma \
- stdlib/std_exit.cmo stdlib/camlheader stdlib/camlheader_ur"
-OCAMLLEX_BYTE=lex/ocamllex$EXE
-OCAMLC_BYTE=ocamlc$EXE
-OCAMLOPT_BYTE=ocamlopt$EXE
-OCAMLBUILD_BYTE="ocamlbuild/ocamlbuildlib.cma \
- ocamlbuild/ocamlbuildlightlib.cma \
- ocamlbuild/ocamlbuild.byte$EXE \
- ocamlbuild/ocamlbuildlight.byte$EXE"
-TOPLEVEL=ocaml$EXE
-TOOLS_BYTE="tools/objinfo.byte$EXE \
- tools/ocamldep.byte$EXE tools/profiling.cmo \
- tools/ocamlprof.byte$EXE tools/ocamlcp.byte$EXE \
- tools/ocamlmktop.byte$EXE tools/ocamlmklib$EXE \
- tools/scrapelabels.byte tools/addlabels.byte \
- tools/dumpobj.byte$EXE"
-if [ ! -z "$DEBUGGER" ]; then
- DEBUGGER=debugger/ocamldebug$EXE
-fi
-OCAMLDOC_BYTE="ocamldoc/ocamldoc$EXE ocamldoc/odoc_info.cma"
-STDLIB_NATIVE="stdlib/stdlib.cmxa stdlib/std_exit.cmx asmrun/libasmrun.$A"
-case $PROFILING in
-prof)
- STDLIB_NATIVE="$STDLIB_NATIVE asmrun/libasmrunp.$A \
- stdlib/stdlib.p.cmxa stdlib/std_exit.p.cmx";;
-noprof) ;;
-*) echo "unexpected PROFILING value $PROFILING"; exit 1;;
-esac
-OCAMLC_NATIVE=ocamlc.opt$EXE
-OCAMLOPT_NATIVE=ocamlopt.opt$EXE
-OCAMLLEX_NATIVE=lex/ocamllex.opt$EXE
-TOOLS_NATIVE=tools/ocamldep.native$EXE
-OCAMLDOC_NATIVE="ocamldoc/ocamldoc.opt$EXE ocamldoc/odoc_info.cmxa ocamldoc/stdlib_man/Pervasives.3o"
-OCAMLBUILDLIB_NATIVE="ocamlbuild/ocamlbuildlib.cmxa \
- ocamlbuild/ocamlbuildlightlib.cmxa"
-OCAMLBUILD_NATIVE="$OCAMLBUILDLIB_NATIVE \
- ocamlbuild/ocamlbuild.native$EXE \
- ocamlbuild/ocamlbuildlight.native$EXE"
-if [ -x boot/myocamlbuild.native ]; then
- OCAMLBUILD=./boot/myocamlbuild.native
-else
- OCAMLBUILD="./boot/ocamlrun boot/myocamlbuild"
-fi
-
-OCAMLBUILD="$OCAMLBUILD -no-ocamlfind"
diff --git a/build/tolower.sed b/build/tolower.sed
deleted file mode 100644
index ce0eb1651..000000000
--- a/build/tolower.sed
+++ /dev/null
@@ -1,23 +0,0 @@
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-# tolower.sed expands one ...<:lower<FOO>>... to ...foo... per line
-h
-s/.*<:lower<\(.*\)>>.*/\1/
-t cont
-b end
-:cont
-y/ABCDEFGHIJKLMNOPQRSTUVWXYZ/abcdefghijklmnopqrstuvwxyz/
-s/$/|/
-G
-s/\(.*\)|\n\(.*\)<:lower<\(.*\)>>/\2\1/
-:end
diff --git a/build/world.all.sh b/build/world.all.sh
deleted file mode 100755
index dffd88ed1..000000000
--- a/build/world.all.sh
+++ /dev/null
@@ -1,24 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-set -e
-cd `dirname $0`/..
-. build/targets.sh
-set -x
-$OCAMLBUILD $@ \
- $STDLIB_BYTE $OCAMLC_BYTE $OCAMLLEX_BYTE $OCAMLOPT_BYTE $TOPLEVEL \
- $TOOLS_BYTE $OTHERLIBS_BYTE $OCAMLBUILD_BYTE $DEBUGGER $OCAMLDOC_BYTE \
- $STDLIB_NATIVE $OCAMLC_NATIVE $OCAMLOPT_NATIVE \
- $OCAMLLEX_NATIVE $TOOLS_NATIVE $OTHERLIBS_NATIVE \
- $OCAMLBUILD_NATIVE $OCAMLDOC_NATIVE
diff --git a/build/world.byte.sh b/build/world.byte.sh
deleted file mode 100755
index d66f0a809..000000000
--- a/build/world.byte.sh
+++ /dev/null
@@ -1,21 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-set -e
-cd `dirname $0`/..
-. build/targets.sh
-set -x
-$OCAMLBUILD $@ \
- $STDLIB_BYTE $OCAMLC_BYTE $OCAMLLEX_BYTE $OCAMLOPT_BYTE $TOPLEVEL $TOOLS_BYTE \
- $OTHERLIBS_BYTE $OCAMLBUILD_BYTE $DEBUGGER $OCAMLDOC_BYTE
diff --git a/build/world.native.sh b/build/world.native.sh
deleted file mode 100755
index 039cfbf3e..000000000
--- a/build/world.native.sh
+++ /dev/null
@@ -1,22 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2007 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. #
-# #
-#########################################################################
-
-set -e
-cd `dirname $0`/..
-. build/targets.sh
-set -x
-$OCAMLBUILD $@ \
- $STDLIB_NATIVE $OCAMLC_NATIVE $OCAMLOPT_NATIVE \
- $OCAMLLEX_NATIVE $TOOLS_NATIVE $OTHERLIBS_NATIVE \
- $OCAMLBUILD_NATIVE $OCAMLDOC_NATIVE
diff --git a/build/world.sh b/build/world.sh
deleted file mode 100755
index 3b08dc78d..000000000
--- a/build/world.sh
+++ /dev/null
@@ -1,35 +0,0 @@
-#!/bin/sh
-
-#########################################################################
-# #
-# OCaml #
-# #
-# Nicolas Pouillard, projet Gallium, INRIA Rocquencourt #
-# #
-# Copyright 2008 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. #
-# #
-#########################################################################
-
-cd `dirname $0`
-set -e
-if [ -e ocamlbuild_mixed_mode ]; then
- echo ocamlbuild mixed mode detected
- echo 'please cleanup and re-launch (make clean ; ./build/distclean.sh)'
- exit 1
-fi
-case "$1" in
- all|a|al) mode=all;;
- byte|b|by|byt) mode=byte;;
- native|na|nat|nati|nativ) mode=native;;
- *) echo 'Unexpected target. Expected targets are: all,byte,native' \
- >/dev/stderr
- exit 1;;
-esac
-shift
-./mkconfig.sh
-./mkmyocamlbuild_config.sh
-./boot-c-parts.sh
-./boot.sh "$@"
-./world."$mode".sh "$@"
diff --git a/myocamlbuild.ml b/myocamlbuild.ml
deleted file mode 100644
index 0bf0e476d..000000000
--- a/myocamlbuild.ml
+++ /dev/null
@@ -1,607 +0,0 @@
-(***********************************************************************)
-(* *)
-(* OCaml *)
-(* *)
-(* Nicolas Pouillard, projet Gallium, INRIA Rocquencourt *)
-(* *)
-(* Copyright 2007 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. *)
-(* *)
-(***********************************************************************)
-
-open Ocamlbuild_plugin
-open Command
-open Arch
-open Format
-
-module C = Myocamlbuild_config
-
-let () = mark_tag_used "windows";;
-let windows = Sys.os_type = "Win32";;
-if windows then tag_any ["windows"];;
-let ccomptype = C.ccomptype
-(*let () = if ccomptype <> "cc" then eprintf "ccomptype: %s@." ccomptype;;*)
-
-let fp_cat oc f = with_input_file ~bin:true f (fun ic -> copy_chan ic oc)
-
-(* Improve using the command module in Myocamlbuild_config
- with the variant version (`S, `A...) *)
-let mkdll out files opts =
- let s = Command.string_of_command_spec in
- Cmd(Sh(Printf.sprintf "%s -o %s %s %s" C.mkdll out (s files) (s opts)))
-
-let mkexe out files opts =
- let s = Command.string_of_command_spec in
- Cmd(Sh(Printf.sprintf "%s -o %s %s %s" C.mkexe out (s files) (s opts)))
-
-let mklib out files opts =
- let s = Command.string_of_command_spec in
- Cmd(Sh(C.mklib out (s files) (s opts)))
-
-let syslib x = A(C.syslib x);;
-let syscamllib x =
- if ccomptype = "msvc" then A(Printf.sprintf "lib%s.lib" x)
- else A("-l"^x)
-
-let ccoutput cc obj file =
- if ccomptype = "msvc" then
- Seq[Cmd(S[cc; A"-c"; Px file]);
- mv (Pathname.basename (Pathname.update_extension C.o file)) obj]
- else
- Cmd(S[cc; A"-c"; P file; A"-o"; Px obj])
-
-let mkobj obj file opts =
- let tags = tags_of_pathname file++"c"++"compile"++ccomptype in
- let bytecc_with_opts = S[Sh C.bytecc; Sh C.bytecccompopts; opts; T tags] in
- ccoutput bytecc_with_opts obj file
-
-let mknatobj obj file opts =
- let nativecc_with_opts = S[Sh C.nativecc; opts; Sh C.nativecccompopts] in
- ccoutput nativecc_with_opts obj file
-
-let add_exe a =
- if not windows || Pathname.check_extension a "exe" then a
- else a-.-"exe";;
-
-let add_exe_if_exists a =
- if not windows || Pathname.check_extension a "exe" then a
- else
- let exe = a-.-"exe" in
- if Pathname.exists exe then exe else a;;
-
-let convert_command_for_windows_shell spec =
- if not windows then spec else
- let rec self specs acc =
- match specs with
- | N :: specs -> self specs acc
- | S[] :: specs -> self specs acc
- | S[x] :: specs -> self (x :: specs) acc
- | S specs :: specs' -> self (specs @ specs') acc
- | (P(a) | A(a)) :: specs ->
- let dirname = Pathname.dirname a in
- let basename = Pathname.basename a in
- let p =
- if dirname = Pathname.current_dir_name then Sh(add_exe_if_exists basename)
- else Sh(add_exe_if_exists (dirname ^ "\\" ^ basename)) in
- if String.contains_string basename 0 "ocamlrun" = None then
- List.rev (p :: acc) @ specs
- else
- self specs (p :: acc)
- | [] | (Px _ | T _ | V _ | Sh _ | Quote _) :: _ ->
- invalid_arg "convert_command_for_windows_shell: invalid atom in head position"
- in S(self [spec] [])
-
-let convert_for_windows_shell solver () =
- convert_command_for_windows_shell (solver ())
-
-let ocamlrun = A"boot/ocamlrun"
-let full_ocamlrun = P((Sys.getcwd ()) / "boot/ocamlrun")
-
-let boot_ocamlc = S[ocamlrun; A"boot/ocamlc"; A"-I"; A"boot"; A"-nostdlib"]
-
-let mixed = Pathname.exists "build/ocamlbuild_mixed_mode";;
-
-let if_mixed_dir dir =
- if mixed then ".."/dir else dir;;
-
-let unix_dir =
- if Sys.os_type = "Win32" || C.system = "mingw" then
- if_mixed_dir "otherlibs/win32unix"
- else
- if_mixed_dir "otherlibs/unix";;
-
-let threads_dir = if_mixed_dir "otherlibs/threads";;
-let systhreads_dir = if_mixed_dir "otherlibs/systhreads";;
-let dynlink_dir = if_mixed_dir "otherlibs/dynlink";;
-let str_dir = if_mixed_dir "otherlibs/str";;
-let toplevel_dir = if_mixed_dir "toplevel";;
-
-let systhreads_file f = "otherlibs/systhreads"/f
-let systhreads_obj f = "otherlibs/systhreads"/f-.-C.o
-let systhreads_lib f = "otherlibs/systhreads"/f-.-C.a
-let systhreads_dll f = "otherlibs/systhreads"/f-.-C.so
-
-let ocamlc_solver =
- let native_deps = ["ocamlc.opt"; "stdlib/stdlib.cmxa";
- "stdlib/std_exit.cmx"; "stdlib/std_exit"-.-C.o] in
- let byte_deps = ["ocamlc"; "stdlib/stdlib.cma"; "stdlib/std_exit.cmo"] in
- fun () ->
- if Pathname.exists "../ocamlcomp.sh" then S[A"../ocamlcomp.sh"] else
- if List.for_all Pathname.exists native_deps then
- S[A"./ocamlc.opt"; A"-nostdlib"]
- else if List.for_all Pathname.exists byte_deps then
- S[ocamlrun; A"./ocamlc"; A"-nostdlib"]
- else boot_ocamlc;;
-
-Command.setup_virtual_command_solver "OCAMLC" ocamlc_solver;;
-Command.setup_virtual_command_solver "OCAMLCWIN" (convert_for_windows_shell ocamlc_solver);;
-
-let ocamlopt_solver () =
- S[if Pathname.exists "../ocamlcompopt.sh" then S[A"../ocamlcompopt.sh"] else
- if Pathname.exists "ocamlopt.opt" && Pathname.exists ("stdlib/stdlib.cmxa")
- then A"./ocamlopt.opt"
- else S[ocamlrun; A"./ocamlopt"];
- A"-nostdlib"];;
-
-Command.setup_virtual_command_solver "OCAMLOPT" ocamlopt_solver;;
-Command.setup_virtual_command_solver "OCAMLOPTWIN" (convert_for_windows_shell ocamlopt_solver);;
-
-let ocamlc = V"OCAMLC";;
-let ocamlopt = V"OCAMLOPT";;
-
-let ar = A"ar";;
-
-dispatch begin function
-| Before_hygiene ->
- if mixed then
- let patt = String.concat ","
- ["asmcomp"; "bytecomp"; "debugger"; "driver";
- "lex"; "ocamldoc"; "otherlibs"; "parsing"; "stdlib"; "tools";
- "toplevel"; "typing"; "utils"]
- in Ocamlbuild_pack.Configuration.parse_string
- (sprintf "<{%s}/**>: not_hygienic, -traverse" patt)
-
-| After_options ->
- begin
- Options.ocamlrun := ocamlrun;
- Options.ocamllex := S[ocamlrun; P"boot/ocamllex"];
- Options.ocamlyacc := if windows then P"./boot/ocamlyacc.exe" else P"boot/ocamlyacc";
- Options.ocamlmklib := S[ocamlrun; P"tools/ocamlmklib.byte"; A"-ocamlc"; Quote (V"OCAMLCWIN");
- A"-ocamlopt"; Quote (V"OCAMLOPTWIN")(* ; A"-v" *)];
- Options.ocamldep := S[ocamlrun; P"boot/ocamldep"];
-
- Options.ext_obj := C.o;
- Options.ext_lib := C.a;
- Options.ext_dll := String.after C.ext_dll 1;
-
- Options.nostdlib := true;
- Options.make_links := false;
- if !Options.just_plugin then
- Options.ocamlc := boot_ocamlc
- else begin
- Options.ocamlc := ocamlc;
- Options.plugin := false;
- Options.ocamlopt := ocamlopt;
- end;
- end
-| After_rules ->
- let module M = struct
-
-
-flag ["ocaml"; "ocamlyacc"] (A"-v");;
-
-flag ["ocaml"; "compile"; "strict_sequence"] (A"-strict-sequence");;
-
-non_dependency "otherlibs/threads/pervasives.ml" "Unix";;
-non_dependency "otherlibs/threads/pervasives.ml" "String";;
-
-let add_extensions extensions modules =
- List.fold_right begin fun x ->
- List.fold_right begin fun ext acc ->
- x-.-ext :: acc
- end extensions
- end modules [];;
-
-
-use_lib "toplevel/topstart" "toplevel/toplevellib";;
-use_lib "otherlibs/dynlink/extract_crc" "otherlibs/dynlink/dynlink";;
-
-hide_package_contents "otherlibs/dynlink/dynlinkaux";;
-
-flag ["ocaml"; "link"; "file:driver/main.native"; "native"] begin
- S[A"-ccopt"; A C.bytecclinkopts; A"-cclib"; A C.bytecclibs]
-end;;
-
-dep ["ocaml"; "link"; "file:driver/main.native"; "native"]
- ["asmrun/meta"-.-C.o; "asmrun/dynlink"-.-C.o];;
-
-dep ["ocaml"; "compile"; "native"] ["stdlib/libasmrun"-.-C.a];;
-
-flag ["ocaml"; "link"] (S[A"-I"; P "stdlib"]);;
-flag ["ocaml"; "compile"; "include_unix"] (S[A"-I"; P unix_dir]);;
-flag ["ocaml"; "compile"; "include_str"] (S[A"-I"; P str_dir]);;
-flag ["ocaml"; "compile"; "include_dynlink"] (S[A"-I"; P dynlink_dir]);;
-flag ["ocaml"; "compile"; "include_toplevel"] (S[A"-I"; P toplevel_dir]);;
-flag ["ocaml"; "link"; "use_unix"] (S[A"-I"; P unix_dir]);;
-flag ["ocaml"; "link"; "use_dynlink"] (S[A"-I"; P dynlink_dir]);;
-flag ["ocaml"; "link"; "use_str"] (S[A"-I"; P str_dir]);;
-flag ["ocaml"; "link"; "use_toplevel"] (S[A"-I"; P toplevel_dir]);;
-
-let setup_arch arch =
- let annotated_arch = annotate arch in
- let (_include_dirs_table, _for_pack_table) = mk_tables annotated_arch in
- (* Format.eprintf "%a@." (Ocaml_arch.print_table (List.print pp_print_string)) include_dirs_table;; *)
- iter_info begin fun i ->
- Pathname.define_context i.current_path i.include_dirs
- end annotated_arch;;
-
-
-Pathname.define_context "" ["stdlib"];;
-Pathname.define_context "utils" [Pathname.current_dir_name; "stdlib"];;
-Pathname.define_context "parsing" ["parsing"; "utils"; "stdlib"];;
-Pathname.define_context "typing" ["typing"; "parsing"; "utils"; "stdlib"];;
-Pathname.define_context "ocamldoc" ["typing"; "parsing"; "utils"; "tools"; "bytecomp"; "stdlib"];;
-Pathname.define_context "bytecomp" ["bytecomp"; "parsing"; "typing"; "utils"; "stdlib"];;
-Pathname.define_context "tools" ["tools"; (* "toplevel"; *) "parsing"; "utils"; "driver"; "bytecomp"; "asmcomp"; "typing"; "stdlib"];;
-Pathname.define_context "toplevel" ["toplevel"; "parsing"; "typing"; "bytecomp"; "utils"; "driver"; "stdlib"];;
-Pathname.define_context "driver" ["driver"; "asmcomp"; "bytecomp"; "typing"; "utils"; "parsing"; "stdlib"];;
-Pathname.define_context "debugger" ["bytecomp"; "utils"; "typing"; "parsing"; "toplevel"; "stdlib"];;
-Pathname.define_context "otherlibs/dynlink" ["otherlibs/dynlink"; "bytecomp"; "utils"; "typing"; "parsing"; "stdlib"];;
-Pathname.define_context "otherlibs/dynlink/nat" ["otherlibs/dynlink/nat"; "asmcomp"; "stdlib"];;
-Pathname.define_context "asmcomp" ["asmcomp"; "bytecomp"; "parsing"; "typing"; "utils"; "stdlib"];;
-Pathname.define_context "ocamlbuild" ["ocamlbuild"; "."];;
-Pathname.define_context "lex" ["lex"; "stdlib"];;
-
-List.iter (fun x -> let x = "otherlibs"/x in Pathname.define_context x [x; "stdlib"])
- ["bigarray"; "graph"; "num"; "str"; "systhreads"; "unix"; "win32graph"; "win32unix"];;
-
-(* The bootstrap standard library *)
-copy_rule "The bootstrap standard library" "stdlib/%" "boot/%";;
-
-(* About the standard library *)
-copy_rule "stdlib asmrun" ("asmrun/%"-.-C.a) ("stdlib/%"-.-C.a);;
-copy_rule "stdlib byterun" ("byterun/%"-.-C.a) ("stdlib/%"-.-C.a);;
-
-(* The thread specific standard library *)
-copy_rule "The thread specific standard library (mllib)" ~insert:`bottom "stdlib/%.mllib" "otherlibs/threads/%.mllib";;
-copy_rule "The thread specific standard library (cmo)" ~insert:`bottom "stdlib/%.cmo" "otherlibs/threads/%.cmo";;
-copy_rule "The thread specific standard library (cmi)" ~insert:`top "stdlib/%.cmi" "otherlibs/threads/%.cmi";;
-copy_rule "The thread specific standard library (mli)" ~insert:`bottom "stdlib/%.mli" "otherlibs/threads/%.mli";;
-copy_rule "The thread specific unix library (mli)" ~insert:`bottom "otherlibs/unix/%.mli" "otherlibs/threads/%.mli";;
-copy_rule "The thread specific unix library (ml)" ~insert:`bottom "otherlibs/unix/%.ml" "otherlibs/threads/%.ml";;
-copy_rule "The thread specific unix library (mllib)" ~insert:`bottom "otherlibs/unix/%.mllib" "otherlibs/threads/%.mllib";;
-
-(* Temporary rule, waiting for a full usage of ocamlbuild *)
-copy_rule "Temporary rule, waiting for a full usage of ocamlbuild" "%.mlbuild" "%.ml";;
-
-copy_rule "graph/graphics.ml -> win32graph/graphics.ml" "otherlibs/graph/graphics.ml" "otherlibs/win32graph/graphics.ml";;
-copy_rule "graph/graphics.mli -> win32graph/graphics.mli" "otherlibs/graph/graphics.mli" "otherlibs/win32graph/graphics.mli";;
-
-rule "the ocaml toplevel"
- ~prod:"ocaml"
- ~deps:["stdlib/stdlib.mllib"; "toplevel/topstart.byte"; "toplevel/expunge.byte"]
- begin fun _ _ ->
- let modules = string_list_of_file "stdlib/stdlib.mllib" in
- Cmd(S[ocamlrun; A"toplevel/expunge.byte"; A"toplevel/topstart.byte"; Px"ocaml";
- A"outcometree"; A"topdirs"; A"toploop"; atomize modules])
- end;;
-
-let copy_rule' ?insert src dst = copy_rule (sprintf "%s -> %s" src dst) ?insert src dst;;
-
-copy_rule' "driver/main.byte" "ocamlc";;
-copy_rule' "driver/main.native" "ocamlc.opt";;
-copy_rule' "driver/optmain.byte" "ocamlopt";;
-copy_rule' "driver/optmain.native" "ocamlopt.opt";;
-copy_rule' "lex/main.byte" "lex/ocamllex";;
-copy_rule' "lex/main.native" "lex/ocamllex.opt";;
-copy_rule' "debugger/main.byte" "debugger/ocamldebug";;
-copy_rule' "ocamldoc/odoc.byte" "ocamldoc/ocamldoc";;
-copy_rule' "ocamldoc/odoc.native" "ocamldoc/ocamldoc.opt";;
-copy_rule' "tools/ocamlmklib.byte" "tools/ocamlmklib";;
-copy_rule' "otherlibs/dynlink/extract_crc.byte" "otherlibs/dynlink/extract_crc";;
-copy_rule' "myocamlbuild_config.mli" "ocamlbuild/ocamlbuild_Myocamlbuild_config.mli";;
-copy_rule' "myocamlbuild_config.ml" "ocamlbuild/ocamlbuild_Myocamlbuild_config.ml";;
-
-copy_rule' ~insert:`bottom "%" "%.exe";;
-
-ocaml_lib "stdlib/stdlib";;
-
-let stdlib_mllib_contents =
- lazy (string_list_of_file "stdlib/stdlib.mllib");;
-
-let import_stdlib_contents build exts =
- let l =
- List.fold_right begin fun x ->
- List.fold_right begin fun ext acc ->
- ["stdlib"/(String.uncapitalize x)-.-ext] :: acc
- end exts
- end !*stdlib_mllib_contents []
- in
- let res = build l in
- List.iter Outcome.ignore_good res
-;;
-
-rule "byte stdlib in mixed mode"
- ~stamp:"byte_stdlib_mixed_mode"
- ~deps:["stdlib/stdlib.mllib"; "stdlib/stdlib.cma";
- "stdlib/std_exit.cmo"; "stdlib/libcamlrun"-.-C.a;
- "stdlib/camlheader"; "stdlib/camlheader_ur"]
- begin fun env build ->
- let (_ : Command.t) =
- Ocamlbuild_pack.Ocaml_compiler.byte_library_link_mllib
- "stdlib/stdlib.mllib" "stdlib/stdlib.cma" env build
- in
- import_stdlib_contents build ["cmi"];
- Nop
- end;;
-
-rule "native stdlib in mixed mode"
- ~stamp:"native_stdlib_mixed_mode"
- ~deps:["stdlib/stdlib.mllib"; "stdlib/stdlib.cmxa";
- "stdlib/stdlib"-.-C.a; "stdlib/std_exit.cmx";
- "stdlib/std_exit"-.-C.o; "stdlib/libasmrun"-.-C.a;
- "stdlib/camlheader"; "stdlib/camlheader_ur"]
- begin fun env build ->
- let (_ : Command.t) =
- Ocamlbuild_pack.Ocaml_compiler.native_library_link_mllib
- "stdlib/stdlib.mllib" "stdlib/stdlib.cmxa" env build
- in
- import_stdlib_contents build ["cmi"];
- Nop
- end;;
-
-copy_rule' ~insert:`top "otherlibs/dynlink/natdynlink.ml" "otherlibs/dynlink/nat/dynlink.ml";;
-copy_rule' ~insert:`top "otherlibs/dynlink/dynlink.mli" "otherlibs/dynlink/nat/dynlink.mli";;
-copy_rule' ~insert:`top "otherlibs/dynlink/nat/dynlink.cmx" "otherlibs/dynlink/dynlink.cmx";;
-copy_rule' ~insert:`top ("otherlibs/dynlink/nat/dynlink"-.-C.o) ("otherlibs/dynlink/dynlink"-.-C.o);;
-copy_rule' ~insert:`top "otherlibs/dynlink/nat/dynlink.cmxa" "otherlibs/dynlink/dynlink.cmxa";;
-copy_rule' ~insert:`top ("otherlibs/dynlink/nat/dynlink"-.-C.a) ("otherlibs/dynlink/dynlink"-.-C.a);;
-dep ["ocaml"; "compile"; "native"; "file:otherlibs/dynlink/nat/dynlink.cmx"] ["otherlibs/dynlink/nat/dynlink.cmi"];;
-
-rule "C files"
- ~prod:("%"-.-C.o)
- ~dep:"%.c"
- ~insert:(`before "ocaml C stubs: c -> o")
- begin fun env _ ->
- mkobj (env ("%"-.-C.o)) (env "%.c") N
- end;;
-
-let () =
- (* define flags otherlibs_unix, otherlibs_bigarray... *)
- let otherlibs = "otherlibs" in
- let open Pathname in
- Array.iter (fun file ->
- if is_directory (concat "otherlibs" file) then
- mark_tag_used ("otherlibs_" ^ file)
- ) (readdir otherlibs);;
-
-(* ../ is because .h files are not dependencies so they are not imported in build dir *)
-flag ["c"; "compile"; "otherlibs_bigarray"] (S[A"-I"; P"../otherlibs/bigarray"]);;
-flag [(* "ocaml" or "c"; *) "ocamlmklib"; "otherlibs_graph"] (S[Sh C.x11_link]);;
-flag ["c"; "compile"; "otherlibs_graph"] (S[Sh C.x11_includes; A"-I../otherlibs/graph"]);;
-flag ["c"; "compile"; "otherlibs_win32graph"] (A"-I../otherlibs/win32graph");;
-flag ["ocaml"; "ocamlmklib"; "otherlibs_threads"] (S[A"-oc"; A"otherlibs/threads/vmthreads"]);;
-flag ["c"; "compile"; "otherlibs_num"] begin
- S[A("-DBNG_ARCH_"^C.bng_arch);
- A("-DBNG_ASM_LEVEL="^C.bng_asm_level);
- A"-I"; P"../otherlibs/num"]
-end;;
-flag ["c"; "compile"; "otherlibs_win32unix"] (A"-I../otherlibs/win32unix");;
-flag [(* "ocaml" or "c"; *) "ocamlmklib"; "otherlibs_win32unix"] (S[A"-cclib"; Quote (syslib "ws2_32")]);;
-flag ["c"; "link"; "dll"; "otherlibs_win32unix"] (syslib "ws2_32");;
-let flags = S[syslib "kernel32"; syslib "gdi32"; syslib "user32"] in
-flag ["c"; "ocamlmklib"; "otherlibs_win32graph"] (S[A"-cclib"; Quote flags]);
-flag ["c"; "link"; "dll"; "otherlibs_win32graph"] flags;;
-
-if windows then flag ["c"; "compile"; "otherlibs_bigarray"] (A"-DIN_OCAML_BIGARRAY");;
-
-if windows then flag ["ocamlmklib"] (A"-custom");;
-
-flag ["ocaml"; "pp"; "ocamldoc_sources"] begin
- if windows then
- S[A"grep"; A"-v"; A"DEBUG"]
- else
- A"../ocamldoc/remove_DEBUG"
-end;;
-
-let ocamldoc = P"./ocamldoc/ocamldoc.opt" in
-let stdlib_mlis =
- List.fold_right
- (fun x acc -> "stdlib"/(String.uncapitalize x)-.-"mli" :: acc)
- (string_list_of_file "stdlib/stdlib.mllib")
- ["otherlibs/unix/unix.mli"; "otherlibs/str/str.mli";
- "otherlibs/bigarray/bigarray.mli"; "otherlibs/num/num.mli"] in
-rule "Standard library manual"
- ~prod:"ocamldoc/stdlib_man/Pervasives.3o"
- ~stamp:"ocamldoc/stdlib_man.stamp" (* Depend on this file if you want to depends on all files of stdlib_man/* *)
- ~deps:stdlib_mlis
- begin fun _ _ ->
- Seq[Cmd(S[A"mkdir"; A"-p"; P"ocamldoc/stdlib_man"]);
- Cmd(S[ocamldoc; A"-man"; A"-d"; P"ocamldoc/stdlib_man";
- A"-I"; P "stdlib"; A"-I"; P"otherlibs/unix"; A"-I"; P"otherlibs/num";
- A"-t"; A"OCaml library"; A"-man-mini"; atomize stdlib_mlis])]
- end;;
-
-flag ["ocaml"; "compile"; "bootstrap_thread"]
- (S[A"-I"; P systhreads_dir; A"-I"; P threads_dir]);;
-
-flag ["ocaml"; "link"; "bootstrap_thread"]
- (S[A"-I"; P systhreads_dir; A"-I"; P threads_dir]);;
-
-(* Sys threads *)
-
-let systhreads_stubs_headers =
- List.map systhreads_file
- [if windows then "st_win32.h" else "st_posix.h"; "threads.h"]
-;;
-
-rule "native systhreads"
- ~prod:(systhreads_obj "st_stubs_n")
- ~deps:(systhreads_file "st_stubs.c" :: systhreads_stubs_headers)
- ~insert:`top
- begin fun _ _ ->
- mknatobj (systhreads_obj "st_stubs_n")
- (systhreads_file "st_stubs.c")
- (S[A"-I../asmrun"; A"-I../byterun"; A"-Iotherlibs/systhreads";
- if windows then N else Sh C.sharedcccompopts;
- A"-DNATIVE_CODE"; A("-DTARGET_"^C.arch); A("-DSYS_"^C.system)])
- end;;
-
-rule "bytecode systhreads"
- ~prod:(systhreads_obj "st_stubs_b")
- ~deps:(systhreads_file "st_stubs.c" :: systhreads_stubs_headers)
- ~insert:`top
- begin fun _ _ ->
- mkobj (systhreads_obj "st_stubs_b") (systhreads_file "st_stubs.c")
- (S[A"-I../byterun"; A"-Iotherlibs/systhreads"; Sh C.sharedcccompopts])
- end;;
-
-rule "libthreadsnat.a"
- ~prod:(systhreads_lib "libthreadsnat")
- ~dep:(systhreads_obj "st_stubs_n")
- ~insert:`top
- begin fun _ _ ->
- if windows then
- mklib (systhreads_lib "libthreadsnat") (P(systhreads_obj "st_stubs_n")) N
- else
- (* Dynamic linking with -lpthread is risky on many platforms, so
- do not create a shared object for libthreadsnat. *)
- Cmd(S[ar; A"rc"; Px(systhreads_lib "libthreadsnat");
- P(systhreads_obj "st_stubs_n")])
- end;
-
-(* See remark above: force static linking of libthreadsnat.a *)
-if windows then
- flag ["ocaml"; "link"; "library"; "otherlibs_systhreads"; "native"] begin
- S[A"-cclib"; syscamllib "threadsnat"; (* A"-cclib"; syscamllib "unix"; seems to be useless and can be dangerous during bootstrap *) Sh C.pthread_link]
- end;;
-
-flag ["ocaml"; "ocamlmklib"; "otherlibs_systhreads"] (S[(* A"-cclib"; syscamllib "unix";; seems to be useless and can be dangerous during bootstrap *) Sh C.pthread_link]);;
-
-flag ["c"; "compile"; "otherlibs"] begin
- S[A"-I"; P"../byterun";
- A"-I"; P(".."/unix_dir);
- Sh C.bytecccompopts;
- Sh C.sharedcccompopts]
-end;;
-
-flag ["c"; "compile"; "otherlibs"; "cc"] (A"-O");;
-flag ["c"; "compile"; "otherlibs"; "mingw"] (A"-O");;
-
-(* The numeric opcodes *)
-rule "The numeric opcodes"
- ~prod:"bytecomp/opcodes.ml"
- ~dep:"byterun/instruct.h"
- ~insert:`top
- begin fun _ _ ->
- Cmd(Sh "sed -n -e '/^enum/p' -e 's/,//g' -e '/^ /p' byterun/instruct.h | \
- awk -f ../tools/make-opcodes > bytecomp/opcodes.ml")
- end;;
-
-rule "tools/opnames.ml"
- ~prod:"tools/opnames.ml"
- ~dep:"byterun/instruct.h"
- begin fun _ _ ->
- Cmd(Sh"unset LC_ALL || : ; \
- unset LC_CTYPE || : ; \
- unset LC_COLLATE LANG || : ; \
- sed -e '/\\/\\*/d' \
- -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 > tools/opnames.ml")
- end;;
-
-(* The version number *)
-rule "stdlib/sys.ml"
- ~prod:"stdlib/sys.ml"
- ~deps:["stdlib/sys.mlp"; "VERSION"]
- begin fun _ _ ->
- let version = with_input_file "VERSION" input_line in
- Seq [rm_f "stdlib/sys.ml";
- Cmd (S[A"sed"; A"-e";
- A(sprintf "s,%%%%VERSION%%%%,%s," version);
- Sh"<"; P"stdlib/sys.mlp"; Sh">"; Px"stdlib/sys.ml"]);
- chmod (A"-w") "stdlib/sys.ml"]
- end;;
-
-(* The predefined exceptions and primitives *)
-
-rule "camlheader"
- ~prods:["stdlib/camlheader"; "stdlib/camlheader_ur"]
- ~deps:["stdlib/header.c"; "stdlib/headernt.c"]
- begin fun _ _ ->
- if C.sharpbangscripts then
- Cmd(Sh("echo '#!"^C.bindir^"/ocamlrun' > stdlib/camlheader && \
- echo '#!' | tr -d '\\012' > stdlib/camlheader_ur"))
- else if windows then
- Seq[mkexe "tmpheader.exe" (P"stdlib/headernt.c") (S[A"-I../byterun"; Sh C.extralibs]);
- rm_f "camlheader.exe";
- mv "tmpheader.exe" "stdlib/camlheader";
- cp "stdlib/camlheader" "stdlib/camlheader_ur"]
- else
- let tmpheader = "tmpheader"^C.exe in
- Cmd(S[Sh C.bytecc; Sh C.bytecccompopts; Sh C.bytecclinkopts;
- A"-I"; A"../stdlib";
- A("-DRUNTIME_NAME='\""^C.bindir^"/ocamlrun\"'");
- A"stdlib/header.c"; A"-o"; Px tmpheader; Sh"&&";
- A"strip"; P tmpheader; Sh"&&";
- A"mv"; P tmpheader; A"stdlib/camlheader"; Sh"&&";
- A"cp"; A"stdlib/camlheader"; A"stdlib/camlheader_ur"])
- end;;
-
-(* Private copy of dynlink.{ml,mli} in debugger/ *)
-copy_rule "otherlibs/dynlink/dynlink.mli -> debugger/dynlink.mli" "otherlibs/dynlink/dynlink.mli" "debugger/dynlink.mli";;
-rule "debugger/dynlink.ml"
- ~prod: "debugger/dynlink.ml"
- ~dep: "otherlibs/dynlink/dynlink.ml"
- begin fun _ _ ->
- Cmd(Sh"grep -v 'REMOVE_ME for ../../debugger/dynlink.ml' \
- < otherlibs/dynlink/dynlink.ml >debugger/dynlink.ml")
- end;;
-
-
-copy_rule "win32unix use some unix files" "otherlibs/unix/%" "otherlibs/win32unix/%";;
-
-(* Temporary rule *)
-rule "tools/ocamlmklib.ml"
- ~prod:"tools/ocamlmklib.ml"
- ~dep:"tools/ocamlmklib.mlp"
- (fun _ _ -> cp "tools/ocamlmklib.mlp" "tools/ocamlmklib.ml");;
-
-
-rule "bytecomp/runtimedef.ml"
- ~prod:"bytecomp/runtimedef.ml"
- ~deps:["byterun/primitives"; "byterun/fail.h"]
- begin fun _ _ ->
- Cmd(S[A"../build/mkruntimedef.sh";Sh">"; Px"bytecomp/runtimedef.ml"])
- end;;
-
-(* Choose the right machine-dependent files *)
-
-let mk_arch_rule ~src ~dst =
- let prod = "asmcomp"/dst in
- let dep = "asmcomp"/C.arch/src in
- rule (sprintf "arch specific files %S%%" dst) ~prod ~dep begin
- if windows then fun env _ -> cp (env dep) (env prod)
- else fun env _ -> ln_s (env (C.arch/src)) (env prod)
- end;;
-
-mk_arch_rule ~src:(if ccomptype = "msvc" then "proc_nt.ml" else "proc.ml") ~dst:"proc.ml";;
-List.iter (fun x -> mk_arch_rule ~src:x ~dst:x)
- ["arch.ml"; "reload.ml"; "scheduling.ml"; "selection.ml"];;
-
-let emit_mlp = "asmcomp"/C.arch/(if ccomptype = "msvc" then "emit_nt.mlp" else "emit.mlp") in
-rule "emit.mlp"
- ~prod:"asmcomp/emit.ml"
- ~deps:[emit_mlp; "tools/cvt_emit.byte"]
- begin fun _ _ ->
- Cmd(S[ocamlrun; P"tools/cvt_emit.byte"; Sh "<"; P emit_mlp;
- Sh">"; Px"asmcomp/emit.ml"])
- end;;
- end in ()
- | _ -> ()
-end
diff --git a/myocamlbuild_config.mli b/myocamlbuild_config.mli
deleted file mode 100644
index d19a39aed..000000000
--- a/myocamlbuild_config.mli
+++ /dev/null
@@ -1,72 +0,0 @@
-(*************************************************************************)
-(* *)
-(* OCaml *)
-(* *)
-(* Nicolas Pouillard, projet Gallium, INRIA Rocquencourt *)
-(* *)
-(* Copyright 2007 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. *)
-(* *)
-(*************************************************************************)
-
-val prefix : string
-val bindir : string
-val libdir : string
-val manext : string
-val ranlib : string
-val ranlibcmd : string
-val arcmd : string
-val sharpbangscripts : bool
-val bng_arch : string
-val bng_asm_level : string
-val pthread_link : string
-val x11_includes : string
-val x11_link : string
-val bytecc : string
-val bytecccompopts : string
-val bytecclinkopts : string
-val bytecclibs : string
-val byteccrpath : string
-val exe : string
-val supports_shared_libraries : bool
-val sharedcccompopts : string
-val mksharedlibrpath : string
-val arch : string
-val model : string
-val system : string
-val nativecc : string
-val nativecccompopts : string
-val nativeccprofopts : string
-val nativecclinkopts : string
-val nativeccrpath : string
-val nativecclibs : string
-val packld : string
-val dllcccompopts : string
-val asm : string
-val aspp : string
-val asppprofflags : string
-val profiling : string
-val dynlinkopts : string
-val otherlibraries : string
-val with_debugger : string
-val cc_profile : string
-val systhread_support : bool
-val syslib : string -> string
-val mkexe : string
-val mkdll : string
-val mkmaindll : string
-val mklib : string -> string -> string -> string
-val ext_lib : string
-val ext_obj : string
-val ext_asm : string
-val ext_dll : string
-val o : string
-val a : string
-val so : string
-val toolchain : string
-val ccomptype : string
-val extralibs : string
-val asm_cfi_supported : bool
-val target : string
-val host : string
diff --git a/tools/.depend b/tools/.depend
index bc45dc761..45e11b29c 100644
--- a/tools/.depend
+++ b/tools/.depend
@@ -27,14 +27,6 @@ depend.cmo : ../parsing/parsetree.cmi ../utils/misc.cmi \
depend.cmx : ../parsing/parsetree.cmi ../utils/misc.cmx \
../parsing/longident.cmx ../parsing/location.cmx ../parsing/asttypes.cmi \
depend.cmi
-dump_ast.cmo : ../typing/typetexp.cmi ../typing/typedtree.cmi \
- ../toplevel/toploop.cmi ../parsing/parse.cmi ../typing/outcometree.cmi \
- ../typing/oprint.cmi ../driver/errors.cmi ../typing/env.cmi \
- ../utils/config.cmi
-dump_ast.cmx : ../typing/typetexp.cmx ../typing/typedtree.cmx \
- ../toplevel/toploop.cmx ../parsing/parse.cmx ../typing/outcometree.cmi \
- ../typing/oprint.cmx ../driver/errors.cmx ../typing/env.cmx \
- ../utils/config.cmx
dumpobj.cmo : ../utils/tbl.cmi opnames.cmo ../bytecomp/opcodes.cmo \
../utils/misc.cmi ../parsing/location.cmi ../bytecomp/lambda.cmi \
../bytecomp/instruct.cmi ../typing/ident.cmi ../utils/config.cmi \
@@ -63,26 +55,24 @@ ocaml299to3.cmo :
ocaml299to3.cmx :
ocamlcp.cmo : ../driver/main_args.cmi
ocamlcp.cmx : ../driver/main_args.cmx
-ocamldep.cmo : ../parsing/syntaxerr.cmi ../driver/pparse.cmi \
- ../parsing/parsetree.cmi ../parsing/parse.cmi ../utils/misc.cmi \
- ../parsing/location.cmi ../parsing/lexer.cmi depend.cmi \
+ocamldep.cmo : ../driver/pparse.cmi ../parsing/parsetree.cmi \
+ ../parsing/parse.cmi ../utils/misc.cmi ../parsing/location.cmi depend.cmi \
../utils/config.cmi ../driver/compenv.cmi ../utils/clflags.cmi
-ocamldep.cmx : ../parsing/syntaxerr.cmx ../driver/pparse.cmx \
- ../parsing/parsetree.cmi ../parsing/parse.cmx ../utils/misc.cmx \
- ../parsing/location.cmx ../parsing/lexer.cmx depend.cmx \
+ocamldep.cmx : ../driver/pparse.cmx ../parsing/parsetree.cmi \
+ ../parsing/parse.cmx ../utils/misc.cmx ../parsing/location.cmx depend.cmx \
../utils/config.cmx ../driver/compenv.cmx ../utils/clflags.cmx
-ocamlmklib.cmo : myocamlbuild_config.cmo
-ocamlmklib.cmx : myocamlbuild_config.cmx
+ocamlmklib.cmo : ocamlmklibconfig.cmo
+ocamlmklib.cmx : ocamlmklibconfig.cmx
+ocamlmklibconfig.cmo :
+ocamlmklibconfig.cmx :
ocamlmktop.cmo : ../utils/ccomp.cmi
ocamlmktop.cmx : ../utils/ccomp.cmx
ocamloptp.cmo : ../driver/main_args.cmi
ocamloptp.cmx : ../driver/main_args.cmx
-ocamlprof.cmo : ../utils/warnings.cmi ../parsing/syntaxerr.cmi \
- ../parsing/parsetree.cmi ../parsing/parse.cmi ../parsing/location.cmi \
- ../parsing/lexer.cmi
-ocamlprof.cmx : ../utils/warnings.cmx ../parsing/syntaxerr.cmx \
- ../parsing/parsetree.cmi ../parsing/parse.cmx ../parsing/location.cmx \
- ../parsing/lexer.cmx
+ocamlprof.cmo : ../utils/warnings.cmi ../parsing/parsetree.cmi \
+ ../parsing/parse.cmi ../parsing/location.cmi
+ocamlprof.cmx : ../utils/warnings.cmx ../parsing/parsetree.cmi \
+ ../parsing/parse.cmx ../parsing/location.cmx
opnames.cmo :
opnames.cmx :
primreq.cmo : ../utils/config.cmi ../bytecomp/cmo_format.cmi
@@ -93,13 +83,11 @@ read_cmt.cmo : ../typing/cmt_format.cmi cmt2annot.cmo ../utils/clflags.cmi
read_cmt.cmx : ../typing/cmt_format.cmx cmt2annot.cmx ../utils/clflags.cmx
scrapelabels.cmo :
scrapelabels.cmx :
-tast_iter.cmo : ../typing/typedtree.cmi ../parsing/asttypes.cmi \
- tast_iter.cmi
-tast_iter.cmx : ../typing/typedtree.cmx ../parsing/asttypes.cmi \
- tast_iter.cmi
+tast_iter.cmo : ../typing/typedtree.cmi tast_iter.cmi
+tast_iter.cmx : ../typing/typedtree.cmx tast_iter.cmi
untypeast.cmo : ../typing/typedtree.cmi ../typing/path.cmi \
../parsing/parsetree.cmi ../parsing/longident.cmi ../typing/ident.cmi \
- ../parsing/asttypes.cmi untypeast.cmi
+ ../parsing/asttypes.cmi ../parsing/ast_helper.cmi untypeast.cmi
untypeast.cmx : ../typing/typedtree.cmx ../typing/path.cmx \
../parsing/parsetree.cmi ../parsing/longident.cmx ../typing/ident.cmx \
- ../parsing/asttypes.cmi untypeast.cmi
+ ../parsing/asttypes.cmi ../parsing/ast_helper.cmx untypeast.cmi
diff --git a/tools/Makefile.shared b/tools/Makefile.shared
index 84b674122..fd5100c94 100644
--- a/tools/Makefile.shared
+++ b/tools/Makefile.shared
@@ -93,17 +93,8 @@ clean::
# To help building mixed-mode libraries (OCaml + C)
-ocamlmklib: myocamlbuild_config.cmo ocamlmklib.cmo
- $(CAMLC) $(LINKFLAGS) -o ocamlmklib myocamlbuild_config.cmo \
- ocamlmklib.cmo
-
-ocamlmklib.cmo: myocamlbuild_config.cmi
-
-myocamlbuild_config.cmi: myocamlbuild_config.cmo
-
-myocamlbuild_config.ml: ../config/Makefile ../build/mkmyocamlbuild_config.sh
- ../build/mkmyocamlbuild_config.sh
- cp ../myocamlbuild_config.ml .
+ocamlmklib: ocamlmklibconfig.cmo ocamlmklib.cmo
+ $(CAMLC) $(LINKFLAGS) -o ocamlmklib ocamlmklibconfig.cmo ocamlmklib.cmo
install::
cp ocamlmklib $(BINDIR)/ocamlmklib$(EXE)
@@ -111,22 +102,22 @@ install::
clean::
rm -f ocamlmklib
-ocamlmklib.ml: ocamlmklib.mlp ../config/Makefile
- echo '(* THIS FILE IS GENERATED FROM ocamlmklib.mlp *)' >ocamlmklib.ml
- sed -e "s|%%BINDIR%%|$(BINDIR)|" \
- -e "s|%%SUPPORTS_SHARED_LIBRARIES%%|$(SUPPORTS_SHARED_LIBRARIES)|" \
- -e "s|%%MKSHAREDLIB%%|$(MKSHAREDLIB)|" \
- -e "s|%%BYTECCRPATH%%|$(BYTECCRPATH)|" \
- -e "s|%%NATIVECCRPATH%%|$(NATIVECCRPATH)|" \
- -e "s|%%MKSHAREDLIBRPATH%%|$(MKSHAREDLIBRPATH)|" \
- -e "s|%%RANLIB%%|$(RANLIB)|" \
- ocamlmklib.mlp >> ocamlmklib.ml
+ocamlmklibconfig.ml: ../config/Makefile
+ (echo 'let bindir = "$(BINDIR)"'; \
+ echo 'let ext_lib = "$(EXT_LIB)"'; \
+ echo 'let ext_dll = "$(EXT_DLL)"'; \
+ echo 'let supports_shared_libraries = $(SUPPORTS_SHARED_LIBRARIES)';\
+ echo 'let mkdll = "$(MKDLL)"'; \
+ echo 'let byteccrpath = "$(BYTECCRPATH)"'; \
+ echo 'let nativeccrpath = "$(NATIVECCRPATH)"'; \
+ echo 'let mksharedlibrpath = "$(MKSHAREDLIBRPATH)"'; \
+ sed -n -e 's/^#ml //p' ../config/Makefile) \
+ > ocamlmklibconfig.ml
-beforedepend:: ocamlmklib.ml
+beforedepend:: ocamlmklibconfig.ml
clean::
- rm -f ocamlmklib.ml
-
+ rm -f ocamlmklibconfig.ml
# Converter olabl/ocaml 2.99 to ocaml 3
diff --git a/tools/eqparsetree.ml b/tools/eqparsetree.ml
index 6326d67e0..332efa3e1 100644
--- a/tools/eqparsetree.ml
+++ b/tools/eqparsetree.ml
@@ -666,7 +666,7 @@ and eq_expression_desc :
eq_list
(fun ((a0, a1), (b0, b1)) ->
(eq_pattern (a0, b0)) && (eq_expression (a1, b1)))
- (a2, b2))
+ (a2, b2)
| (Pexp_apply (a0, a1), Pexp_apply (b0, b1)) ->
(eq_expression (a0, b0)) &&
(eq_list
diff --git a/tools/ocamlmklib.mlp b/tools/ocamlmklib.ml
index 9a47d1b5e..0ef86979b 100644
--- a/tools/ocamlmklib.mlp
+++ b/tools/ocamlmklib.ml
@@ -11,7 +11,7 @@
(***********************************************************************)
open Printf
-open Myocamlbuild_config
+open Ocamlmklibconfig
(* PR#4783: under Windows, don't use absolute paths because we do
not know where the binary distribution will be installed. *)