summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--.depend8
-rw-r--r--Changes135
-rw-r--r--VERSION2
-rw-r--r--driver/compenv.ml1
-rw-r--r--driver/main.ml1
-rw-r--r--driver/main_args.ml14
-rw-r--r--driver/main_args.mli1
-rw-r--r--driver/optmain.ml1
-rw-r--r--ocamlbuild/log.ml23
-rw-r--r--ocamlbuild/log.mli11
-rw-r--r--ocamlbuild/ocaml_compiler.ml39
-rw-r--r--ocamlbuild/ocaml_specific.ml28
-rw-r--r--ocamlbuild/testsuite/internal.ml22
-rw-r--r--otherlibs/bigarray/bigarray_stubs.c6
-rw-r--r--stdlib/camlinternalFormat.ml32
-rw-r--r--stdlib/camlinternalFormat.mli6
-rw-r--r--stdlib/obj.ml5
-rw-r--r--stdlib/obj.mli1
-rw-r--r--tools/ocamlcp.ml1
-rw-r--r--tools/ocamloptp.ml1
-rw-r--r--toplevel/opttopmain.ml1
-rw-r--r--toplevel/topmain.ml1
-rw-r--r--typing/envaux.ml2
-rw-r--r--typing/typecore.ml3
-rw-r--r--utils/clflags.ml1
-rw-r--r--utils/clflags.mli1
26 files changed, 225 insertions, 122 deletions
diff --git a/.depend b/.depend
index 1e9f2259c..9b6b9ffb6 100644
--- a/.depend
+++ b/.depend
@@ -189,11 +189,11 @@ typing/env.cmx : utils/warnings.cmx typing/types.cmx utils/tbl.cmx \
typing/cmi_format.cmx utils/clflags.cmx typing/btype.cmx \
parsing/asttypes.cmi typing/env.cmi
typing/envaux.cmo : typing/types.cmi typing/subst.cmi typing/printtyp.cmi \
- typing/path.cmi typing/mtype.cmi utils/misc.cmi typing/ident.cmi \
- typing/env.cmi parsing/asttypes.cmi typing/envaux.cmi
+ typing/path.cmi utils/misc.cmi typing/ident.cmi typing/env.cmi \
+ parsing/asttypes.cmi typing/envaux.cmi
typing/envaux.cmx : typing/types.cmx typing/subst.cmx typing/printtyp.cmx \
- typing/path.cmx typing/mtype.cmx utils/misc.cmx typing/ident.cmx \
- typing/env.cmx parsing/asttypes.cmi typing/envaux.cmi
+ typing/path.cmx utils/misc.cmx typing/ident.cmx typing/env.cmx \
+ parsing/asttypes.cmi typing/envaux.cmi
typing/ident.cmo : typing/ident.cmi
typing/ident.cmx : typing/ident.cmi
typing/includeclass.cmo : typing/types.cmi typing/printtyp.cmi \
diff --git a/Changes b/Changes
index 082231281..c37c8b03c 100644
--- a/Changes
+++ b/Changes
@@ -18,7 +18,7 @@ Ocaml 4.02.0:
Language features:
- Attributes and extension nodes
(Alain Frisch)
-- PR#5095: Generative functors
+- Generative functors (PR#5905)
(Jacques Garrigue)
- Module aliases
(Jacques Garrigue)
@@ -53,7 +53,7 @@ Type system:
* Module aliases are now typed in a specific way, which remembers their
identity. In particular this changes the signature inferred by
"module type of"
- (Jacques Garrigue)
+ (Jacques Garrigue, feedback from Leo White, Mark Shinwell and Nick Chapman)
- PR#6331: Slight change in the criterion to distinguish private
abbreviations and private row types: create a private abbreviation for
closed objects and fixed polymorphic variants.
@@ -82,29 +82,26 @@ Compilers:
- PR#6042: Optimization of integer division and modulus by constant divisors
(Xavier Leroy and Phil Denys)
- Add "-open" command line flag for opening a single module before typing
+ (Leo White, Mark Shinwell and Nick Chapman)
* "-o" now sets module name to the output file name up to the first "."
(it also applies when "-o" is not given, i.e. the module name is then
the input file name up to the first ".")
- (Leo White and Mark Shinwell)
+ (Leo White, Mark Shinwell and Nick Chapman)
* PR#5779: better sharing of structured constants
(Alain Frisch)
-- PR#6182: better message for virtual objects and class types
- (Leo P. White, Stephen Dolan)
- PR#5817: new flag to keep locations in cmi files
(Alain Frisch)
- PR#5854: issue warning 3 when referring to a value marked with
the [@@ocaml.deprecated] attribute
(Alain Frisch, suggestion by Pierre-Marie Pédrot)
+- PR#6017: a new format implementation based on GADTs
+ (Benoît Vaugon and Gabriel Scherer)
* PR#6203: Constant exception constructors no longer allocate
(Alain Frisch)
-- PR#6311: Improve signature mismatch error messages
- (Alain Frisch, suggestion by Daniel Bünzli)
+- PR#6260: avoid unnecessary boxing in let
+ (Vladimir Brankov)
- PR#6345: Better compilation of optional arguments with default values
(Alain Frisch, review by Jacques Garrigue)
-- PR#6260: Unnecessary boxing in let
- (Vladimir Brankov)
-- PR#6017: a new format implementation based on GADTs
- (Benoît Vaugon and Gabriel Scherer)
- PR#6389: ocamlopt -opaque option for incremental native compilation
(Pierre Chambart, Gabriel Scherer)
@@ -128,7 +125,7 @@ Runtime system:
- Fixed a major performance problem on large heaps (~1GB) by making heap
increments proportional to heap size by default
(Damien Doligez)
-- PR#4765: Structural equality should treat exception specifically
+- PR#4765: Structural equality treats exception specifically
(Alain Frisch)
- PR#5009: efficient comparison/indexing of exceptions
(Alain Frisch, request by Markus Mottl)
@@ -141,10 +138,8 @@ Runtime system:
(Xavier Leroy)
Standard library:
-* Add new modules: Bytes and BytesLabels.
+* Add new modules Bytes and BytesLabels for mutable byte sequences.
(Damien Doligez)
-- PR#6355: Improve documentation regarding finalisers and multithreading
- (Daniel Bünzli, Mark Shinwell)
- PR#4986: add List.sort_uniq and Set.of_list
(Alain Frisch)
- PR#5935: a faster version of "raise" which does not maintain the backtrace
@@ -155,7 +150,9 @@ Standard library:
(John Whitington)
- PR#6180: efficient creation of uninitialized float arrays
(Alain Frisch, request by Markus Mottl)
-- Trigger warning 3 for all values marked as deprected in the documentation.
+- PR#6355: Improve documentation regarding finalisers and multithreading
+ (Daniel Bünzli, Mark Shinwell)
+- Trigger warning 3 for all values marked as deprecated in the documentation.
(Damien Doligez)
OCamldoc:
@@ -170,53 +167,30 @@ OCamldoc:
(Maxence Guesdon, report by Anil Madhavapeddy)
Bug fixes:
-- PR#6507: crash on AArch64 resulting from incorrect setting of
- [caml_bottom_of_stack]. (Richard Jones, Mark Shinwell)
- PR#2719: wrong scheduling of bound checks within a
try...with Invalid_argument -> _ ... (Xavier Leroy)
-- PR#4771: Clarify documentation of Dynlink.allow_only
- (Damien Doligez, report by David Allsopp)
-- PR#6232: Don't use [mktemp] on platforms where [mkstemp] is available
- (Stéphane Glondu, Mark Shinwell)
-- PR#6439: Don't use the deprecated [getpagesize] function
- (John Whitington, Mark Shinwell)
- PR#4719: Sys.executable_name wrong if executable name contains dots (Windows)
(Alain Frisch, report by Bart Jacobs)
-- PR#4855: 'camlp4 -I +dir' accepted, dir is relative to 'camlp4 -where'
- (Jun Furuse and Hongbo Zhang, report by Dmitry Grebeniuk)
-- PR#5201: ocamlbuild: add --norc to the bash invocation to help performances
- (user 'daweil')
- PR#5406 ocamlbuild: "tag 'package' does not expect a parameter"
(Gabriel Scherer)
-- PR#5598: follow-up fix related to PR#6165
- (Damien Doligez)
+- PR#5598, PR#6165: Alterations to handling of \013 in source files
+ breaking other tools
+ (David Allsopp and Damien Doligez)
- PR#5820: Fix camlp4 lexer roll back problem
(Hongbo Zhang)
-- PR#5851: warn when -r is disabled because no _tags file is present
- (Gabriel Scherer)
- PR#5946: CAMLprim taking (void) as argument
(Benoît Vaugon)
- PR#6038: on x86-32, enforce 16-byte stack alignment for compatibility
with recent GCC and Clang. Win32/MSVC keeps 4-byte stack alignment.
(Xavier Leroy)
-- PR#6062: Fix a regression bug caused by commit 13047
+- PR#6062: Fix a 4.01 camlp4 DELETE_RULE regression caused by commit 13047
(Hongbo Zhang, report by Christophe Troestler)
-- PR#6109: Typos in ocamlbuild error messages
- (Gabriel Kerneis)
-- PR#6116: more efficient implementation of Digest.to_hex
- (ygrek)
-- PR#6142: add cmt file support to ocamlobjinfo
- (Anil Madhavapeddy)
-- PR#6165: Alterations to handling of \013 in source files breaking other tools
- (David Allsopp)
- PR#6173: Typing error message is worse than before
(Jacques Garrigue and John Whitington)
- PR#6174: OCaml compiler loops on an example using GADTs (-rectypes case)
(Jacques Garrigue and Grégoire Henry, report by Chantal Keller)
-- PR#6175: add open! support to camlp4
+- PR#6175: open! was not suppored by camlp4
(Hongbo Zhang)
-- PR#6183: enhanced documentation for 'Unix.shutdown_connection'
- (Anil Madhavapeddy, report by Jun Furuse)
- PR#6184: ocamlbuild: `ocamlfind ocamldep` does not support -predicate
(Jacques-Pascal Deplaix)
- PR#6194: Incorrect unused warning with first-class modules in patterns
@@ -226,6 +200,8 @@ Bug fixes:
(Xavier Leroy)
- PR#6216: inlining of GADT matches generates invalid assembly
(Xavier Leroy and Alain Frisch, report by Mark Shinwell)
+- PR#6232: Don't use [mktemp] on platforms where [mkstemp] is available
+ (Stéphane Glondu, Mark Shinwell)
- PR#6233: out-of-bounds exceptions lose their locations on ARM, PowerPC
(Jacques-Henri Jourdan and Xavier Leroy,
report and testing by Stéphane Glondu)
@@ -242,8 +218,6 @@ Bug fixes:
(Xavier Leroy, report by Pierre-Marie Pédrot)
- PR#6262: equality of first-class modules take module aliases into account
(Alain Frisch and Leo White)
-- PR#6267: more information printed by "bt" command of ocamldebug
- (Josh Watzman)
- PR#6268: -DMODEL_$(MODEL) not passed when building asmrun/arm.p.o
(Peter Michael Green)
- PR#6273: fix Sys.file_exists on large files (Win32)
@@ -280,31 +254,43 @@ Bug fixes:
(Jacques Garrigue, report by Gabriel Scherer and Benoît Vaugon)
- PR#6408: Optional arguments given as ~?arg instead of ?arg in message
(Michael O'Connor)
-- PR#6418: reimplement parametrized Format tags/indentation with GADTs
- (Benoît Vaugon)
+- PR#6411: missing libgcc_s_sjlj-1.dll in mingw (add -static-libgcc)
+ (Jun Furuse and Alain Frisch, Jonathan Protzenko and Adrien Nader)
- PR#6436: Typos in @deprecated text in stdlib/arrayLabels.mli
(John Whitington)
+- PR#6439: Don't use the deprecated [getpagesize] function
+ (John Whitington, Mark Shinwell)
+- PR#6441: undetected tail-call in some mutually-recursive functions
+ (many arguments, and mutual block mixes functions and non-functions)
+ (Stefan Holdermans, review by Xavier Leroy)
- PR#6443: ocaml segfault when List.fold_left is traced then executed
- (Jacques Garrigue, report by Reventlov)
+ (Jacques Garrigue, report by user 'Reventlov')
+- PR#6451: some bugs in untypeast.ml
+ (Jun Furuse, review by Alain Frisch)
- PR#6460: runtime assertion failure with large [| e1;...eN |]
float array expressions
(Leo White)
+- PR#6463: -dtypedtree fails on class fields
+ (Leo White)
+- PR#6469: invalid -dsource printing of "external _pipe = ...", "Pervasives.(!)"
+ (Gabriel Scherer and Damien Doligez, user 'ngunn')
- PR#6482: ocamlbuild fails when _tags file in unhygienic directory
(Gabriel Scherer)
+- PR#6502: ocamlbuild spurious warning on "use_menhir" tag
+ (Xavier Leroy)
- PR#6505: Missed Type-error leads to a segfault upon record access
- (Jacques Garrigue, report by Christoph Höger)
+ (Jacques Garrigue, Jeremy Yallop, report by Christoph Höger)
+- PR#6507: crash on AArch64 resulting from incorrect setting of
+ [caml_bottom_of_stack]. (Richard Jones, Mark Shinwell)
- PR#6509: add -linkall flag to ocamlcommon.cma
(Frédéric Bour)
- PR#6513: Fatal error Ctype.Unify(_) in functor type
- (Jacques Garrigue, report by Dario Teixeira)
-- fix -dsource printing of "external _pipe = ..."
- (Gabriel Scherer)
+- PR#6523: failure upon character bigarray access, and unnecessary change
+ in comparison ordering (Jeremy Yallop, Mark Shinwell)
- bound-checking bug in caml_string_{get,set}{16,32,64}
(Pierre Chambart and Gabriel Scherer, report by Nicolas Trangez)
- sometimes wrong stack alignment at out-of-bounds array access
(Gabriel Scherer and Xavier Leroy, report by Pierre Chambart)
-- make ocamldebug -I auto-detection work with ocamlbuild
- (Josh Watzman)
Features wishes:
- PR#4243: make the Makefiles parallelizable
@@ -312,10 +298,18 @@ Features wishes:
- PR#4323: have "of_string" in Num and Big_int work with binary and
hex representations
(Zoe Paraskevopoulou, review by Gabriel Scherer)
+- PR#4771: Clarify documentation of Dynlink.allow_only
+ (Damien Doligez, report by David Allsopp)
+- PR#4855: 'camlp4 -I +dir' accepted, dir is relative to 'camlp4 -where'
+ (Jun Furuse and Hongbo Zhang, report by Dmitry Grebeniuk)
+- PR#5201: ocamlbuild: add --norc to the bash invocation to help performances
+ (user 'daweil')
- PR#5650: Camlp4FoldGenerator doesn't handle well "abstract" types
(Hongbo Zhang)
- PR#5808: allow simple patterns, not just identifiers, in "let p : t = ..."
(Alain Frisch)
+- PR#5851: warn when -r is disabled because no _tags file is present
+ (Gabriel Scherer)
- PR#5899: a programmer-friendly access to backtrace information
(Jacques-Henri Jourdan and Gabriel Scherer)
- PR#6000 comment 9644: add a warning for non-principal coercions to format
@@ -328,25 +322,46 @@ Features wishes:
(David Sheets)
- PR#6087: ocamlbuild, improve _tags parsing of escaped newlines
(Gabriel Scherer, request by Daniel Bünzli)
+- PR#6109: Typos in ocamlbuild error messages
+ (Gabriel Kerneis)
+- PR#6116: more efficient implementation of Digest.to_hex
+ (ygrek)
+- PR#6142: add cmt file support to ocamlobjinfo
+ (Anil Madhavapeddy)
- PR#6166: document -ocamldoc option of ocamlbuild
(Xavier Clerc)
+- PR#6182: better message for virtual objects and class types
+ (Leo White, Stephen Dolan)
+- PR#6183: enhanced documentation for 'Unix.shutdown_connection'
+ (Anil Madhavapeddy, report by Jun Furuse)
- PR#6187: ocamlbuild: warn when using -plugin-tag(s) without myocamlbuild.ml
(Jacques-Pascal Deplaix)
-- PR#6246: allow wilcard _ as for-loop index
+- PR#6246: allow wildcard _ as for-loop index
(Alain Frisch, request by ygrek)
+- PR#6267: more information printed by "bt" command of ocamldebug
+ (Josh Watzman)
- PR#6270: remove need for -I directives to ocamldebug in common case
(Josh Watzman, review by Xavier Clerc and Alain Frisch)
+- PR#6311: Improve signature mismatch error messages
+ (Alain Frisch, suggestion by Daniel Bünzli)
- PR#6358: obey DESTDIR in install targets
(Gabriel Scherer, request by François Berenger)
+- PR#6388, PR#6424: more parsetree correctness checks for -ppx users
+ (Alain Frisch, request by Peter Zotov and Jun Furuse)
- PR#6406: Expose OCaml version in C headers
(Peter Zotov and Romain Calascibetta)
-- PR#5899: a programmer-friendly access to backtrace information
- (Jacques-Henri Jourdan and Gabriel Scherer)
+- PR#6446: improve "unused declaration" warnings wrt. name shadowing
+ (Alain Frisch)
+- PR#6495: ocamlbuild tags 'safe_string', 'unsafe_string'
+ (Anil Madhavapeddy)
+- PR#6497: pass context information to -ppx preprocessors
+ (Peter Zotov, Alain Frisch)
- ocamllex: user-definable refill action
(Frédéric Bour, review by Gabriel Scherer and Luc Maranget)
- shorten syntax for functor signatures: "functor (M1:S1) (M2:S2) .. -> .."
(Thomas Gazagnaire and Jeremy Yallop, review by Gabriel Scherer)
-
+- make ocamldebug -I auto-detection work with ocamlbuild
+ (Josh Watzman)
OCaml 4.01.0:
-------------
@@ -767,8 +782,6 @@ Feature wishes:
(Anil Madhavapeddy)
- PR#6060: ocamlbuild tags 'principal', 'strict_sequence' and 'short_paths'
(Anil Madhavapeddy)
-- PR#6495: ocamlbuild tags 'safe_string', 'unsafe_string'
- (Anil Madhavapeddy)
- ocamlbuild tag 'no_alias_deps'
(Daniel Bünzli)
diff --git a/VERSION b/VERSION
index 85ca9e823..a61a34c25 100644
--- a/VERSION
+++ b/VERSION
@@ -1,4 +1,4 @@
-4.03.0+dev2-2014-08-22
+4.03.0+dev3-2014-08-29
# The version string is the first line of this file.
# It must be in the format described in stdlib/sys.mli
diff --git a/driver/compenv.ml b/driver/compenv.ml
index 32ecb937e..82704fd8f 100644
--- a/driver/compenv.ml
+++ b/driver/compenv.ml
@@ -169,6 +169,7 @@ let read_OCAMLPARAM ppf position =
| "rectypes" -> set "rectypes" [ recursive_types ] v
| "safe-string" -> clear "safe-string" [ unsafe_string ] v
| "strict-sequence" -> set "strict-sequence" [ strict_sequence ] v
+ | "strict-formats" -> set "strict-formats" [ strict_formats ] v
| "thread" -> set "thread" [ use_threads ] v
| "unsafe" -> set "unsafe" [ fast ] v
| "verbose" -> set "verbose" [ verbose ] v
diff --git a/driver/main.ml b/driver/main.ml
index 4b1c7264a..f8358a0cb 100644
--- a/driver/main.ml
+++ b/driver/main.ml
@@ -115,6 +115,7 @@ module Options = Main_args.Make_bytecomp_options (struct
let _safe_string = unset unsafe_string
let _short_paths = unset real_paths
let _strict_sequence = set strict_sequence
+ let _strict_formats = set strict_formats
let _thread = set use_threads
let _vmthread = set use_vmthreads
let _unsafe = set fast
diff --git a/driver/main_args.ml b/driver/main_args.ml
index 9d66e2b86..4f9668c75 100644
--- a/driver/main_args.ml
+++ b/driver/main_args.ml
@@ -453,6 +453,15 @@ let mk_opaque f =
\ (reduces necessary recompilation on module change)"
;;
+let mk_strict_formats f =
+ "-strict-formats", Arg.Unit f,
+ " Reject invalid formats accepted by legacy implementations\n\
+ \ (Warning: Invalid formats may behave differently from\n\
+ \ previous OCaml versions, and will become always-rejected\n\
+ \ in future OCaml versions. You should use this flag\n\
+ \ to detect and fix invalid formats.)"
+;;
+
let mk__ f =
"-", Arg.String f,
"<file> Treat <file> as a file name (even if it starts with `-')"
@@ -474,6 +483,7 @@ module type Common_options = sig
val _safe_string : unit -> unit
val _short_paths : unit -> unit
val _strict_sequence : unit -> unit
+ val _strict_formats : unit -> unit
val _unsafe : unit -> unit
val _unsafe_string : unit -> unit
val _version : unit -> unit
@@ -651,6 +661,7 @@ struct
mk_safe_string F._safe_string;
mk_short_paths F._short_paths;
mk_strict_sequence F._strict_sequence;
+ mk_strict_formats F._strict_formats;
mk_thread F._thread;
mk_unsafe F._unsafe;
mk_unsafe_string F._unsafe_string;
@@ -701,6 +712,7 @@ struct
mk_short_paths F._short_paths;
mk_stdin F._stdin;
mk_strict_sequence F._strict_sequence;
+ mk_strict_formats F._strict_formats;
mk_unsafe F._unsafe;
mk_unsafe_string F._unsafe_string;
mk_version F._version;
@@ -767,6 +779,7 @@ struct
mk_shared F._shared;
mk_short_paths F._short_paths;
mk_strict_sequence F._strict_sequence;
+ mk_strict_formats F._strict_formats;
mk_thread F._thread;
mk_unsafe F._unsafe;
mk_unsafe_string F._unsafe_string;
@@ -830,6 +843,7 @@ module Make_opttop_options (F : Opttop_options) = struct
mk_short_paths F._short_paths;
mk_stdin F._stdin;
mk_strict_sequence F._strict_sequence;
+ mk_strict_formats F._strict_formats;
mk_unsafe F._unsafe;
mk_unsafe_string F._unsafe_string;
mk_version F._version;
diff --git a/driver/main_args.mli b/driver/main_args.mli
index 9a69c799e..95b7c69e3 100644
--- a/driver/main_args.mli
+++ b/driver/main_args.mli
@@ -26,6 +26,7 @@ module type Common_options = sig
val _safe_string : unit -> unit
val _short_paths : unit -> unit
val _strict_sequence : unit -> unit
+ val _strict_formats : unit -> unit
val _unsafe : unit -> unit
val _unsafe_string : unit -> unit
val _version : unit -> unit
diff --git a/driver/optmain.ml b/driver/optmain.ml
index cd36e7bd7..947d43073 100644
--- a/driver/optmain.ml
+++ b/driver/optmain.ml
@@ -114,6 +114,7 @@ module Options = Main_args.Make_optcomp_options (struct
let _safe_string = clear unsafe_string
let _short_paths = clear real_paths
let _strict_sequence = set strict_sequence
+ let _strict_formats = set strict_formats
let _shared () = shared := true; dlcode := true
let _S = set keep_asm_file
let _thread = set use_threads
diff --git a/ocamlbuild/log.ml b/ocamlbuild/log.ml
index 6e3ac1501..d50969e34 100644
--- a/ocamlbuild/log.ml
+++ b/ocamlbuild/log.ml
@@ -49,19 +49,30 @@ let event ?pretend x = Display.event !-internal_display ?pretend x
let display x = Display.display !-internal_display x
let do_at_end = Queue.create ()
+let already_asked = Hashtbl.create 10
-let at_end_always thunk = Queue.add thunk do_at_end
-let at_end thunk = at_end_always (function
+let at_end_always ~name thunk =
+ if not (Hashtbl.mem already_asked name) then begin
+ Hashtbl.add already_asked name ();
+ Queue.add thunk do_at_end;
+ end
+
+let at_end ~name thunk = at_end_always ~name (function
| `Quiet -> ()
| `Success | `Error -> thunk `Error)
-let at_failure thunk = at_end_always (function
+let at_failure ~name thunk = at_end_always ~name (function
| `Success | `Quiet -> ()
| `Error -> thunk `Error)
let finish ?how () =
- Queue.iter (fun thunk ->
- thunk (match how with None -> `Quiet | Some how -> how)
- ) do_at_end;
+ while not (Queue.is_empty do_at_end) do
+ let actions = Queue.copy do_at_end in
+ Queue.clear do_at_end;
+ (* calling a thunk may add new actions again, hence the loop *)
+ Queue.iter (fun thunk ->
+ thunk (match how with None -> `Quiet | Some how -> how)
+ ) actions;
+ done;
match !internal_display with
| None -> ()
| Some d -> Display.finish ?how d
diff --git a/ocamlbuild/log.mli b/ocamlbuild/log.mli
index f174a1979..413a476dd 100644
--- a/ocamlbuild/log.mli
+++ b/ocamlbuild/log.mli
@@ -34,6 +34,11 @@ val update : unit -> unit
val mode : string -> bool
(** Wrap logging event so that only fire at the end of the compilation
- process, possibly depending on the termination status. *)
-val at_end : ([> `Error | `Quiet ] -> unit) -> unit
-val at_failure : ([> `Error ] -> unit) -> unit
+ process, possibly depending on the termination status.
+
+ The name is used to avoid printing the same hint/warning twice,
+ even if [at_end] is called several times. Use different names for
+ distinct events.
+*)
+val at_end : name:string -> ([> `Error | `Quiet ] -> unit) -> unit
+val at_failure : name:string -> ([> `Error ] -> unit) -> unit
diff --git a/ocamlbuild/ocaml_compiler.ml b/ocamlbuild/ocaml_compiler.ml
index 99186ad37..c270a7f63 100644
--- a/ocamlbuild/ocaml_compiler.ml
+++ b/ocamlbuild/ocaml_compiler.ml
@@ -116,25 +116,30 @@ let prepare_compile build ml =
match mandatory, res with
| _, Good _ -> ()
| `mandatory, Bad exn ->
- if not !Options.ignore_auto then raise exn
- else dprintf 3
+ if not !Options.ignore_auto then raise exn;
+ dprintf 3
"Warning: Failed to build the module %s requested by ocamldep."
name;
- Log.at_failure (fun `Error ->
- eprintf "Hint:@ Recursive@ traversal@ of@ subdirectories@ \
- was@ not@ enabled@ for@ this@ build,@ as@ the@ working@ \
- directory does@ not@ look@ like@ an@ ocamlbuild@ project@ \
- (no@ '_tags'@ or@ 'myocamlbuild.ml'@ file).@ \
- If@ you@ have@ modules@ in@ subdirectories,@ you@ should@ add@ \
- the@ option@ \"-r\"@ or@ create@ an@ empty@ '_tags'@ file.@\n\
- @\n\
- To@ enable@ recursive@ traversal@ for@ some@ subdirectories@ \
- only,@ you@ can@ use@ the@ following@ '_tags'@ file:@\n\
- @[<v 4>@,\
- true: -traverse@,\
- <dir1> or <dir2>: traverse@,\
- @]"
- );
+ if not (!Options.recursive || Options.ocamlbuild_project_heuristic ())
+ then Log.at_failure ~name:"a module failed to build,
+ while recursive traversal was disabled by fragile heuristic;
+ hint that having a _tags or myocamlbuild.ml would maybe solve
+ the build error"
+ (fun `Error ->
+ eprintf "Hint:@ Recursive@ traversal@ of@ subdirectories@ \
+ was@ not@ enabled@ for@ this@ build,@ as@ the@ working@ \
+ directory does@ not@ look@ like@ an@ ocamlbuild@ project@ \
+ (no@ '_tags'@ or@ 'myocamlbuild.ml'@ file).@ \
+ If@ you@ have@ modules@ in@ subdirectories,@ you@ should@ add@ \
+ the@ option@ \"-r\"@ or@ create@ an@ empty@ '_tags'@ file.@\n\
+ @\n\
+ To@ enable@ recursive@ traversal@ for@ some@ subdirectories@ \
+ only,@ you@ can@ use@ the@ following@ '_tags'@ file:@\n\
+ @[<v 4>@,\
+ true: -traverse@,\
+ <dir1> or <dir2>: traverse@,\
+ @]"
+ );
| `just_try, Bad _ -> ()
end modules results
diff --git a/ocamlbuild/ocaml_specific.ml b/ocamlbuild/ocaml_specific.ml
index 43605d361..134a15332 100644
--- a/ocamlbuild/ocaml_specific.ml
+++ b/ocamlbuild/ocaml_specific.ml
@@ -598,18 +598,22 @@ let () =
(fun param -> S [A "-for-pack"; A param]);
pflag ["ocaml"; "native"; "compile"] "inline"
(fun param -> S [A "-inline"; A param]);
- pflag ["ocaml"; "compile"] "pp"
- (fun param -> S [A "-pp"; A param]);
- pflag ["ocaml"; "ocamldep"] "pp"
- (fun param -> S [A "-pp"; A param]);
- pflag ["ocaml"; "doc"] "pp"
- (fun param -> S [A "-pp"; A param]);
- pflag ["ocaml"; "infer_interface"] "pp"
- (fun param -> S [A "-pp"; A param]);
+ List.iter (fun pp ->
+ pflag ["ocaml"; "compile"] pp
+ (fun param -> S [A ("-" ^ pp); A param]);
+ pflag ["ocaml"; "ocamldep"] pp
+ (fun param -> S [A ("-" ^ pp); A param]);
+ pflag ["ocaml"; "doc"] pp
+ (fun param -> S [A ("-" ^ pp); A param]);
+ pflag ["ocaml"; "infer_interface"] pp
+ (fun param -> S [A ("-" ^ pp); A param])
+ ) ["pp"; "ppx"];
pflag ["ocaml";"compile";] "warn"
(fun param -> S [A "-w"; A param]);
pflag ["ocaml";"compile";] "warn_error"
(fun param -> S [A "-warn-error"; A param]);
+ pflag ["ocaml"; "compile"] "open"
+ (fun param -> S [A "-open"; A param]);
()
let camlp4_flags camlp4s =
@@ -683,6 +687,14 @@ flag ["ocaml"; "link"; "program"; "custom"; "byte"] (A "-custom");;
flag ["ocaml"; "link"; "library"; "custom"; "byte"] (A "-custom");;
flag ["ocaml"; "compile"; "profile"; "native"] (A "-p");;
flag ["ocaml"; "compile"; "no_alias_deps";] (A "-no-alias-deps");;
+flag ["ocaml"; "compile"; "strict_formats";] (A "-strict-formats");;
+flag ["ocaml"; "native"; "compile"; "opaque";] (A "-opaque");;
+flag ["ocaml"; "native"; "compile"; "no_float_const_prop";] (A "-no-float-const-prop");
+flag ["ocaml"; "compile"; "keep_locs";] (A "-keep-locs");
+flag ["ocaml"; "absname"; "compile"] (A "-absname");;
+flag ["ocaml"; "absname"; "infer_interface"] (A "-absname");;
+flag ["ocaml"; "byte"; "compile"; "compat_32";] (A "-compat-32");
+
(* threads, with or without findlib *)
flag ["ocaml"; "compile"; "thread"] (A "-thread");;
diff --git a/ocamlbuild/testsuite/internal.ml b/ocamlbuild/testsuite/internal.ml
index fec20c746..fc7ff98dd 100644
--- a/ocamlbuild/testsuite/internal.ml
+++ b/ocamlbuild/testsuite/internal.ml
@@ -162,7 +162,7 @@ let () = test "OutputObj"
let () = test "StrictSequenceFlag"
~options:[`no_ocamlfind; `quiet]
- ~description:"-strict_sequence tag"
+ ~description:"strict_sequence tag"
~tree:[T.f "hello.ml" ~content:"let () = 1; ()";
T.f "_tags" ~content:"true: strict_sequence\n"]
~failing_msg:"File \"hello.ml\", line 1, characters 9-10:
@@ -170,6 +170,17 @@ Error: This expression has type int but an expression was expected of type
unit\nCommand exited with code 2."
~targets:("hello.byte",[]) ();;
+let () = test "StrictFormatsFlag"
+ ~options:[`no_ocamlfind; `quiet]
+ ~description:"strict_format tag"
+ ~tree:[T.f "hello.ml" ~content:"let _ = Printf.printf \"%.10s\"";
+ T.f "_tags" ~content:"true: strict_formats\n"]
+ ~failing_msg:"File \"hello.ml\", line 1, characters 22-29:
+Error: invalid format \"%.10s\": at character number 0, \
+`precision' is incompatible with 's' in sub-format \"%.10s\"
+Command exited with code 2."
+ ~targets:("hello.byte",[]) ();;
+
let () = test "PrincipalFlag"
~options:[`no_ocamlfind; `quiet]
~description:"-principal tag"
@@ -282,5 +293,14 @@ debug, rectypes
~matching:[M.f "main.byte"]
~targets:("main.byte",[]) ();;
+let () = test "OpenTag"
+ ~description:"Test the parametrized tag for the new -open feature"
+ ~options:[`no_ocamlfind]
+ ~tree:[
+ T.f "test.ml" ~content:"let _ = map rev [ []; [3;2] ]";
+ T.f "_tags" ~content: "<test.*>: open(List)";
+ ]
+ ~matching:[M.f "test.byte"]
+ ~targets:("test.byte",[]) ();;
run ~root:"_test_internal";;
diff --git a/otherlibs/bigarray/bigarray_stubs.c b/otherlibs/bigarray/bigarray_stubs.c
index 5cb842a87..f2ccb92ba 100644
--- a/otherlibs/bigarray/bigarray_stubs.c
+++ b/otherlibs/bigarray/bigarray_stubs.c
@@ -293,7 +293,7 @@ value caml_ba_get_N(value vb, value * vind, int nind)
{ double * p = ((double *) b->data) + offset * 2;
return copy_two_doubles(p[0], p[1]); }
case CAML_BA_CHAR:
- return Val_int(((char *) b->data)[offset]);
+ return Val_int(((unsigned char *) b->data)[offset]);
}
}
@@ -750,7 +750,7 @@ static int caml_ba_compare(value v1, value v2)
case CAML_BA_FLOAT64:
DO_FLOAT_COMPARISON(double);
case CAML_BA_CHAR:
- DO_INTEGER_COMPARISON(char);
+ DO_INTEGER_COMPARISON(uint8);
case CAML_BA_SINT8:
DO_INTEGER_COMPARISON(int8);
case CAML_BA_UINT8:
@@ -1169,7 +1169,7 @@ CAMLprim value caml_ba_fill(value vb, value vinit)
case CAML_BA_SINT8:
case CAML_BA_UINT8: {
int init = Int_val(vinit);
- char * p;
+ unsigned char * p;
for (p = b->data; num_elts > 0; p++, num_elts--) *p = init;
break;
}
diff --git a/stdlib/camlinternalFormat.ml b/stdlib/camlinternalFormat.ml
index 983fc33a9..5dda3a7fc 100644
--- a/stdlib/camlinternalFormat.ml
+++ b/stdlib/camlinternalFormat.ml
@@ -1,19 +1,5 @@
open CamlinternalFormatBasics
-let legacy_behavior = true
-(** When this flag is enabled, the format parser tries to behave as
- the <4.02 implementations, in particular it ignores most benine
- nonsensical format. When the flag is disabled, it will reject any
- format that is not accepted by the specification.
-
- A typical example would be "%+ d": specifying both '+' (if the
- number is positive, pad with a '+' to get the same width as
- negative numbres) and ' ' (if the number is positive, pad with
- a space) does not make sense, but the legacy (< 4.02)
- implementation was happy to just ignore the space.
-*)
-
-
(******************************************************************************)
(* Tools to manipulate scanning set of chars (see %[...]) *)
@@ -1769,7 +1755,7 @@ fun pad prec fmt ->
(* Parse a string representing a format and create a fmt_ebb. *)
(* Raise an Failure exception in case of invalid format. *)
-let fmt_ebb_of_string str =
+let fmt_ebb_of_string ?legacy_behavior str =
(* Parameters naming convention: *)
(* - lit_start: start of the literal sequence. *)
(* - str_ind: current index in the string. *)
@@ -1786,6 +1772,22 @@ let fmt_ebb_of_string str =
(* - symb: char representing the conversion ('c', 's', 'd', ...). *)
(* - char_set: set of characters as bitmap (see scanf %[...]). *)
+ let legacy_behavior = match legacy_behavior with
+ | Some flag -> flag
+ | None -> true
+ (** When this flag is enabled, the format parser tries to behave as
+ the <4.02 implementations, in particular it ignores most benine
+ nonsensical format. When the flag is disabled, it will reject any
+ format that is not accepted by the specification.
+
+ A typical example would be "%+ d": specifying both '+' (if the
+ number is positive, pad with a '+' to get the same width as
+ negative numbres) and ' ' (if the number is positive, pad with
+ a space) does not make sense, but the legacy (< 4.02)
+ implementation was happy to just ignore the space.
+ *)
+ in
+
(* Raise a Failure with a friendly error message. *)
(* Used when the end of the format (or the current sub-format) was encoutered
unexpectedly. *)
diff --git a/stdlib/camlinternalFormat.mli b/stdlib/camlinternalFormat.mli
index 5c5b3e32a..dd8da62d2 100644
--- a/stdlib/camlinternalFormat.mli
+++ b/stdlib/camlinternalFormat.mli
@@ -55,7 +55,11 @@ val type_format :
('a, 'b, 'c, 'd, 'e, 'f) CamlinternalFormatBasics.fmtty ->
('a, 'b, 'c, 'd, 'e, 'f) CamlinternalFormatBasics.fmt
-val fmt_ebb_of_string : string -> ('b, 'c, 'e, 'f) fmt_ebb
+val fmt_ebb_of_string : ?legacy_behavior:bool -> string -> ('b, 'c, 'e, 'f) fmt_ebb
+(* warning: the optional flag legacy_behavior is EXPERIMENTAL and will
+ be removed in the next version. You must not set it explicitly. It
+ is only used by the type-checker implementation.
+*)
val format_of_string_fmtty :
string ->
diff --git a/stdlib/obj.ml b/stdlib/obj.ml
index d054d35c4..ac9695cdb 100644
--- a/stdlib/obj.ml
+++ b/stdlib/obj.ml
@@ -81,3 +81,8 @@ let extension_id x =
let slot = extension_slot x in
(obj (field slot 1) : int)
with Not_found -> invalid_arg "Obj.extension_id"
+
+let extension_slot x =
+ try
+ extension_slot x
+ with Not_found -> invalid_arg "Obj.extension_slot"
diff --git a/stdlib/obj.mli b/stdlib/obj.mli
index 5181e2a22..08b8a4f64 100644
--- a/stdlib/obj.mli
+++ b/stdlib/obj.mli
@@ -55,6 +55,7 @@ val unaligned_tag : int (* should never happen @since 3.11.0 *)
val extension_name : 'a -> string
val extension_id : 'a -> int
+val extension_slot : 'a -> t
(** The following two functions are deprecated. Use module {!Marshal}
instead. *)
diff --git a/tools/ocamlcp.ml b/tools/ocamlcp.ml
index 75adcb82e..51559aea3 100644
--- a/tools/ocamlcp.ml
+++ b/tools/ocamlcp.ml
@@ -83,6 +83,7 @@ module Options = Main_args.Make_bytecomp_options (struct
let _safe_string = option "-safe-string"
let _short_paths = option "-short-paths"
let _strict_sequence = option "-strict-sequence"
+ let _strict_formats = option "-strict-formats"
let _thread () = option "-thread" ()
let _vmthread () = option "-vmthread" ()
let _unsafe = option "-unsafe"
diff --git a/tools/ocamloptp.ml b/tools/ocamloptp.ml
index 4e299c96e..0b788843f 100644
--- a/tools/ocamloptp.ml
+++ b/tools/ocamloptp.ml
@@ -86,6 +86,7 @@ module Options = Main_args.Make_optcomp_options (struct
let _safe_string = option "-safe-string"
let _short_paths = option "-short-paths"
let _strict_sequence = option "-strict-sequence"
+ let _strict_formats = option "-strict-formats"
let _shared = option "-shared"
let _thread = option "-thread"
let _unsafe = option "-unsafe"
diff --git a/toplevel/opttopmain.ml b/toplevel/opttopmain.ml
index 941c3ec26..51d1daac5 100644
--- a/toplevel/opttopmain.ml
+++ b/toplevel/opttopmain.ml
@@ -81,6 +81,7 @@ module Options = Main_args.Make_opttop_options (struct
let _real_paths = set real_paths
let _rectypes = set recursive_types
let _strict_sequence = set strict_sequence
+ let _strict_formats = set strict_formats
let _S = set keep_asm_file
let _short_paths = clear real_paths
let _stdin () = file_argument ""
diff --git a/toplevel/topmain.ml b/toplevel/topmain.ml
index 045be0b75..d1dbeca9d 100644
--- a/toplevel/topmain.ml
+++ b/toplevel/topmain.ml
@@ -82,6 +82,7 @@ module Options = Main_args.Make_bytetop_options (struct
let _short_paths = clear real_paths
let _stdin () = file_argument ""
let _strict_sequence = set strict_sequence
+ let _strict_formats = set strict_formats
let _unsafe = set fast
let _unsafe_string = set unsafe_string
let _version () = print_version ()
diff --git a/typing/envaux.ml b/typing/envaux.ml
index af86fd25b..708da443d 100644
--- a/typing/envaux.ml
+++ b/typing/envaux.ml
@@ -28,7 +28,7 @@ let reset_cache () =
Env.reset_cache()
let extract_sig env mty =
- match Mtype.scrape env mty with
+ match Env.scrape_alias env mty with
Mty_signature sg -> sg
| _ -> fatal_error "Envaux.extract_sig"
diff --git a/typing/typecore.ml b/typing/typecore.ml
index 46a11704e..16a310d60 100644
--- a/typing/typecore.ml
+++ b/typing/typecore.ml
@@ -2975,7 +2975,8 @@ and type_format loc str env =
| End_of_format ->
mk_constr "End_of_format" []
in
- let Fmt_EBB fmt = fmt_ebb_of_string str in
+ let legacy_behavior = not !Clflags.strict_formats in
+ let Fmt_EBB fmt = fmt_ebb_of_string ~legacy_behavior str in
mk_constr "Format" [ mk_fmt fmt; mk_string str ]
))
with Failure msg ->
diff --git a/utils/clflags.ml b/utils/clflags.ml
index e771fec5d..57834ccf9 100644
--- a/utils/clflags.ml
+++ b/utils/clflags.ml
@@ -50,6 +50,7 @@ and principal = ref false (* -principal *)
and real_paths = ref true (* -short-paths *)
and recursive_types = ref false (* -rectypes *)
and strict_sequence = ref false (* -strict-sequence *)
+and strict_formats = ref false (* -strict-formats *)
and applicative_functors = ref true (* -no-app-funct *)
and make_runtime = ref false (* -make-runtime *)
and gprofile = ref false (* -p *)
diff --git a/utils/clflags.mli b/utils/clflags.mli
index 97dca6f49..7e51cf33d 100644
--- a/utils/clflags.mli
+++ b/utils/clflags.mli
@@ -47,6 +47,7 @@ val principal : bool ref
val real_paths : bool ref
val recursive_types : bool ref
val strict_sequence : bool ref
+val strict_formats : bool ref
val applicative_functors : bool ref
val make_runtime : bool ref
val gprofile : bool ref