ocaml/Makefile.Mac

489 lines
14 KiB
Makefile

#########################################################################
# #
# Objective Caml #
# #
# Damien Doligez, projet Para, INRIA Rocquencourt #
# #
# Copyright 1999 Institut National de Recherche en Informatique et #
# en Automatique. All rights reserved. This file is distributed #
# under the terms of the Q Public License version 1.0. #
# #
#########################################################################
# $Id$
# The main Makefile
MacVersion = "Mac{MAJOR}.{MINOR}.{BUGFIX}{STAGE}{REV}"
CAMLC = :boot:ocamlrun :boot:ocamlc -I :boot:
COMPFLAGS = {INCLUDES}
LINKFLAGS =
CAMLYACC = :boot:ocamlyacc
YACCFLAGS =
CAMLLEX = :boot:ocamlrun :boot:ocamllex
CAMLDEP = :boot:ocamlrun :tools:ocamldep
DEPFLAGS = {INCLUDES}
CAMLRUN = :byterun:ocamlrun
INCLUDES = -I :utils: -I :parsing: -I :typing: -I :bytecomp: ¶
-I :driver: -I :toplevel:
UTILS = :utils:misc.cmo :utils:tbl.cmo :utils:config.cmo ¶
:utils:clflags.cmo :utils:terminfo.cmo :utils:ccomp.cmo ¶
:utils:warnings.cmo
PARSING = :parsing:linenum.cmo :parsing:location.cmo :parsing:longident.cmo ¶
:parsing:syntaxerr.cmo :parsing:parser.cmo ¶
:parsing:lexer.cmo :parsing:parse.cmo :parsing:printast.cmo
TYPING = :typing:ident.cmo :typing:path.cmo ¶
:typing:primitive.cmo :typing:types.cmo ¶
:typing:btype.cmo ¶
:typing:subst.cmo :typing:predef.cmo ¶
:typing:datarepr.cmo :typing:env.cmo ¶
:typing:typedtree.cmo ¶
:typing:ctype.cmo :typing:printtyp.cmo ¶
:typing:includeclass.cmo ¶
:typing:mtype.cmo :typing:includecore.cmo ¶
:typing:includemod.cmo :typing:parmatch.cmo ¶
:typing:typetexp.cmo :typing:typecore.cmo ¶
:typing:typedecl.cmo :typing:typeclass.cmo ¶
:typing:typemod.cmo
COMP = :bytecomp:lambda.cmo :bytecomp:printlambda.cmo ¶
:bytecomp:typeopt.cmo :bytecomp:switch.cmo :bytecomp:matching.cmo ¶
:bytecomp:translobj.cmo :bytecomp:translcore.cmo ¶
:bytecomp:translclass.cmo :bytecomp:translmod.cmo ¶
:bytecomp:simplif.cmo :bytecomp:runtimedef.cmo
BYTECOMP = :bytecomp:meta.cmo :bytecomp:instruct.cmo :bytecomp:bytegen.cmo ¶
:bytecomp:printinstr.cmo :bytecomp:opcodes.cmo :bytecomp:emitcode.cmo ¶
:bytecomp:bytesections.cmo :bytecomp:dll.cmo ¶
:bytecomp:symtable.cmo :bytecomp:bytelibrarian.cmo :bytecomp:bytelink.cmo
DRIVER = :driver:errors.cmo :driver:compile.cmo :driver:main_args.cmo ¶
:driver:main.cmo
TOPLEVEL = :driver:errors.cmo :driver:compile.cmo ¶
:toplevel:genprintval.cmo :toplevel:toploop.cmo ¶
:toplevel:trace.cmo :toplevel:topdirs.cmo
TOPLEVELMAIN = :toplevel:topmain.cmo
COMPOBJS = {UTILS} {PARSING} {TYPING} {COMP} {BYTECOMP} {DRIVER}
TOPLIB = {UTILS} {PARSING} {TYPING} {COMP} {BYTECOMP} {TOPLEVEL}
EXPUNGEOBJS = :utils:misc.cmo :utils:tbl.cmo ¶
:utils:config.cmo :utils:clflags.cmo ¶
:typing:ident.cmo :typing:path.cmo ¶
:typing:types.cmo :typing:btype.cmo :typing:predef.cmo ¶
:bytecomp:runtimedef.cmo :bytecomp:bytesections.cmo ¶
:bytecomp:dll.cmo :bytecomp:symtable.cmo ¶
:toplevel:expunge.cmo
PERVASIVES = arg array buffer callback char digest filename format gc hashtbl ¶
lexing list map obj parsing pervasives printexc printf queue random ¶
set sort stack string stream sys oo genlex topdirs toploop weak lazy ¶
marshal int32 int64 nativeint outcometree
# Recompile the system using the bootstrap compiler
all Ä runtime ocamlc ocamllex ocamlyacc ocamltools library ocaml
otherlibraries camlp4out maccaml
# The compilation of ocaml will fail if the runtime has changed.
# Never mind, just do make bootstrap to reach fixpoint again.
# Compile everything the first time
world Ä
domake coldstart
domake all
# Complete bootstrapping cycle
bootstrap Ä
# Save the original bootstrap compiler
domake backup
# Promote the new compiler but keep the old runtime
# This compiler runs on :boot:ocamlrun and produces bytecode for
# :byterun:ocamlrun
domake promote-cross
# Rebuild ocamlc and ocamllex (run on :byterun:ocamlrun)
domake partialclean
domake ocamlc ocamllex
# Rebuild the library (using :byterun:ocamlrun :ocamlc)
domake library-cross
# Promote the new compiler and the new runtime
domake promote
# Rebuild everything, including ocaml and the tools
domake partialclean
domake all
# Check if fixpoint reached
domake compare
LIBFILES = :stdlib.cma :std_exit.cmo :Å.cmi camlheader
# Start up the system from the distribution compiler
coldstart Ä
directory :byterun; domake all; directory ::
duplicate -y :byterun:ocamlrun :boot:ocamlrun
directory :yacc; domake all; directory ::
duplicate -y :yacc:ocamlyacc :boot:ocamlyacc
directory :stdlib
domake -d COMPILER=::boot:ocamlc all
duplicate -y {LIBFILES} ::boot:
directory ::
# Build the core system: the minimum needed to make depend and bootstrap
core Ä runtime ocamlc ocamllex ocamlyacc ocamltools library
# Save the current bootstrap compiler
backup Ä
if `exists -d :boot:Saved:` == ""
newfolder :boot:Saved:
end
move :boot:Saved: :boot:Saved.prev:
newfolder :boot:Saved:
move :boot:Saved.prev: :boot:Saved:Saved.prev:
duplicate -y :boot:ocamlrun :boot:Saved:
move :boot:ocamlc :boot:ocamllex :boot:ocamlyacc :boot:Saved:
directory :boot; duplicate -y {LIBFILES} :Saved:; directory ::
# Promote the newly compiled system to the rank of cross compiler
# (Runs on the old runtime, produces code for the new runtime)
promote-cross Ä
duplicate -y :ocamlc :boot:ocamlc
duplicate -y :lex:ocamllex :boot:ocamllex
duplicate -y :yacc:ocamlyacc :boot:ocamlyacc
directory :stdlib
duplicate -y {LIBFILES} ::boot: || set status 0
directory ::
# Promote the newly compiled system to the rank of bootstrap compiler
# (Runs on the new runtime, produces code for the new runtime)
promote Ä promote-cross
duplicate -y :byterun:ocamlrun :boot:ocamlrun
clean ÄÄ
delete -i :boot:Å.cm[aio] || set status 0
delete -i :boot:camlheader :boot:ocamlrun :boot:ocamlyacc
# Restore the saved bootstrap compiler if a problem arises
restore Ä
move -y :boot:Saved:Å :boot:
delete -y :boot:Saved:
move -y :boot:Saved.prev: :boot:Saved:
# Check if fixpoint reached
compare Ä
set exit 0
equal -q :boot:ocamlc :ocamlc && equal -q :boot:ocamllex :lex:ocamllex
if {status}
echo "¶nFixpoint not reached, try one more bootstrapping cycle.¶n"
else
echo "¶nFixpoint reached, bootstrap succeeded.¶n"
end
# Remove old bootstrap compilers
cleanboot Ä
delete -i -y :boot:Saved:Saved.prev|| set status 0
install Ä $OutOfDate
flush
for i in "{BINDIR}" "{LIBDIR}" "{APPLIDIR}" "{APPLIDIR}stdlib:"
if "`exists -d "{i}"`" == ""
newfolder "{i}"
end
end
directory :byterun:
domake install
directory ::
duplicate -y :ocamlc "{BINDIR}ocamlc"
duplicate -y :ocaml "{BINDIR}ocaml"
directory :stdlib:
domake install
directory ::
duplicate -y :lex:ocamllex "{BINDIR}ocamllex"
duplicate -y :yacc:ocamlyacc "{BINDIR}ocamlyacc"
duplicate -y toplevellib.cma expunge "{LIBDIR}"
duplicate -y :typing:outcometree.cmi :typing:outcometree.mli "{LIBDIR}"
duplicate -y :toplevel:topmain.cmo "{LIBDIR}topmain.cmo"
duplicate -y :toplevel:toploop.cmi :toplevel:topdirs.cmi "{LIBDIR}"
directory :tools:
domake install
directory ::
directory :camlp4:
execute :config:config.mpw
domake install -d LIBDIR="{LIBDIR}camlp4:"
directory ::
duplicate -y :man:ocaml.help "{HELPFILE}"
for i in {OTHERLIBRARIES}
directory :otherlibs:{i}
domake install
directory :::
end
duplicate -y "{LIBDIR}"Å "{APPLIDIR}stdlib:"
duplicate -y :test:Moretest:graph_example.ml "{APPLIDIR}"
directory :maccaml:
domake install
directory ::
clean ÄÄ partialclean
# The compiler
ocamlc Ä {COMPOBJS}
{CAMLC} {LINKFLAGS} -o ocamlc {COMPOBJS}
partialclean ÄÄ
delete -i ocamlc
# The toplevel
ocaml Ä toplevellib.cma {TOPLEVELMAIN} expunge
{CAMLC} {LINKFLAGS} -linkall -o ocaml.tmp toplevellib.cma {TOPLEVELMAIN}
{CAMLRUN} :expunge ocaml.tmp ocaml {PERVASIVES} || set status 0
delete -i ocaml.tmp
toplevellib.cma Ä {TOPLIB}
{CAMLC} -a -o toplevellib.cma {TOPLIB}
partialclean ÄÄ
delete -i ocaml toplevellib.cma
# The configuration file
:utils:config.ml Ä :utils:config.mlp :config:config.Mac
delete -i :utils:config.ml
streamedit -e "/let version =/ replace /¶¶¶"°/ ¶"/{MacVersion}¶¶¶"""
-e "1,$ replace /%%BYTERUN%%/ ¶"{BINDIR}ocamlrun¶""
-e "1,$ replace /%%LIBDIR%%/ ¶"{LIBDIR}""
-e "1,$ replace /%%EXT_OBJ%%/ '.o'"
-e "1,$ replace /%%EXT_LIB%%/ '.x'"
:utils:config.mlp > :utils:config.ml
partialclean ÄÄ
delete -i :utils:config.ml
beforedepend ÄÄ :utils:config.ml
# The parser
:parsing:parser.mli Ä :parsing:parser.ml
echo -n
:parsing:parser.ml Ä :parsing:parser.mly
{CAMLYACC} {YACCFLAGS} :parsing:parser.mly
partialclean ÄÄ
delete -i :parsing:parser.mli :parsing:parser.ml :parsing:parser.output
beforedepend ÄÄ :parsing:parser.mli :parsing:parser.ml
# The lexer
:parsing:lexer.ml Ä :parsing:lexer.mll
streamedit -e "1,$ replace /¶¶''\223'¶¶'-¶¶''\246'¶¶'/ '' -c °"
-e "1,$ replace /¶¶''\248'¶¶'-¶¶''\255'¶¶'/ '' -c °"
-e "1,$ replace /¶¶''\192'¶¶'-¶¶''\214'¶¶'/ '' -c °"
-e "1,$ replace /¶¶''\216'¶¶'-¶¶''\222'¶¶'/ '' -c °"
-e "1,$ replace /¶¶''\216'¶¶'-¶¶''\246'¶¶'/ '' -c °"
<:parsing:lexer.mll >:parsing:lexer_tmp.mll
{CAMLLEX} :parsing:lexer_tmp.mll
rename -y :parsing:lexer_tmp.ml :parsing:lexer.ml
partialclean ÄÄ
delete -i :parsing:lexer.ml
beforedepend ÄÄ :parsing:lexer.ml
# The auxiliary lexer for counting line numbers
:parsing:linenum.ml Ä :parsing:linenum.mll
{CAMLLEX} :parsing:linenum.mll
partialclean ÄÄ
delete -i :parsing:linenum.ml
beforedepend ÄÄ :parsing:linenum.ml
# The numeric opcodes
:bytecomp:opcodes.ml Ä :byterun:instruct.h
:tools:make-opcodes.Mac :byterun:instruct.h :bytecomp:opcodes.ml
partialclean ÄÄ
delete -i :bytecomp:opcodes.ml
beforedepend ÄÄ :bytecomp:opcodes.ml
# The predefined exceptions and primitives
:byterun:primitives Ä
directory :byterun:
domake primitives
directory ::
:bytecomp:runtimedef.ml Ä :byterun:primitives :byterun:fail.h
(echo 'let builtin_exceptions = [|' ;
streamedit -d -e '/¶/¶* (¶"[A-Za-z_]*¶")¨0 ¶*¶/°/ print ¨0 ";"' :byterun:fail.h |
streamedit -e '$ replace /;°/ "|]"';
echo 'let builtin_primitives = [|';
streamedit -e "1,$ replace /(Å)¨0/ ' ¶"' ¨0 '";'" -e '$ replace /;°/ "|]"' :byterun:primitives;
) > :bytecomp:runtimedef.ml
partialclean ÄÄ
delete -i :bytecomp:runtimedef.ml
beforedepend ÄÄ :bytecomp:runtimedef.ml
# The "expunge" utility
expunge Ä {EXPUNGEOBJS}
{CAMLC} {LINKFLAGS} -o expunge {EXPUNGEOBJS}
partialclean ÄÄ
delete -i expunge
# The runtime system for the bytecode compiler
runtime Ä
directory :byterun:; domake all; directory ::
clean ÄÄ
directory :byterun:; domake clean; directory ::
alldepend ÄÄ
directory :byterun:; domake depend; directory ::
# The library
library Ä ocamlc
directory :stdlib; domake all; directory ::
library-cross Ä
directory :stdlib; domake -d RUNTIME=::byterun:ocamlrun all; directory ::
partialclean ÄÄ
directory :stdlib; domake clean; directory ::
alldepend ÄÄ
directory :stdlib; domake depend; directory ::
# The lexer and parser generators
ocamllex Ä ocamlyacc ocamlc
directory :lex; domake all; directory ::
partialclean ÄÄ
directory :lex; domake clean; directory ::
alldepend ÄÄ
directory :lex; domake depend; directory ::
ocamlyacc Ä
directory :yacc; domake all; directory ::
clean ÄÄ
directory :yacc; domake clean; directory ::
# Tools
ocamltools Ä ocamlc ocamlyacc ocamllex
directory :tools; domake all; directory ::
partialclean ÄÄ
directory :tools; domake clean; directory ::
alldepend ÄÄ
directory :tools; domake depend; directory ::
# The extra libraries
otherlibraries Ä
for i in {OTHERLIBRARIES}
directory :otherlibs:{i}; domake all; directory :::
end
partialclean ÄÄ
for i in {OTHERLIBRARIES}
directory :otherlibs:{i}; domake partialclean; directory :::
end
clean ÄÄ
for i in {OTHERLIBRARIES}
directory :otherlibs:{i}; domake clean; directory :::
end
alldepend ÄÄ
for i in {OTHERLIBRARIES}
directory :otherlibs:{i}; domake depend; directory :::
end
# Camlp4
camlp4out Ä ocamlc
directory :camlp4:
execute :config:config.mpw
domake all
directory ::
partialclean ÄÄ
directory :camlp4:
execute :config:config.mpw
domake clean
directory ::
alldepend ÄÄ
directory :camlp4:
execute :config:config.mpw
domake depend
directory ::
# The standalone application
maccaml Ä
directory :maccaml:; domake all; directory ::
partialclean ÄÄ
directory :maccaml:; domake partialclean; directory ::
clean ÄÄ
directory :maccaml:; domake clean; directory ::
alldepend ÄÄ
directory :maccaml:; domake depend; directory ::
# Clean up the test directory
clean ÄÄ
if `exists :test:`
directory :test:; domake clean; directory ::
end
# Default rules
.cmo Ä .ml
{CAMLC} {COMPFLAGS} -c {depdir}{default}.ml
.cmi Ä .mli
{CAMLC} {COMPFLAGS} -c {depdir}{default}.mli
partialclean ÄÄ
for i in utils parsing typing bytecomp driver toplevel tools
delete -i :{i}:Å.cm[io] || set status 0
end
depend Ä beforedepend
for d in utils parsing typing bytecomp driver toplevel
{CAMLDEP} {DEPFLAGS} :{d}:Å.mli :{d}:Å.ml
end > Makefile.Mac.depend
alldepend ÄÄ depend
# Make sure the config file was executed
dummy Ä {OTHERLIBRARIES}