Core review work

- Apply the __ heuristic more systematically
- Update tests
- Fix Windows builds
master
Jeremie Dimino 2017-08-18 16:30:39 +01:00 committed by Jeremie Dimino
parent 8f2a15369f
commit 84304a3282
18 changed files with 162 additions and 229 deletions

22
.depend
View File

@ -673,18 +673,20 @@ bytecomp/translclass.cmi : typing/typedtree.cmi parsing/location.cmi \
bytecomp/lambda.cmi typing/ident.cmi parsing/asttypes.cmi
bytecomp/translcore.cmo : typing/types.cmi typing/typeopt.cmi \
typing/typedtree.cmi typing/typecore.cmi bytecomp/translobj.cmi \
bytecomp/translattribute.cmi typing/primitive.cmi typing/predef.cmi \
typing/path.cmi typing/parmatch.cmi utils/misc.cmi bytecomp/matching.cmi \
parsing/longident.cmi parsing/location.cmi bytecomp/lambda.cmi \
typing/ident.cmi typing/env.cmi utils/config.cmi utils/clflags.cmi \
typing/btype.cmi parsing/asttypes.cmi bytecomp/translcore.cmi
bytecomp/translattribute.cmi typing/printtyp.cmi typing/primitive.cmi \
typing/predef.cmi typing/path.cmi typing/parmatch.cmi utils/misc.cmi \
bytecomp/matching.cmi parsing/longident.cmi parsing/location.cmi \
bytecomp/lambda.cmi typing/ident.cmi typing/env.cmi utils/config.cmi \
utils/clflags.cmi typing/btype.cmi parsing/asttypes.cmi \
bytecomp/translcore.cmi
bytecomp/translcore.cmx : typing/types.cmx typing/typeopt.cmx \
typing/typedtree.cmx typing/typecore.cmx bytecomp/translobj.cmx \
bytecomp/translattribute.cmx typing/primitive.cmx typing/predef.cmx \
typing/path.cmx typing/parmatch.cmx utils/misc.cmx bytecomp/matching.cmx \
parsing/longident.cmx parsing/location.cmx bytecomp/lambda.cmx \
typing/ident.cmx typing/env.cmx utils/config.cmx utils/clflags.cmx \
typing/btype.cmx parsing/asttypes.cmi bytecomp/translcore.cmi
bytecomp/translattribute.cmx typing/printtyp.cmx typing/primitive.cmx \
typing/predef.cmx typing/path.cmx typing/parmatch.cmx utils/misc.cmx \
bytecomp/matching.cmx parsing/longident.cmx parsing/location.cmx \
bytecomp/lambda.cmx typing/ident.cmx typing/env.cmx utils/config.cmx \
utils/clflags.cmx typing/btype.cmx parsing/asttypes.cmi \
bytecomp/translcore.cmi
bytecomp/translcore.cmi : typing/types.cmi typing/typedtree.cmi \
typing/primitive.cmi typing/path.cmi parsing/location.cmi \
bytecomp/lambda.cmi typing/ident.cmi typing/env.cmi parsing/asttypes.cmi

12
Changes
View File

@ -1257,10 +1257,14 @@ OCaml 4.05.0 (13 Jul 2017):
(François Bobot, review by Gabriel Scherer, Xavier Leroy, Damien Doligez,
Frédéric Bour)
* GPR#1010: change the compilation scheme of the stdlib. Now x.ml in
compiles to stdlib__x.cm* and we add a Stdlib alias module that is
opened by default to get back the short names.
(Jeremie Dimino, review by Gabriel Radanne)
* GPR#1010: pack all standard library modules into a single module Stdlib
which is the default opened module (Stdlib itself includes Pervasives) to free
up the global namespace for other standard libraries, while still allowing any
OCaml standard library module to be referred to as Stdlib.Module). This is
implemented efficiently using module aliases (prefixing all modules with
Stdlib__, e.g. Stdlib__string).
(Jérémie Dimino, David Allsopp and Florian Angeletti, review by David Allsopp
and Gabriel Radanne)
### Manual and documentation:

View File

@ -956,7 +956,8 @@ clean::
otherlibs_all := bigarray dynlink graph raw_spacetime_lib \
str systhreads threads unix win32graph win32unix
subdirs := asmrun byterun debugger lex ocamldoc ocamltest stdlib tools \
$(addprefix otherlibs/, $(otherlibs_all))
$(addprefix otherlibs/, $(otherlibs_all)) \
ocamldoc/stdlib_non_prefixed
.PHONY: alldepend
ifeq "$(TOOLCHAIN)" "msvc"

View File

@ -274,117 +274,3 @@ generators/odoc_todo.cmx : odoc_module.cmx odoc_info.cmx odoc_html.cmx \
odoc_gen.cmx odoc_args.cmx
generators/odoc_todo.cmxs : odoc_module.cmx odoc_info.cmx odoc_html.cmx \
odoc_gen.cmx odoc_args.cmx
stdlib_non_prefixed/arg.cmi :
stdlib_non_prefixed/array.cmi :
stdlib_non_prefixed/arrayLabels.cmi :
stdlib_non_prefixed/ast_helper.cmi : stdlib_non_prefixed/parsetree.cmi \
stdlib_non_prefixed/longident.cmi stdlib_non_prefixed/location.cmi \
stdlib_non_prefixed/docstrings.cmi stdlib_non_prefixed/asttypes.cmi
stdlib_non_prefixed/ast_invariants.cmi : stdlib_non_prefixed/parsetree.cmi
stdlib_non_prefixed/ast_iterator.cmi : stdlib_non_prefixed/parsetree.cmi \
stdlib_non_prefixed/location.cmi
stdlib_non_prefixed/ast_mapper.cmi : stdlib_non_prefixed/parsetree.cmi \
stdlib_non_prefixed/location.cmi
stdlib_non_prefixed/asttypes.cmi : stdlib_non_prefixed/location.cmi
stdlib_non_prefixed/attr_helper.cmi : stdlib_non_prefixed/parsetree.cmi \
stdlib_non_prefixed/location.cmi stdlib_non_prefixed/format.cmi \
stdlib_non_prefixed/asttypes.cmi
stdlib_non_prefixed/big_int.cmi : stdlib_non_prefixed/nat.cmi
stdlib_non_prefixed/bigarray.cmi : stdlib_non_prefixed/unix.cmi \
stdlib_non_prefixed/complex.cmi \
stdlib_non_prefixed/camlinternalBigarray.cmi
stdlib_non_prefixed/buffer.cmi : stdlib_non_prefixed/uchar.cmi
stdlib_non_prefixed/builtin_attributes.cmi : \
stdlib_non_prefixed/parsetree.cmi stdlib_non_prefixed/location.cmi \
stdlib_non_prefixed/ast_iterator.cmi
stdlib_non_prefixed/bytes.cmi :
stdlib_non_prefixed/bytesLabels.cmi :
stdlib_non_prefixed/callback.cmi :
stdlib_non_prefixed/camlinternalBigarray.cmi : \
stdlib_non_prefixed/complex.cmi
stdlib_non_prefixed/camlinternalFormat.cmi : \
stdlib_non_prefixed/camlinternalFormatBasics.cmi \
stdlib_non_prefixed/buffer.cmi
stdlib_non_prefixed/camlinternalFormatBasics.cmi :
stdlib_non_prefixed/camlinternalLazy.cmi :
stdlib_non_prefixed/camlinternalMod.cmi : stdlib_non_prefixed/obj.cmi
stdlib_non_prefixed/camlinternalOO.cmi : stdlib_non_prefixed/obj.cmi
stdlib_non_prefixed/char.cmi :
stdlib_non_prefixed/complex.cmi :
stdlib_non_prefixed/depend.cmi : stdlib_non_prefixed/set.cmi \
stdlib_non_prefixed/parsetree.cmi stdlib_non_prefixed/map.cmi \
stdlib_non_prefixed/longident.cmi
stdlib_non_prefixed/digest.cmi :
stdlib_non_prefixed/docstrings.cmi : stdlib_non_prefixed/parsetree.cmi \
stdlib_non_prefixed/location.cmi stdlib_non_prefixed/lexing.cmi \
stdlib_non_prefixed/lazy.cmi
stdlib_non_prefixed/ephemeron.cmi : stdlib_non_prefixed/hashtbl.cmi
stdlib_non_prefixed/filename.cmi :
stdlib_non_prefixed/format.cmi : stdlib_non_prefixed/pervasives.cmi \
stdlib_non_prefixed/buffer.cmi
stdlib_non_prefixed/gc.cmi :
stdlib_non_prefixed/genlex.cmi : stdlib_non_prefixed/stream.cmi
stdlib_non_prefixed/hashtbl.cmi :
stdlib_non_prefixed/int32.cmi :
stdlib_non_prefixed/int64.cmi :
stdlib_non_prefixed/lazy.cmi :
stdlib_non_prefixed/lexer.cmi : stdlib_non_prefixed/parser.cmi \
stdlib_non_prefixed/location.cmi stdlib_non_prefixed/lexing.cmi \
stdlib_non_prefixed/format.cmi
stdlib_non_prefixed/lexing.cmi :
stdlib_non_prefixed/list.cmi :
stdlib_non_prefixed/listLabels.cmi :
stdlib_non_prefixed/location.cmi : stdlib_non_prefixed/warnings.cmi \
stdlib_non_prefixed/lexing.cmi stdlib_non_prefixed/format.cmi
stdlib_non_prefixed/longident.cmi :
stdlib_non_prefixed/map.cmi :
stdlib_non_prefixed/marshal.cmi :
stdlib_non_prefixed/moreLabels.cmi : stdlib_non_prefixed/set.cmi \
stdlib_non_prefixed/map.cmi stdlib_non_prefixed/hashtbl.cmi
stdlib_non_prefixed/nat.cmi :
stdlib_non_prefixed/nativeint.cmi :
stdlib_non_prefixed/num.cmi : stdlib_non_prefixed/ratio.cmi \
stdlib_non_prefixed/nat.cmi stdlib_non_prefixed/big_int.cmi
stdlib_non_prefixed/obj.cmi : stdlib_non_prefixed/int32.cmi
stdlib_non_prefixed/oo.cmi : stdlib_non_prefixed/camlinternalOO.cmi
stdlib_non_prefixed/parse.cmi : stdlib_non_prefixed/parsetree.cmi \
stdlib_non_prefixed/lexing.cmi
stdlib_non_prefixed/parser.cmi : stdlib_non_prefixed/parsetree.cmi \
stdlib_non_prefixed/location.cmi stdlib_non_prefixed/lexing.cmi \
stdlib_non_prefixed/docstrings.cmi
stdlib_non_prefixed/parsetree.cmi : stdlib_non_prefixed/longident.cmi \
stdlib_non_prefixed/location.cmi stdlib_non_prefixed/asttypes.cmi
stdlib_non_prefixed/parsing.cmi : stdlib_non_prefixed/obj.cmi \
stdlib_non_prefixed/lexing.cmi
stdlib_non_prefixed/pervasives.cmi : \
stdlib_non_prefixed/camlinternalFormatBasics.cmi
stdlib_non_prefixed/pprintast.cmi : stdlib_non_prefixed/parsetree.cmi \
stdlib_non_prefixed/format.cmi
stdlib_non_prefixed/printast.cmi : stdlib_non_prefixed/parsetree.cmi \
stdlib_non_prefixed/format.cmi
stdlib_non_prefixed/printexc.cmi :
stdlib_non_prefixed/printf.cmi : stdlib_non_prefixed/buffer.cmi
stdlib_non_prefixed/queue.cmi :
stdlib_non_prefixed/random.cmi : stdlib_non_prefixed/nativeint.cmi \
stdlib_non_prefixed/int64.cmi stdlib_non_prefixed/int32.cmi
stdlib_non_prefixed/ratio.cmi : stdlib_non_prefixed/nat.cmi \
stdlib_non_prefixed/big_int.cmi
stdlib_non_prefixed/scanf.cmi : stdlib_non_prefixed/pervasives.cmi
stdlib_non_prefixed/set.cmi :
stdlib_non_prefixed/sort.cmi :
stdlib_non_prefixed/spacetime.cmi :
stdlib_non_prefixed/stack.cmi :
stdlib_non_prefixed/stdLabels.cmi : stdlib_non_prefixed/stringLabels.cmi \
stdlib_non_prefixed/listLabels.cmi stdlib_non_prefixed/bytesLabels.cmi \
stdlib_non_prefixed/arrayLabels.cmi
stdlib_non_prefixed/str.cmi :
stdlib_non_prefixed/stream.cmi :
stdlib_non_prefixed/string.cmi :
stdlib_non_prefixed/stringLabels.cmi :
stdlib_non_prefixed/syntaxerr.cmi : stdlib_non_prefixed/location.cmi \
stdlib_non_prefixed/format.cmi
stdlib_non_prefixed/sys.cmi :
stdlib_non_prefixed/uchar.cmi :
stdlib_non_prefixed/unix.cmi : stdlib_non_prefixed/camlinternalBigarray.cmi
stdlib_non_prefixed/warnings.cmi :
stdlib_non_prefixed/weak.cmi : stdlib_non_prefixed/hashtbl.cmi

View File

@ -450,7 +450,7 @@ clean:
rm -f odoc_parser.output odoc_text_parser.output
rm -f odoc_lexer.ml odoc_text_lexer.ml odoc_see_lexer.ml odoc_ocamlhtml.ml
rm -f odoc_parser.ml odoc_parser.mli odoc_text_parser.ml odoc_text_parser.mli
rm -rf stdlib_man
rm -rf stdlib_man stdlib_html
rm -f generators/*.cm[taiox] generators/*.$(A) generators/*.$(O) generators/*.cmx[as]
rm -f stdlib_non_prefixed/*.mli stdlib_non_prefixed/*.cmi

View File

@ -36,7 +36,6 @@ STDLIB_MLIS=\
str.mli \
unix.mli unixLabels.mli \
bigarray.mli \
num.mli arith_status.mli big_int.mli ratio.mli \
graphics.mli graphicsX11.mli \
dynlink.mli \
thread.mli mutex.mli condition.mli event.mli threadUnix.mli \
@ -47,8 +46,7 @@ STDLIB_MLIS:=$(addprefix $(STDLIB_UNPREFIXED)/, $(STDLIB_MLIS))
# Dependencies for the documented modules
STDLIB_DEPS:=$(STDLIB_MLIS) \
$(TYPING_MLIS:$(SRC)/typing/%.mli=$(STDLIB_UNPREFIXED)/%.mli) \
$(BYTECOMP_MLIS:$(SRC)/bytecomp/%.mli=$(STDLIB_UNPREFIXED)/%.mli) \
$(STDLIB_UNPREFIXED)/nat.mli
$(BYTECOMP_MLIS:$(SRC)/bytecomp/%.mli=$(STDLIB_UNPREFIXED)/%.mli)
# Add back the isolated modules in typing and bytecomp
STDLIB_MLIS:= $(STDLIB_MLIS) \
@ -104,7 +102,7 @@ $(STDLIB_UNPREFIXED)/%.mli: $(SRC)/bytecomp/%.mli
#Extract the pervasives module from stdlib.mli
$(STDLIB_UNPREFIXED)/pervasives.mli: $(SRC)/stdlib/stdlib.mli $(STDLIB_UNPREFIXED)/extract_pervasives.awk
awk -f $(STDLIB_UNPREFIXED)/extract_pervasives.awk $< > $@
$(AWK) -f $(STDLIB_UNPREFIXED)/extract_pervasives.awk $< > $@
# Build cmis file inside the STDLIB_UNPREFIXED directories
$(STDLIB_CMIS): $(STDLIB_DEPS)

View File

@ -1,7 +1,6 @@
annot.cmi : location.cmi
arg.cmi :
arg_helper.cmi : map.cmi
arith_status.cmi :
array.cmi :
arrayLabels.cmi :
ast_helper.cmi : parsetree.cmi longident.cmi location.cmi docstrings.cmi \
@ -11,12 +10,11 @@ ast_iterator.cmi : parsetree.cmi location.cmi
ast_mapper.cmi : parsetree.cmi location.cmi
asttypes.cmi : location.cmi
attr_helper.cmi : parsetree.cmi location.cmi format.cmi asttypes.cmi
big_int.cmi : nat.cmi
bigarray.cmi : unix.cmi complex.cmi camlinternalBigarray.cmi
btype.cmi : types.cmi set.cmi path.cmi map.cmi hashtbl.cmi format.cmi \
asttypes.cmi
buffer.cmi : uchar.cmi
builtin_attributes.cmi : parsetree.cmi location.cmi ast_iterator.cmi
builtin_attributes.cmi : parsetree.cmi location.cmi
bytegen.cmi : lambda.cmi instruct.cmi
bytelibrarian.cmi : format.cmi
bytelink.cmi : symtable.cmi format.cmi digest.cmi cmo_format.cmi
@ -33,7 +31,7 @@ camlinternalMod.cmi : obj.cmi
camlinternalOO.cmi : obj.cmi
ccomp.cmi :
char.cmi :
clflags.cmi : misc.cmi arg.cmi
clflags.cmi : profile.cmi misc.cmi arg.cmi
cmi_format.cmi : types.cmi format.cmi digest.cmi
cmo_format.cmi : tbl.cmi lambda.cmi ident.cmi digest.cmi
cmt_format.cmi : types.cmi typedtree.cmi location.cmi env.cmi digest.cmi \
@ -50,9 +48,9 @@ dll.cmi :
docstrings.cmi : parsetree.cmi location.cmi lexing.cmi lazy.cmi
dynlink.cmi : digest.cmi
emitcode.cmi : instruct.cmi ident.cmi cmo_format.cmi
env.cmi : warnings.cmi types.cmi subst.cmi path.cmi map.cmi longident.cmi \
location.cmi ident.cmi format.cmi digest.cmi consistbl.cmi cmi_format.cmi \
asttypes.cmi
env.cmi : warnings.cmi types.cmi subst.cmi path.cmi misc.cmi map.cmi \
longident.cmi location.cmi ident.cmi format.cmi digest.cmi consistbl.cmi \
cmi_format.cmi asttypes.cmi
envaux.cmi : subst.cmi path.cmi format.cmi env.cmi
ephemeron.cmi : hashtbl.cmi
event.cmi :
@ -73,8 +71,8 @@ includemod.cmi : types.cmi typedtree.cmi path.cmi location.cmi \
instruct.cmi : types.cmi subst.cmi location.cmi lambda.cmi ident.cmi env.cmi
int32.cmi :
int64.cmi :
lambda.cmi : types.cmi set.cmi primitive.cmi path.cmi location.cmi ident.cmi \
env.cmi asttypes.cmi
lambda.cmi : types.cmi primitive.cmi path.cmi location.cmi ident.cmi env.cmi \
asttypes.cmi
lazy.cmi :
lexer.cmi : parser.cmi location.cmi lexing.cmi format.cmi
lexing.cmi :
@ -90,16 +88,14 @@ misc.cmi : set.cmi map.cmi hashtbl.cmi format.cmi
moreLabels.cmi : set.cmi map.cmi hashtbl.cmi
mtype.cmi : types.cmi path.cmi ident.cmi env.cmi
mutex.cmi :
nat.cmi :
nativeint.cmi :
num.cmi : ratio.cmi nat.cmi big_int.cmi
numbers.cmi : set.cmi int64.cmi identifiable.cmi
obj.cmi : int32.cmi
oo.cmi : camlinternalOO.cmi
oprint.cmi : outcometree.cmi format.cmi
outcometree.cmi : format.cmi asttypes.cmi
parmatch.cmi : types.cmi typedtree.cmi parsetree.cmi longident.cmi \
location.cmi hashtbl.cmi format.cmi env.cmi asttypes.cmi
parmatch.cmi : types.cmi typedtree.cmi parsetree.cmi location.cmi \
hashtbl.cmi env.cmi asttypes.cmi
parse.cmi : parsetree.cmi lexing.cmi
parser.cmi : parsetree.cmi location.cmi lexing.cmi docstrings.cmi
parsetree.cmi : longident.cmi location.cmi asttypes.cmi
@ -115,12 +111,13 @@ printexc.cmi :
printf.cmi : buffer.cmi
printinstr.cmi : instruct.cmi format.cmi
printlambda.cmi : lambda.cmi format.cmi
printpat.cmi : typedtree.cmi format.cmi asttypes.cmi
printtyp.cmi : types.cmi path.cmi outcometree.cmi longident.cmi ident.cmi \
format.cmi env.cmi asttypes.cmi
printtyped.cmi : typedtree.cmi format.cmi
profile.cmi : format.cmi
queue.cmi :
random.cmi : nativeint.cmi int64.cmi int32.cmi
ratio.cmi : nat.cmi big_int.cmi
runtimedef.cmi :
scanf.cmi : pervasives.cmi
semantics_of_primitives.cmi : lambda.cmi
@ -149,7 +146,6 @@ tbl.cmi : format.cmi
terminfo.cmi :
thread.cmi : unix.cmi
threadUnix.cmi : unix.cmi
timings.cmi : format.cmi
translattribute.cmi : typedtree.cmi parsetree.cmi location.cmi lambda.cmi
translclass.cmi : typedtree.cmi location.cmi lambda.cmi ident.cmi format.cmi \
asttypes.cmi
@ -175,11 +171,11 @@ typeopt.cmi : types.cmi typedtree.cmi path.cmi lambda.cmi env.cmi
types.cmi : set.cmi primitive.cmi path.cmi parsetree.cmi map.cmi \
longident.cmi location.cmi ident.cmi asttypes.cmi
typetexp.cmi : types.cmi typedtree.cmi path.cmi parsetree.cmi longident.cmi \
location.cmi format.cmi env.cmi asttypes.cmi
location.cmi includemod.cmi format.cmi env.cmi asttypes.cmi
uchar.cmi :
unix.cmi : camlinternalBigarray.cmi
unixLabels.cmi : unix.cmi
unixLabels.cmi : unix.cmi camlinternalBigarray.cmi
untypeast.cmi : typedtree.cmi path.cmi parsetree.cmi longident.cmi \
location.cmi asttypes.cmi
warnings.cmi : lexing.cmi
warnings.cmi : lexing.cmi lazy.cmi
weak.cmi : hashtbl.cmi

View File

@ -1,4 +1,4 @@
TOPDIR=$(abspath ../..)
TOPDIR=../..
include $(TOPDIR)/Makefile.tools
.SUFFIXES:

View File

@ -1,3 +1,17 @@
#**************************************************************************
#* *
#* OCaml *
#* *
#* Jeremie Dimino, Jane Street Europe *
#* *
#* Copyright 2017 Jane Street Group LLC *
#* *
#* All rights reserved. This file is distributed under the terms of *
#* the GNU Lesser General Public License version 2.1, with the *
#* special exception on linking described in the file LICENSE. *
#* *
#**************************************************************************
# This script extract the Pervasives submodule from stdlib.mli into
# pervasives.mli, for ocamldoc
BEGIN { state=0 }

View File

@ -23,13 +23,15 @@ marshal.cmx :
mutex.cmo : thread.cmi mutex.cmi
mutex.cmx : thread.cmx mutex.cmi
mutex.cmi :
pervasives.cmo : unix.cmo
pervasives.cmx : unix.cmx
thread.cmo : unix.cmo thread.cmi
stdlib.cmo : unix.cmi marshal.cmo stdlib.cmi
stdlib.cmx : unix.cmx marshal.cmx stdlib.cmi
stdlib.cmi : marshal.cmo
thread.cmo : unix.cmi thread.cmi
thread.cmx : unix.cmx thread.cmi
thread.cmi : unix.cmo
threadUnix.cmo : unix.cmo thread.cmi threadUnix.cmi
thread.cmi : unix.cmi
threadUnix.cmo : unix.cmi thread.cmi threadUnix.cmi
threadUnix.cmx : unix.cmx thread.cmx threadUnix.cmi
threadUnix.cmi : unix.cmo
unix.cmo :
unix.cmx :
threadUnix.cmi : unix.cmi
unix.cmo : unix.cmi
unix.cmx : unix.cmi
unix.cmi :

View File

@ -75,12 +75,13 @@ unix.cma: $(UNIXLIB_OBJS)
stdlib.cmo: stdlib.mli stdlib.cmi stdlib.ml
$(CAMLC) ${COMPFLAGS} -nopervasives \
-pp "awk -f $(LIB)/expand_module_aliases.awk" -o $@ -c stdlib.ml
-pp "$(AWK) -f $(LIB)/expand_module_aliases.awk" -o $@ -c stdlib.ml
stdlib.mli: $(LIB)/stdlib.mli
ln -s $(LIB)/stdlib.mli stdlib.mli
stdlib.cmi: $(LIB)/stdlib.cmi
rm -f stdlib.cmi
ln -s $(LIB)/stdlib.cmi stdlib.cmi
$(P)marshal.cmo: marshal.mli $(P)marshal.cmi marshal.ml

View File

@ -201,15 +201,6 @@ stdlib.p.cmxa: $(OBJS:.cmo=.p.cmx)
sys.ml: sys.mlp ../VERSION
sed -e "s|%%VERSION%%|`sed -e 1q ../VERSION | tr -d '\r'`|" sys.mlp > $@
# The user write stdlib.ml, but we don't use it as it to build
# stdlib.cmo. First we do the following rewriting via an awk
# preprocessor:
#
# [module FooBar = FooBar] --> [module FooBar = Stdlib__fooBar]
#
# This way the "Stdlib__" names stay hidden to the user and are just
# used as a compilation strategy.
.PHONY: clean
clean::
rm -f sys.ml

View File

@ -1,3 +1,17 @@
#**************************************************************************
#* *
#* OCaml *
#* *
#* Jeremie Dimino, Jane Street Europe *
#* *
#* Copyright 2017 Jane Street Group LLC *
#* *
#* All rights reserved. This file is distributed under the terms of *
#* the GNU Lesser General Public License version 2.1, with the *
#* special exception on linking described in the file LICENSE. *
#* *
#**************************************************************************
# This script adds the Stdlib__ prefixes to the module aliases in
# stdlib.ml and stdlib.mli
BEGIN { state=0 }

View File

@ -1,3 +1,17 @@
#**************************************************************************
#* *
#* OCaml *
#* *
#* Jeremie Dimino, Jane Street Europe *
#* *
#* Copyright 2017 Jane Street Group LLC *
#* *
#* All rights reserved. This file is distributed under the terms of *
#* the GNU Lesser General Public License version 2.1, with the *
#* special exception on linking described in the file LICENSE. *
#* *
#**************************************************************************
# This script remove the module aliases from stdlib.ml and stdlib.mli
# so that ocamldep doesn't register dependencies from stdlib to all
# other modules

View File

@ -21,13 +21,13 @@
*)
module Pervasives : sig
(** Pervasives operations.
(** Pervasive operations.
This module provides the basic operations over the built-in types
(numbers, booleans, byte sequences, strings, exceptions, references,
lists, arrays, input-output channels, ...).
This module is included in the toplevel {!Stdlib} module.
This module is included in the toplevel [Stdlib] module.
*)

View File

@ -16,9 +16,9 @@
<pre><span id="MODULEModule_whitespace"><span class="keyword">module</span> Module_whitespace</span>: <code class="code"><span class="keyword">sig</span></code> <a href="Module_whitespace.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><hr width="100%">
<pre><span id="MODULEM"><span class="keyword">module</span> <a href="Module_whitespace.M.html">M</a></span>: <code class="type">Set.Make</code><code class="code">(</code><code class="code"><span class="keyword">sig</span></code></pre><div class="sig_block">
<pre><span id="MODULEM"><span class="keyword">module</span> <a href="Module_whitespace.M.html">M</a></span>: <code class="type">Stdlib.Set.Make</code><code class="code">(</code><code class="code"><span class="keyword">sig</span></code></pre><div class="sig_block">
<pre><span id="TYPEt"><span class="keyword">type</span> <code class="type"></code>t</span> = <code class="type">int</code> </pre>
<pre><span id="VALcompare"><span class="keyword">val</span> compare</span> : <code class="type">'a -> 'a -> int</code></pre></div>
<pre><code class="code"><span class="keyword">end</span></code><code class="code">)</code></pre></body></html>
<pre><code class="code"><span class="keyword">end</span></code><code class="code">)</code></pre></body></html>

View File

@ -4,7 +4,7 @@ CRC of implementation: <MD5>
Globals defined:
Question
Interfaces imported:
<MD5> Stdlib
<MD5> Question
<MD5> Pervasives
<MD5> CamlinternalFormatBasics
Implementations imported:

View File

@ -72,6 +72,60 @@ let non_shadowed_pervasive = function
with Not_found -> true)
| _ -> false
let find_double_underscore s =
let len = String.length s in
let rec loop i =
if i + 1 >= len then
None
else if s.[i] = '_' && s.[i + 1] = '_' then
Some i
else
loop (i + 1)
in
loop 0
let rec module_path_is_an_alias_of env path ~alias_of =
match Env.find_module path env with
| { md_type = Mty_alias (_, path'); _ } ->
Path.same path' alias_of ||
module_path_is_an_alias_of env path' ~alias_of
| _ -> false
| exception Not_found -> false
(* Simple heuristic to print Foo__bar.* as Foo.Bar.* when Foo.Bar is an alias
for Foo__bar. This pattern is used by the stdlib. *)
let rec rewrite_double_underscore_paths env p =
match p with
| Pdot (p, s, n) ->
Pdot (rewrite_double_underscore_paths env p, s, n)
| Papply (a, b) ->
Papply (rewrite_double_underscore_paths env a,
rewrite_double_underscore_paths env b)
| Pident id ->
let name = Ident.name id in
match find_double_underscore name with
| None -> p
| Some i ->
let better_lid =
Ldot
(Lident (String.sub name 0 i),
String.capitalize_ascii
(String.sub name (i + 2) (String.length name - i - 2)))
in
match Env.lookup_module ~load:true better_lid env with
| exception Not_found -> p
| p' ->
if module_path_is_an_alias_of env p' ~alias_of:p then
p'
else
p
let rewrite_double_underscore_paths env p =
if env == Env.empty then
p
else
rewrite_double_underscore_paths env p
let rec tree_of_path = function
| Pident id ->
Oide_ident (ident_name id)
@ -81,7 +135,8 @@ let rec tree_of_path = function
| Pdot(p, s, _pos) ->
Oide_dot (tree_of_path p, s)
| Papply(p1, p2) ->
Oide_apply (tree_of_path p1, tree_of_path p2)
Oide_apply (tree_of_path p1,
tree_of_path p2)
let rec path ppf = function
| Pident id ->
@ -96,6 +151,11 @@ let rec path ppf = function
| Papply(p1, p2) ->
fprintf ppf "%a(%a)" path p1 path p2
let tree_of_path p =
tree_of_path (rewrite_double_underscore_paths !printing_env p)
let path ppf p =
path ppf (rewrite_double_underscore_paths !printing_env p)
let rec string_of_out_ident = function
| Oide_ident s -> s
| Oide_dot (id, s) -> String.concat "." [string_of_out_ident id; s]
@ -305,18 +365,6 @@ let rec normalize_type_path ?(cache=false) env p =
Not_found ->
(Env.normalize_path None env p, Id)
let find_double_underscore s =
let len = String.length s in
let rec loop i =
if i + 1 >= len then
None
else if s.[i] = '_' && s.[i + 1] = '_' then
Some i
else
loop (i + 1)
in
loop 0
let penalty s =
if s <> "" && s.[0] = '_' then
10
@ -406,46 +454,11 @@ let rec get_best_path r =
l;
get_best_path r
let rec module_path_is_an_alias_of env path ~alias_of =
match Env.find_module path env with
| { md_type = Mty_alias (_, path'); _ } ->
Path.same path' alias_of ||
module_path_is_an_alias_of env path' ~alias_of
| _ -> false
| exception Not_found -> false
(* Simple heuristic to print Foo__bar.* as Foo.Bar.* when Foo.Bar is an alias
for Foo__bar. This pattern is used by the stdlib. *)
let rec rewrite_double_underscore_paths env p =
match p with
| Pdot (p, s, n) -> Pdot (rewrite_double_underscore_paths env p, s, n)
| Papply (a, b) ->
Papply (rewrite_double_underscore_paths env a,
rewrite_double_underscore_paths env b)
| Pident id ->
let name = Ident.name id in
match find_double_underscore name with
| None -> p
| Some i ->
let better_lid =
Ldot
(Lident (String.sub name 0 i),
String.capitalize_ascii
(String.sub name (i + 2) (String.length name - i - 2)))
in
match Env.lookup_module ~load:true better_lid env with
| exception Not_found -> p
| p' ->
if module_path_is_an_alias_of env p' ~alias_of:p then
p'
else
p
let best_type_path p =
if !printing_env == Env.empty
then (p, Id)
else if !Clflags.real_paths
then (rewrite_double_underscore_paths !printing_env p, Id)
then (p, Id)
else
let (p', s) = normalize_type_path !printing_env p in
let get_path () = get_best_path (PathMap.find p' !printing_map) in
@ -457,7 +470,7 @@ let best_type_path p =
done;
let p'' = try get_path () with Not_found -> p' in
(* Format.eprintf "%a = %a -> %a@." path p path p' path p''; *)
(rewrite_double_underscore_paths !printing_env p'', s)
(p'', s)
(* Print a type expression *)
@ -1728,6 +1741,3 @@ let report_ambiguous_type_error ppf env (tp0, tp0') tpl txt1 txt2 txt3 =
@]"
txt2 type_path_list tpl
txt3 (type_path_expansion tp0) tp0')
let tree_of_path p = tree_of_path (rewrite_double_underscore_paths !printing_env p)
let path ppf p = path ppf (rewrite_double_underscore_paths !printing_env p)